1/* 
    2% ===================================================================
    3% File 'logicmoo_u_cyc_kb_tinykb.pfc'
    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 make us more like Cyc
   12%
   13% Dec 13, 2035
   14% Douglas Miles
   15*/
   16%:- module(tiny_kb,['TINYKB-ASSERTION'/5, 'TINYKB-ASSERTION'/6]).
   17:- module(logicmoo_u_cyc_kb_tinykb,
   18          [
   19          
   20          /*
   21        logicmoo_i_cyc_xform/0,
   22         addTinyCycL/1,
   23         isa_db/2,
   24         ist_tiny/2,
   25          
   26         loadTinyKB/0,
   27         
   28         call_tiny_stub/3,
   29         
   30         
   31         
   32         print_assertion/3,
   33         sent_to_conseq/2,
   34         tinyAssertion/3,
   35         tinyAssertion0/3,
   36         tinyKB/1,
   37         tinyKB/3,
   38         tinyKB1/1,
   39         tinyKB2/1,
   40         tinyKB_All/3,
   41         tinyKB_wstr/1,
   42         tiny_support/3,
   43   
   44   %make_el_stub/4,
   45   %cyc_to_mpred_idiom/2,
   46   */
   47   
   48          ]).   49
   50:- set_module(class(development)).   51
   52:- use_module(library(pfc_lib)).   53:- set_fileAssertMt(baseKB).   54
   55%:- if(current_predicate(rdf_rewrite:arity/2)).
   56:- kb_global(rdf_rewrite:arity/2).   57%:- endif.
   58
   59%:- use_module(library('filestreams')).
   60% ===================================================================
   61% OPERATOR PRECEDANCE
   62% ===================================================================
   63
   64:- op(500,fx,'~').   65:- op(1050,xfx,('==>')).   66:- op(1050,xfx,'<==>').   67:- op(1050,xfx,('<-')).   68:- op(1100,fx,('==>')).   69:- op(1150,xfx,('::::')).   70:- 
   71 system:((
   72 op(1199,fx,('==>')), 
   73 op(1190,xfx,('::::')),
   74 op(1180,xfx,('==>')),
   75 op(1170,xfx,'<==>'),  
   76 op(1160,xfx,('<-')),
   77 op(1150,xfx,'=>'),
   78 op(1140,xfx,'<='),
   79 op(1130,xfx,'<=>'), 
   80 op(600,yfx,'&'), 
   81 op(600,yfx,'v'),
   82 op(350,xfx,'xor'),
   83 op(300,fx,'~'))).   84
   85:- baseKB:kb_shared((baseKB:mtDressedMt/1,baseKB:mtUndressedMt/1)).   86
   87:- dynamic(tinyKB9/1).   88:- multifile(tinyKB9/1).   89
   90
   91:- dynamic(cwtdl_failed/1).   92
   93cwtdl(Goal,DL,TL):-
   94  quietly((ignore((nortrace,
   95   (show_failure(why,catch(call_with_time_limit(TL,(((call_with_depth_limit(Goal,DL,DLE),DLE\==depth_limit_exceeded)))),E,(dmsg(E:cwtdl(Goal,DL,TL)),fail)))
   96     ->true;
   97    assert(cwtdl_failed(Goal))))))).
   98
   99:- meta_predicate((cwtdl(0,+,+),transfer_predicate(?,0,0),transTiny(?,0))).  100
  101
  102%:- in_cmt(doall((filematch(logicmoo('plarkc/mpred_cyc_kb_tinykb.pl'),F),source_file(X,F),predicate_property(X,static),X\='$pldoc'(_G8428,_G8429,_G8430,_G8431),listing(X)))).
  103
  104% https://www.dropbox.com/sh/9jexwgm9amw80mj/AADieFX-yQ_p6AfoF-Yy4muAa?dl=0
  105
  106% https://www.dropbox.com/sh/n506umkk6tqqhkm/AACFbLDyCAkf392zE2Z05u2ta?dl=0
  107
  108transfer_predicate(C,If,Q):-doall((clause(C,true,Ref),If,Q,on_x_log_throw(erase(Ref)))).
  109
  110transTiny(Template,If):-transfer_predicate(tinyK8(Template),If,once(ain(Template))).
  111
  112
  113reallyLoadTiny:- transTiny(tCol(X),ground(X)).
  114reallyLoadTiny:- transTiny(arity(X,Y),ground((X,Y))).
  115reallyLoadTiny:- transTiny(genls(X,Y),((X\=ftAtomicTerm,ground((X,Y))))).
  116reallyLoadTiny:- mpred_trace.
  117reallyLoadTiny:- transTiny(genls(X,Y),((ground((X,Y))))).
  118%TODO_VERIFY_STILL_UNNEEDED :- retract_all((ftClosedAtomicTerm(A) :- ftAtomicTerm(A))).
  119%TODO_VERIFY_STILL_UNNEEDED :- mpred_withdraw(genls(ftAtomicTerm,ftClosedAtomicTerm)).
  120reallyLoadTiny:- transTiny(genlMt(X,Y),writeq((X,Y))).
  121reallyLoadTiny:- transTiny(ttExpressionType(X),ground(X)).
  122
  123%TODO_VERIFY_STILL_UNNEEDED :-mpred_withdraw(genls(ftAtomicTerm,ftClosedAtomicTerm)).
  124
  125%TODO_VERIFY_STILL_UNNEEDED :-retract_all((ftClosedAtomicTerm(A) :- ftAtomicTerm(A))).
  126reallyLoadTiny:- mpred_notrace.
  127
  128
  129:- if(false).  130:- doall(reallyLoadTiny).  131:- endif.  132
  133
  134
  135
  136:- (baseKB:(ain((((cycl(X),{must(cyc_to_pdkb(X,Y))}) ==> clif(Y)))))).  137
  138%%TODO FIX  :- ain(baseKB:(((cycl('$VAR'('X')),{must(cyc_to_pdkb('$VAR'('X'),'$VAR'('Y')))}) ==> clif('$VAR'('Y'))))).
  139% ?-listing(cycl).
  140
  141%TODO FIX :- must(isa(iExplorer2,tHominid)).
  142%TODO FIX :- must(tHominid(iExplorer2)).
  143
  144% tHominid(iExplorer2).
  145
  146
  147
  148
  149% extra_tcol(Mt,A,ID):- isTT(Mt,t(genls,A,Other),ID),atom(Other),Other\=A,'Thing'\=Other.
  150% extra_tcol(Mt,A,ID):- isTT(Mt,t(genls,Other,A),ID),atom(Other),Other\=A,'Thing'\=Other.
  151
  152
  153% :- kb_shared((  argGenl/3,argIsa/3,argQuotedIsa/3)).
  154
  155:- dynamic((
  156  
  157        % argGenl/3,argIsa/3,argQuotedIsa/3,
  158
  159        
  160        baseKB:cycPrepending/2,
  161        baseKB:cyc_to_plarkc/2,
  162        lmcache:isCycUnavailable_known/1,
  163        baseKB:mpred_to_cyc/2)).  164
  165:- dynamic(lmcache:isCycAvailable_known/0).  166:- volatile(lmcache:isCycAvailable_known/0).  167
  168isa_db(I,C):-clause(isa(I,C),true).
  169
  170:- asserta(elmt:elmt_is_a_module).  171:- set_module(elmt:class(development)).  172
  173:- forall(between(4,9,N),kb_global(elmt:exactlyAssertedELMT/N)).  174
  175/*
  176:- kb_shared((elmt:exactlyAssertedELMT/4,elmt:exactlyAssertedELMT/5,elmt:exactlyAssertedELMT/6,elmt:exactlyAssertedELMT/7)).
  177:- dynamic((exactlyAssertedEL_next/4,exactlyAssertedEL_next/5,exactlyAssertedEL_next/6,exactlyAssertedEL_next/7)).
  178:- dynamic((exactlyAssertedEL_first/4,exactlyAssertedEL_first/5,exactlyAssertedEL_first/6,exactlyAssertedEL_first/7)).
  179:- dynamic(assertedTinyKB_implies_first/4).
  180:- dynamic(assertedTinyKB_not_first/3).
  181:- dynamic((exactlyAssertedEL_first/5,exactlyAssertedEL_with_vars/5,exactlyAssertedEL_with_vars/6,assertedTinyKB_implies_Already/4)).
  182*/
  183
  184 % :- set_prolog_flag(subclause_expansion,true).
  185
  186:- dynamic(tinyKB0/1).  187
  188
  189tinyKB_wstr(P):-baseKB:mtUndressedMt(MT),tinyKB(P,MT,_).
  190tinyKB_wstr(ist(MT,P)):-baseKB:mtDressedMt(MT),tinyKB(P,MT,_).
  191
  192
  193/*
  194:- dynamic(argIsa/3).
  195:- kb_shared(argIsa/3).
  196:- dynamic(argGenl/3).
  197:- kb_shared(argGenl/3).
  198:- dynamic(argQuotedIsa/3).
  199:- kb_shared(argQuotedIsa/3).
  200isa(I,C):-elmt:exactlyAssertedELMT(isa,I,C,_,_).
  201genls(I,C):-elmt:exactlyAssertedELMT(genls,I,C,_,_).
  202arity(I,C):-elmt:exactlyAssertedELMT(arity,I,C,_,_).
  203argIsa(P,N,C):-elmt:exactlyAssertedELMT(argIsa,P,N,C,_,_).
  204argGenl(P,N,C):-elmt:exactlyAssertedELMT(argGenl,P,N,C,_,_).
  205argQuotedIsa(P,N,C):-elmt:exactlyAssertedELMT(argQuotedIsa,P,N,C,_,_).
  206*/
  207% queuedTinyKB(CycL,MT):- (baseKB:mtUndressedMt(MT);baseKB:mtDressedMt(MT)),(STR=vStrMon;STR=vStrDef),  tinyKB_All(CycL,MT,STR),
  208% \+ clause(elmt:exactlyAssertedELMT(CycL,_,_,_),true).
  209% queuedTinyKB(CycL):-baseKB:mtUndressedMt(MT),queuedTinyKB(CycL,MT).
  210% queuedTinyKB(ist(MT,CycL)):-baseKB:mtDressedMt(MT),queuedTinyKB(CycL,MT).
  211
  212tinyKBA(P):-tinyKB_All(P,_MT,_)*->true;find_and_call(tinyKB0(P)).
  213
  214ist_tiny(MT,P):-tinyKB(P,MT,vStrMon).
  215ist_tiny(MT,P):-tinyKB(P,MT,vStrDef).
  216
  217%TODO ADD BACK AFTER OPTIZING
  218tinyKB(P):- current_prolog_flag(logicmoo_load_state,making_renames),!,tinyKBA(P).
  219tinyKB(P):- tinyKBA(P).
  220tinyKB(ist(MT,P)):- (nonvar(MT)->true;baseKB:mtDressedMt(MT)),!,tinyKB_All(P,MT,_).
  221
  222
  223tinyKB1(P):- current_prolog_flag(logicmoo_load_state,making_renames),!,tinyKBA(P).
  224                 
  225tinyKB1(D):-no_repeats(tinyKB2(D)).
  226tinyKB2(P):-tinyKBA(P)*->true;tinyKB0(P).
  227tinyKB2(isa(C1,C3)):-nonvar(C1),!,tinyKBA(isa(C1,C2)),tinyKB2(genls(C2,C3)).
  228tinyKB2(genls(C1,C3)):-nonvar(C1),tinyKBA(genls(C1,C2)),tinyKB2(genls(C2,C3)).
  229/*
  230tinyKB2(genls(C1,C3)):-nonvar(C1),tinyKB0(genls(C1,C2)),tinyKB0(genls(C2,C3)).
  231tinyKB2(genls(C1,C4)):-nonvar(C1),tinyKB0(genls(C1,C2)),tinyKB0(genls(C2,C3)),tinyKB0(genls(C3,C4)).
  232tinyKB2(genls(C1,C5)):-nonvar(C1),tinyKB0(genls(C1,C2)),tinyKB0(genls(C2,C3)),tinyKB0(genls(C3,C4)),tinyKB0(genls(C4,C5)).
  233*/
  234%TODO ADD BACK AFTER OPTIZING tinyKB(P):-nonvar(P),if_defined(P).
  235
  236tinyKB(PO,MT,STR):-
  237  (nonvar(MT)->true;(baseKB:mtUndressedMt(MT);baseKB:mtDressedMt(MT))),
  238  (nonvar(STR)->true;(STR=vStrMon;STR=vStrDef)),
  239  tinyKB_All(PO,MT,STR).
  240
  241tinyKB_All(V,MT,STR):- tinyAssertion(V,MT,STR).
  242tinyKB_All(PO,MT,STR):- % current_predicate(_:'TINYKB-ASSERTION'/5),!,
  243    if_defined(tiny_kb_ASSERTION(PLISTIn,PROPS)),
  244        once((sexpr_sterm_to_pterm(PLISTIn,P),
  245               memberchk(amt(MT),PROPS),
  246               memberchk(str(STR),PROPS), 
  247              (member(vars(VARS),PROPS)->(nput_variable_names( []),fixvars(P,0,VARS,PO),nput_variable_names( PO));PO=P ))).
  248
  249loadTinyKB:-forall((tinyKB(C,MT,STR),cyc_to_pdkb(C,P)),((print_assertion(P,MT,STR),wdmsg(ain(P))))).
  250% ssveTinyKB:-tinyKB_All(tinyKB(P,MT,STR),tell((print_assertion(P,MT,STR),ain(P)))).
  251
  252print_assertion(P,MT,STR):- P=..PL,append([exactlyAssertedELMT|PL],[MT,STR],PPL),PP=..PPL, 
  253 portray_clause(current_output,elmt:PP,[numbervars(false)]).
  254
  255
  256:- set_prolog_flag(expect_pfc_file,some_preds).  257baseKB:mtUndressedMt('iUniversalVocabularyImplementationMt').
  258baseKB:mtUndressedMt('iLogicalTruthImplementationMt').
  259baseKB:mtUndressedMt('iCoreCycLImplementationMt').
  260baseKB:mtUndressedMt('iUniversalVocabularyMt').
  261baseKB:mtUndressedMt('iLogicalTruthMt').
  262baseKB:mtUndressedMt('iCoreCycLMt').
  263baseKB:mtUndressedMt('baseKB').
  264
  265baseKB:mtDressedMt('iBookkeepingMt').
  266baseKB:mtDressedMt('iEnglishParaphraseMt').
  267baseKB:mtDressedMt('iGeneralEnglishMt').
  268baseKB:mtDressedMt('iTemporaryEnglishParaphraseMt').
  269baseKB:mtDressedMt('iAct_GeneralCycKE').
  270baseKB:mtDressedMt('iTechnicalEnglishLexicalMt').
  271
  272:- set_prolog_flag(expect_pfc_file,never).  273
  274into_mpred_form_tiny(V,V):- current_prolog_flag(logicmoo_load_state,making_renames),!.
  275into_mpred_form_tiny(V,R):- into_mpred_form(V,R),!. 
  276
  277call_tiny_stub(V,MT,STR):-into_mpred_form_tiny(V,M),!,M=..ML,((ML=[t|ARGS]-> true; ARGS=ML)),
  278 CALL=..[exactlyAssertedELMT|ARGS],!,
  279 baseKB:call(elmt:CALL,MT,STR).
  280
  281make_el_stub(V,MT,STR,CALL):-into_mpred_form_tiny(V,M),!,M=..ML,((ML=[t|ARGS]-> true; ARGS=ML)),append(ARGS,[MT,STR],CARGS),CALL=..[elmt:exactlyAssertedELMT|CARGS],!.
  282
  283tinyAssertion(V,MT,STR):- 
  284 nonvar(V) -> call_tiny_stub(V,MT,STR);
  285  (tinyAssertion0(W,MT,STR),once(into_mpred_form_tiny(W,V))).
  286
  287tinyAssertion0(t(A,B,C,D,E),MT,STR):-elmt:exactlyAssertedELMT(A,B,C,D,E,MT,STR).
  288tinyAssertion0(t(A,B,C,D),MT,STR):-elmt:exactlyAssertedELMT(A,B,C,D,MT,STR).
  289tinyAssertion0(t(A,B,C),MT,STR):-elmt:exactlyAssertedELMT(A,B,C,MT,STR).
  290tinyAssertion0(t(A,B),MT,STR):-elmt:exactlyAssertedELMT(A,B,MT,STR).
  291
  292
  293addTinyCycL(CycLIn):- into_mpred_form_tiny(CycLIn,CycL),
  294  ignore((tiny_support(CycL,_MT,CALL),must(retract(CALL)))),!,
  295  addCycL(CycL),!.
  296
  297
  298
  299tiny_support(CycLIn,MT,CALL):- compound(CycLIn),!,into_mpred_form_tiny(CycLIn,CycL), 
  300  CycL=..[F|Args], append(Args,[MT,_STR],WMT),
  301  CCALL=..[exactlyAssertedELMT,F|WMT],!,
  302  ((baseKB:clause(elmt:CCALL,true), CCALL=CALL) ; baseKB:clause(elmt:CCALL,(CALL,_))).
  303tiny_support(CycLOut,MT,CALL):- between(4,9,Len),
  304 functor(CCALL,exactlyAssertedELMT,Len),
  305 CCALL=..[exactlyAssertedELMT,F|WMT],
  306 append(Args,[MT,_STR],WMT),
  307 baseKB:call(elmt:CCALL),(atom(F)->CycL=..[F|Args];append_termlist(F,Args,CycL)),((baseKB:clause(CCALL,true), CCALL=CALL) ; baseKB:clause(CCALL,(CALL,_))), fully_expand(CycL,CycLOut).
  308
  309
  310logicmoo_i_cyc_xform:- dmsg("Compiling tinyKB should take under a minute"),
  311    gripe_time(60,baseKB:qcompile(library('logicmoo/plarkc/logicmoo_i_cyc_xform.pfc'))).
  312
  313
  314:- after_boot(dmsg("Dont forget to ?- logicmoo_i_cyc_xform.")).  315% :- logicmoo_i_cyc_xform.
  316
  317:- set_module(elmt:class(development)).  318
  319%:- dynamic((elmt:exactlyAssertedELMT/4,elmt:exactlyAssertedELMT/5,elmt:exactlyAssertedELMT/6,elmt:exactlyAssertedELMT/7)).
  320:- dynamic((exactlyAssertedEL_next/4,exactlyAssertedEL_next/5,exactlyAssertedEL_next/6,exactlyAssertedEL_next/7)).  321:- dynamic((exactlyAssertedEL_first/4,exactlyAssertedEL_first/5,exactlyAssertedEL_first/6,exactlyAssertedEL_first/7)).  322:- dynamic(assertedTinyKB_implies_first/4).  323:- dynamic(assertedTinyKB_not_first/3).  324:- dynamic((exactlyAssertedEL_first/5,exactlyAssertedEL_with_vars/5,exactlyAssertedEL_with_vars/6,assertedTinyKB_implies_Already/4)).  325:- dynamic(assertedTinyKB_not/3).  326:- dynamic(assertedTinyKB_implies/4).  327
  328%:- export((elmt:exactlyAssertedELMT/4,elmt:exactlyAssertedELMT/5,elmt:exactlyAssertedELMT/6,elmt:exactlyAssertedELMT/7)).
  329:- export((exactlyAssertedEL_next/4,exactlyAssertedEL_next/5,exactlyAssertedEL_next/6,exactlyAssertedEL_next/7)).  330:- export((exactlyAssertedEL_first/4,exactlyAssertedEL_first/5,exactlyAssertedEL_first/6,exactlyAssertedEL_first/7)).  331:- export(assertedTinyKB_implies_first/4).  332:- export(assertedTinyKB_not_first/3).  333:- export((exactlyAssertedEL_first/5,exactlyAssertedEL_with_vars/5,exactlyAssertedEL_with_vars/6,assertedTinyKB_implies_Already/4)).  334:- export(assertedTinyKB_not/3).  335:- export(assertedTinyKB_implies/4).  336
  337:- style_check(-singleton).  338:- style_check(-discontiguous).  339% :-style_check(-atom).
  340% :-style_check(-string).
  341:- set_prolog_flag(double_quotes,string).  342:- set_prolog_flag(access_level,system).  343%:- discontiguous elmt:exactlyAssertedELMT/5. 
  344
  345elmt:exactlyAssertedELMT(A,B,MT,STR):- exactlyAssertedEL_first(A,B,MT,STR),true.
  346elmt:exactlyAssertedELMT(A,B,C,MT,STR):- exactlyAssertedEL_first(A,B,C,MT,STR),true.
  347elmt:exactlyAssertedELMT(A,B,C,D,MT,STR):- exactlyAssertedEL_first(A,B,C,D,MT,STR),true.
  348elmt:exactlyAssertedELMT(Pred,A,C,MT,STR):- exactlyAssertedEL_with_vars(Pred,A,C,MT,STR),true.
  349elmt:exactlyAssertedELMT(Pred,A,C,D,MT,STR):- exactlyAssertedEL_with_vars(Pred,A,C,D,MT,STR),true.
  350
  351elmt:exactlyAssertedELMT(implies,A,C,MT,STR):- assertedTinyKB_implies_first(A,C,MT,STR),true.
  352elmt:exactlyAssertedELMT(not,What,MT,STR):- assertedTinyKB_not_first(What,MT,STR),true.
  353elmt:exactlyAssertedELMT(A,B,MT,STR):- exactlyAssertedEL_next(A,B,MT,STR),true.
  354elmt:exactlyAssertedELMT(A,B,C,MT,STR):- exactlyAssertedEL_next(A,B,C,MT,STR),true.
  355elmt:exactlyAssertedELMT(A,B,C,D,MT,STR):- exactlyAssertedEL_next(A,B,C,D,MT,STR),true.
  356elmt:exactlyAssertedELMT(A,B,C,D,E,MT,STR):- exactlyAssertedEL_next(A,B,C,D,E,MT,STR),true.
  357elmt:exactlyAssertedELMT(implies,A,C,MT,STR):- assertedTinyKB_implies(A,C,MT,STR),not(if_defined(is_better_backchained(=>(A,C)))).
  358elmt:exactlyAssertedELMT(implies,A,C,MT,STR):- assertedTinyKB_implies(A,C,MT,STR),if_defined(is_better_backchained(=>(A,C))).
  359elmt:exactlyAssertedELMT(not,What,MT,STR):- assertedTinyKB_not(What,MT,STR),true.
  360
  361
  362:- install_constant_renamer_until_eof.  363:- discontiguous exactlyAssertedEL_first/5.  364
  365%:- must_not_be_pfc_file.
  366
  367exactlyAssertedEL_first(isa, xor, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  368exactlyAssertedEL_first(isa, xor, 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
  369exactlyAssertedEL_first(isa, xor, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  370
  371:- if( \+ current_prolog_flag(runtime_debug, 0)).  372:- listing(exactlyAssertedEL_first/5).  373:- endif.  374:- sanity(clause_asserted(exactlyAssertedEL_first(isa, xor, rtLogicalConnective, iUniversalVocabularyMt, vStrDef))).  375
  376exactlyAssertedEL_first(isa, xor, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  377exactlyAssertedEL_first(isa, xor, 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
  378exactlyAssertedEL_first(isa, unknownSentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  379exactlyAssertedEL_first(isa, unitMultiplicationFactor, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  380exactlyAssertedEL_first(isa, trueSubL, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  381exactlyAssertedEL_first(isa, trueSubL, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  382exactlyAssertedEL_first(isa, trueSubL, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  383exactlyAssertedEL_first(isa, trueSentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  384exactlyAssertedEL_first(isa, trueRule, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  385
  386
  387exactlyAssertedEL_first(isa, transitiveViaArgInverse, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  388exactlyAssertedEL_first(isa, transitiveViaArgInverse, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  389exactlyAssertedEL_first(isa, transitiveViaArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  390exactlyAssertedEL_first(isa, transitiveViaArg, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  391exactlyAssertedEL_first(isa, thereExists, 'Quantifier', 'LogicalTruthMt', vStrDef).
  392exactlyAssertedEL_first(isa, thereExists, 'ExistentialQuantifier', 'UniversalVocabularyMt', vStrDef).
  393exactlyAssertedEL_first(isa, thereExists, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  394exactlyAssertedEL_first(isa, thereExistExactly, 'ExistentialQuantifier-Bounded', 'UniversalVocabularyMt', vStrDef).
  395exactlyAssertedEL_first(isa, thereExistAtMost, 'ExistentialQuantifier-Bounded', 'UniversalVocabularyMt', vStrDef).
  396exactlyAssertedEL_first(isa, thereExistAtLeast, 'ExistentialQuantifier-Bounded', 'UniversalVocabularyMt', vStrDef).
  397exactlyAssertedEL_first(isa, termOfUnit, 'ReformulatorIrrelevantFORT', 'UniversalVocabularyMt', vStrDef).
  398exactlyAssertedEL_first(isa, termOfUnit, tPred, 'LogicalTruthImplementationMt', vStrDef).
  399exactlyAssertedEL_first(isa, termOfUnit, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  400exactlyAssertedEL_first(isa, termOfUnit, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  401exactlyAssertedEL_first(isa, termOfUnit, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  402exactlyAssertedEL_first(isa, termExternalIDString, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  403exactlyAssertedEL_first(isa, termDependsOn, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  404exactlyAssertedEL_first(isa, termDependsOn, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  405exactlyAssertedEL_first(isa, termChosen, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  406exactlyAssertedEL_first(isa, termChosen, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  407exactlyAssertedEL_first(isa, synonymousExternalConcept, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  408exactlyAssertedEL_first(isa, substring, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  409exactlyAssertedEL_first(isa, substring, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  410exactlyAssertedEL_first(isa, substring, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  411exactlyAssertedEL_first(isa, substring, 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  412exactlyAssertedEL_first(isa, subsetOf, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  413exactlyAssertedEL_first(isa, subsetOf, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  414exactlyAssertedEL_first(isa, skolemizeForward, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  415exactlyAssertedEL_first(isa, skolem, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  416exactlyAssertedEL_first(isa, skolem, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  417exactlyAssertedEL_first(isa, singleEntryFormatInArgs, 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
  418exactlyAssertedEL_first(isa, singleEntryFormatInArgs, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  419exactlyAssertedEL_first(isa, singleEntryFormatInArgs, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  420exactlyAssertedEL_first(isa, siblingDisjointExceptions, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  421exactlyAssertedEL_first(isa, siblingDisjointExceptions, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  422exactlyAssertedEL_first(isa, sharedNotes, 'DocumentationPredicate', 'UniversalVocabularyMt', vStrDef).
  423exactlyAssertedEL_first(isa, sharedNotes, 'DistributingMetaKnowledgePredicate', 'UniversalVocabularyMt', vStrDef).
  424exactlyAssertedEL_first(isa, sharedNotes, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  425exactlyAssertedEL_first(isa, sentenceTruth, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  426exactlyAssertedEL_first(isa, sentenceImplies, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  427exactlyAssertedEL_first(isa, sentenceImplies, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  428exactlyAssertedEL_first(isa, sentenceEquiv, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  429exactlyAssertedEL_first(isa, sentenceEquiv, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  430exactlyAssertedEL_first(isa, sentenceEquiv, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  431exactlyAssertedEL_first(isa, sentenceEquiv, 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
  432exactlyAssertedEL_first(isa, sentenceDesignationArgnum, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  433exactlyAssertedEL_first(isa, scopingArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  434exactlyAssertedEL_first(isa, salientAssertions, 'DocumentationPredicate', 'UniversalVocabularyMt', vStrDef).
  435exactlyAssertedEL_first(isa, salientAssertions, 'DistributingMetaKnowledgePredicate', 'UniversalVocabularyMt', vStrDef).
  436exactlyAssertedEL_first(isa, salientAssertions, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  437exactlyAssertedEL_first(isa, ruleTemplateDirection, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  438exactlyAssertedEL_first(isa, ruleTemplateDirection, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  439exactlyAssertedEL_first(isa, ruleAfterRemoving, tPred, 'CoreCycLImplementationMt', vStrDef).
  440exactlyAssertedEL_first(isa, ruleAfterRemoving, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  441exactlyAssertedEL_first(isa, ruleAfterRemoving, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  442exactlyAssertedEL_first(isa, ruleAfterAdding, tPred, 'CoreCycLImplementationMt', vStrDef).
  443exactlyAssertedEL_first(isa, ruleAfterAdding, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  444exactlyAssertedEL_first(isa, ruleAfterAdding, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  445exactlyAssertedEL_first(isa, rewriteOf, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  446exactlyAssertedEL_first(isa, rewriteOf, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  447exactlyAssertedEL_first(isa, rewriteOf, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  448exactlyAssertedEL_first(isa, rewriteOf, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  449exactlyAssertedEL_first(isa, rewriteOf, 'CycLReformulationRulePredicate', 'UniversalVocabularyMt', vStrDef).
  450exactlyAssertedEL_first(isa, resultQuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  451exactlyAssertedEL_first(isa, resultQuotedIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  452exactlyAssertedEL_first(isa, resultIsaArgIsa, 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
  453exactlyAssertedEL_first(isa, resultIsaArgIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  454exactlyAssertedEL_first(isa, resultIsaArgIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  455exactlyAssertedEL_first(isa, resultIsaArg, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  456exactlyAssertedEL_first(isa, resultIsaArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  457exactlyAssertedEL_first(isa, resultIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  458exactlyAssertedEL_first(isa, resultIsa, tPred, 'LogicalTruthMt', vStrDef).
  459exactlyAssertedEL_first(isa, resultIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  460exactlyAssertedEL_first(isa, resultIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  461exactlyAssertedEL_first(isa, resultGenlArg, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  462exactlyAssertedEL_first(isa, resultGenlArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  463exactlyAssertedEL_first(isa, resultGenl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  464exactlyAssertedEL_first(isa, resultGenl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  465exactlyAssertedEL_first(isa, resultGenl, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  466exactlyAssertedEL_first(isa, requiredArg3Pred, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  467exactlyAssertedEL_first(isa, requiredArg2Pred, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  468exactlyAssertedEL_first(isa, requiredArg1Pred, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  469exactlyAssertedEL_first(isa, relationMemberInstance, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  470exactlyAssertedEL_first(isa, relationInstanceMember, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  471exactlyAssertedEL_first(isa, relationInstanceExists, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  472exactlyAssertedEL_first(isa, relationInstanceAll, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  473exactlyAssertedEL_first(isa, relationExpansion, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  474exactlyAssertedEL_first(isa, relationExistsMinAll, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  475exactlyAssertedEL_first(isa, relationExistsMaxAll, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  476exactlyAssertedEL_first(isa, relationExistsInstance, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  477exactlyAssertedEL_first(isa, relationExistsCountAll, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  478exactlyAssertedEL_first(isa, relationExistsAll, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  479exactlyAssertedEL_first(isa, relationAllInstance, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  480exactlyAssertedEL_first(isa, relationAllExistsMin, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  481exactlyAssertedEL_first(isa, relationAllExistsMax, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  482exactlyAssertedEL_first(isa, relationAllExistsCount, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  483exactlyAssertedEL_first(isa, relationAllExists, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  484exactlyAssertedEL_first(isa, relationAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  485exactlyAssertedEL_first(isa, reformulatorRuleProperties, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  486exactlyAssertedEL_first(isa, reformulatorRuleProperties, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  487exactlyAssertedEL_first(isa, reformulatorRule, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  488exactlyAssertedEL_first(isa, reformulatorRule, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  489exactlyAssertedEL_first(isa, reformulatorRule, 'CycLReformulationRulePredicate', 'UniversalVocabularyMt', vStrDef).
  490exactlyAssertedEL_first(isa, reformulatorEquiv, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  491exactlyAssertedEL_first(isa, reformulatorEquiv, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  492exactlyAssertedEL_first(isa, reformulatorEquiv, 'CycLReformulationRulePredicate', 'UniversalVocabularyMt', vStrDef).
  493exactlyAssertedEL_first(isa, reformulatorEquals, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  494exactlyAssertedEL_first(isa, reformulatorEquals, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  495exactlyAssertedEL_first(isa, reformulatorEquals, 'CycLReformulationRulePredicate', 'UniversalVocabularyMt', vStrDef).
  496exactlyAssertedEL_first(isa, reformulationPrecondition, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  497exactlyAssertedEL_first(isa, reformulationPrecondition, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  498exactlyAssertedEL_first(isa, reformulationDirectionInMode, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  499exactlyAssertedEL_first(isa, reformulationDirectionInMode, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  500exactlyAssertedEL_first(isa, ratioOfTo, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  501exactlyAssertedEL_first(isa, quotedIsa, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  502exactlyAssertedEL_first(isa, quotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  503exactlyAssertedEL_first(isa, quotedIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  504exactlyAssertedEL_first(isa, quotedDefnSufficient, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  505exactlyAssertedEL_first(isa, quotedDefnSufficient, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  506exactlyAssertedEL_first(isa, quotedDefnNecessary, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  507exactlyAssertedEL_first(isa, quotedDefnNecessary, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  508exactlyAssertedEL_first(isa, quotedDefnIff, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  509exactlyAssertedEL_first(isa, quotedDefnIff, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  510exactlyAssertedEL_first(isa, quotedArgument, 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
  511exactlyAssertedEL_first(isa, quotedArgument, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  512exactlyAssertedEL_first(isa, querySentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  513exactlyAssertedEL_first(isa, quantitySubsumes, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  514exactlyAssertedEL_first(isa, quantitySubsumes, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  515exactlyAssertedEL_first(isa, quantitySubsumes, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  516exactlyAssertedEL_first(isa, quantitySubsumes, 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  517exactlyAssertedEL_first(isa, quantityIntersects, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  518exactlyAssertedEL_first(isa, quantityIntersects, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  519exactlyAssertedEL_first(isa, quantityIntersects, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  520exactlyAssertedEL_first(isa, prettyString, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  521exactlyAssertedEL_first(isa, preservesGenlsInArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  522exactlyAssertedEL_first(isa, predicateConventionMt, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  523exactlyAssertedEL_first(isa, predicateConventionMt, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  524exactlyAssertedEL_first(isa, pragmaticRequirement, 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
  525exactlyAssertedEL_first(isa, pragmaticRequirement, 'ExceptionPredicate', 'UniversalVocabularyMt', vStrDef).
  526exactlyAssertedEL_first(isa, pragmaticRequirement, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  527exactlyAssertedEL_first(isa, pragmaticRequirement, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  528exactlyAssertedEL_first(isa, pragmaticallyNormal, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  529exactlyAssertedEL_first(isa, pragmaticallyNormal, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  530exactlyAssertedEL_first(isa, pointQuantValue, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  531exactlyAssertedEL_first(isa, performSubL, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  532exactlyAssertedEL_first(isa, performSubL, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  533exactlyAssertedEL_first(isa, overlappingExternalConcept, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  534exactlyAssertedEL_first(isa, or, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  535exactlyAssertedEL_first(isa, or, 'VariableArityRelation', 'LogicalTruthMt', vStrDef).
  536exactlyAssertedEL_first(isa, or, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  537exactlyAssertedEL_first(isa, or, 'LogicalConnective', 'LogicalTruthMt', vStrDef).
  538exactlyAssertedEL_first(isa, or, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  539exactlyAssertedEL_first(isa, or, 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
  540exactlyAssertedEL_first(isa, operatorFormulas, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  541exactlyAssertedEL_first(isa, openEntryFormatInArgs, 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
  542exactlyAssertedEL_first(isa, openEntryFormatInArgs, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  543exactlyAssertedEL_first(isa, openEntryFormatInArgs, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  544exactlyAssertedEL_first(isa, opaqueArgument, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  545exactlyAssertedEL_first(isa, omitArgIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  546exactlyAssertedEL_first(isa, oldConstantName, 'DocumentationPredicate', 'UniversalVocabularyMt', vStrDef).
  547exactlyAssertedEL_first(isa, oldConstantName, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  548exactlyAssertedEL_first(isa, oldConstantName, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  549exactlyAssertedEL_first(isa, numericallyEquals, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  550exactlyAssertedEL_first(isa, numericallyEquals, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  551exactlyAssertedEL_first(isa, numericallyEquals, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  552exactlyAssertedEL_first(isa, numericallyEquals, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  553exactlyAssertedEL_first(isa, nthSmallestElement, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  554exactlyAssertedEL_first(isa, nthLargestElement, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  555exactlyAssertedEL_first(isa, notAssertibleMt, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  556exactlyAssertedEL_first(isa, notAssertibleMt, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  557exactlyAssertedEL_first(isa, notAssertibleCollection, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  558exactlyAssertedEL_first(isa, notAssertibleCollection, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  559exactlyAssertedEL_first(isa, notAssertible, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  560exactlyAssertedEL_first(isa, notAssertible, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  561exactlyAssertedEL_first(isa, not, 'UnaryRelation', 'UniversalVocabularyMt', vStrDef).
  562exactlyAssertedEL_first(isa, not, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  563exactlyAssertedEL_first(isa, not, 'LogicalConnective', 'LogicalTruthMt', vStrDef).
  564exactlyAssertedEL_first(isa, not, 'FixedArityRelation', 'LogicalTruthMt', vStrDef).
  565exactlyAssertedEL_first(isa, nonAbducibleWithValueInArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  566exactlyAssertedEL_first(isa, negationPreds, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  567exactlyAssertedEL_first(isa, negationPreds, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  568exactlyAssertedEL_first(isa, negationPreds, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  569exactlyAssertedEL_first(isa, negationPreds, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  570exactlyAssertedEL_first(isa, negationMt, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  571exactlyAssertedEL_first(isa, negationMt, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  572exactlyAssertedEL_first(isa, negationInverse, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  573exactlyAssertedEL_first(isa, negationInverse, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  574exactlyAssertedEL_first(isa, nearestIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  575exactlyAssertedEL_first(isa, nearestGenls, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  576exactlyAssertedEL_first(isa, nearestGenlPreds, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  577exactlyAssertedEL_first(isa, nearestGenlMt, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  578exactlyAssertedEL_first(isa, nearestDifferentIsa, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  579exactlyAssertedEL_first(isa, nearestDifferentGenls, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  580exactlyAssertedEL_first(isa, nearestCommonSpecs, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  581exactlyAssertedEL_first(isa, nearestCommonIsa, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  582exactlyAssertedEL_first(isa, nearestCommonGenls, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  583exactlyAssertedEL_first(isa, nearestCommonGenlMt, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  584exactlyAssertedEL_first(isa, natFunction, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  585exactlyAssertedEL_first(isa, natFunction, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  586exactlyAssertedEL_first(isa, natArgumentsEqual, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  587exactlyAssertedEL_first(isa, natArgument, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  588exactlyAssertedEL_first(isa, natArgument, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  589exactlyAssertedEL_first(isa, myCreator, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  590exactlyAssertedEL_first(isa, myCreator, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  591exactlyAssertedEL_first(isa, myCreator, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  592exactlyAssertedEL_first(isa, myCreationTime, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  593exactlyAssertedEL_first(isa, myCreationTime, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  594exactlyAssertedEL_first(isa, myCreationSecond, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  595exactlyAssertedEL_first(isa, myCreationSecond, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  596exactlyAssertedEL_first(isa, myCreationPurpose, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  597exactlyAssertedEL_first(isa, myCreationPurpose, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  598exactlyAssertedEL_first(isa, multiplicationUnits, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  599exactlyAssertedEL_first(isa, multiplicationUnits, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  600exactlyAssertedEL_first(isa, mtVisible, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  601exactlyAssertedEL_first(isa, mtVisible, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  602exactlyAssertedEL_first(isa, minQuantValue, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  603exactlyAssertedEL_first(isa, minimizeExtent, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  604exactlyAssertedEL_first(isa, minimize, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  605exactlyAssertedEL_first(isa, microtheoryDesignationArgnum, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  606exactlyAssertedEL_first(isa, meetsPragmaticRequirement, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  607exactlyAssertedEL_first(isa, meetsPragmaticRequirement, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  608exactlyAssertedEL_first(isa, means, tPred, 'CoreCycLMt', vStrDef).
  609exactlyAssertedEL_first(isa, means, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  610exactlyAssertedEL_first(isa, means, 'AntiTransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  611exactlyAssertedEL_first(isa, maxQuantValue, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  612exactlyAssertedEL_first(isa, knownSentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  613exactlyAssertedEL_first(isa, knownAntecedentRule, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  614exactlyAssertedEL_first(isa, knownAntecedentRule, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  615exactlyAssertedEL_first(isa, ist, tPred, 'LogicalTruthMt', vStrDef).
  616exactlyAssertedEL_first(isa, ist, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
  617exactlyAssertedEL_first(isa, ist, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  618exactlyAssertedEL_first(isa, isa, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  619exactlyAssertedEL_first(isa, isa, 'ReformulatorIrrelevantFORT', 'UniversalVocabularyMt', vStrDef).
  620exactlyAssertedEL_first(isa, isa, tPred, 'LogicalTruthMt', vStrDef).
  621exactlyAssertedEL_first(isa, isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  622exactlyAssertedEL_first(isa, isa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  623exactlyAssertedEL_first(isa, irrelevantTerm, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  624exactlyAssertedEL_first(isa, irrelevantPredAssertion, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  625exactlyAssertedEL_first(isa, irrelevantMt, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  626exactlyAssertedEL_first(isa, irrelevantAssertion, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  627exactlyAssertedEL_first(isa, interArgResultIsaReln, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  628exactlyAssertedEL_first(isa, interArgResultIsaReln, 'QuintaryPredicate', 'UniversalVocabularyMt', vStrDef).
  629exactlyAssertedEL_first(isa, interArgResultIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  630exactlyAssertedEL_first(isa, interArgResultIsa, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  631exactlyAssertedEL_first(isa, interArgResultGenlReln, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  632exactlyAssertedEL_first(isa, interArgResultGenlReln, 'QuintaryPredicate', 'UniversalVocabularyMt', vStrDef).
  633exactlyAssertedEL_first(isa, interArgResultGenl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  634exactlyAssertedEL_first(isa, interArgResultGenl, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  635exactlyAssertedEL_first(isa, interArgIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  636exactlyAssertedEL_first(isa, interArgIsa, 'QuintaryPredicate', 'UniversalVocabularyMt', vStrDef).
  637exactlyAssertedEL_first(isa, interArgIsa, 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  638exactlyAssertedEL_first(isa, interArgDifferent, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  639exactlyAssertedEL_first(isa, interArgDifferent, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  640exactlyAssertedEL_first(isa, interArgDifferent, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  641exactlyAssertedEL_first(isa, interArgDifferent, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  642exactlyAssertedEL_first(isa, interArgDifferent, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  643exactlyAssertedEL_first(isa, integerBetween, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  644exactlyAssertedEL_first(isa, instanceElementType, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  645exactlyAssertedEL_first(isa, instanceElementType, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  646exactlyAssertedEL_first(isa, indexicalReferent, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  647exactlyAssertedEL_first(isa, independentArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  648exactlyAssertedEL_first(isa, implies, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  649exactlyAssertedEL_first(isa, implies, 'LogicalConnective', 'LogicalTruthMt', vStrDef).
  650exactlyAssertedEL_first(isa, implies, 'FixedArityRelation', 'LogicalTruthMt', vStrDef).
  651exactlyAssertedEL_first(isa, implies, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  652exactlyAssertedEL_first(isa, hypotheticalTerm, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  653exactlyAssertedEL_first(isa, hypotheticalTerm, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  654exactlyAssertedEL_first(isa, holdsIn, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  655exactlyAssertedEL_first(isa, hlPrototypicalInstance, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  656exactlyAssertedEL_first(isa, highlyRelevantTerm, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  657exactlyAssertedEL_first(isa, highlyRelevantPredAssertion, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  658exactlyAssertedEL_first(isa, highlyRelevantMt, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  659exactlyAssertedEL_first(isa, highlyRelevantAssertion, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  660exactlyAssertedEL_first(isa, greaterThanOrEqualTo, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  661exactlyAssertedEL_first(isa, greaterThanOrEqualTo, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  662exactlyAssertedEL_first(isa, greaterThanOrEqualTo, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  663exactlyAssertedEL_first(isa, greaterThanOrEqualTo, 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  664exactlyAssertedEL_first(isa, greaterThan, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  665exactlyAssertedEL_first(isa, greaterThan, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  666exactlyAssertedEL_first(isa, greaterThan, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  667exactlyAssertedEL_first(isa, genMassNoun, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  668exactlyAssertedEL_first(isa, genls, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  669exactlyAssertedEL_first(isa, genls, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  670exactlyAssertedEL_first(isa, genls, 'ReformulatorIrrelevantFORT', 'UniversalVocabularyMt', vStrDef).
  671exactlyAssertedEL_first(isa, genls, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  672exactlyAssertedEL_first(isa, genls, tPred, 'LogicalTruthMt', vStrDef).
  673exactlyAssertedEL_first(isa, genls, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  674exactlyAssertedEL_first(isa, genlRules, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  675exactlyAssertedEL_first(isa, genlPreds, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  676exactlyAssertedEL_first(isa, genlPreds, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  677exactlyAssertedEL_first(isa, genlPreds, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  678exactlyAssertedEL_first(isa, genlPreds, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  679exactlyAssertedEL_first(isa, genlMt, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  680exactlyAssertedEL_first(isa, genlMt, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  681exactlyAssertedEL_first(isa, genlMt, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  682exactlyAssertedEL_first(isa, genlMt, tPred, 'LogicalTruthMt', vStrDef).
  683exactlyAssertedEL_first(isa, genlMt, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  684exactlyAssertedEL_first(isa, genlInverse, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  685exactlyAssertedEL_first(isa, genlInverse, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  686exactlyAssertedEL_first(isa, genlInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  687exactlyAssertedEL_first(isa, genlCanonicalizerDirectives, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  688exactlyAssertedEL_first(isa, genKeyword, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  689exactlyAssertedEL_first(isa, genFormat, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  690exactlyAssertedEL_first(isa, forwardNonTriggerLiteral, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  691exactlyAssertedEL_first(isa, formulaArity, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  692exactlyAssertedEL_first(isa, forAll, 'Quantifier', 'UniversalVocabularyMt', vStrDef).
  693exactlyAssertedEL_first(isa, forAll, 'Quantifier', 'LogicalTruthMt', vStrDef).
  694exactlyAssertedEL_first(isa, forAll, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  695exactlyAssertedEL_first(isa, followingValue, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  696exactlyAssertedEL_first(isa, followingValue, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  697exactlyAssertedEL_first(isa, fanOutArg, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  698exactlyAssertedEL_first(isa, fanOutArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  699exactlyAssertedEL_first(isa, extentCardinality, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  700exactlyAssertedEL_first(isa, extConceptOverlapsColAndReln, 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
  701exactlyAssertedEL_first(isa, expresses, tPred, 'CoreCycLMt', vStrDef).
  702exactlyAssertedEL_first(isa, expresses, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  703exactlyAssertedEL_first(isa, expansionDefn, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  704exactlyAssertedEL_first(isa, expansion, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  705exactlyAssertedEL_first(isa, expansion, 'CycLReformulationRulePredicate', 'UniversalVocabularyMt', vStrDef).
  706exactlyAssertedEL_first(isa, expansion, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  707exactlyAssertedEL_first(isa, exceptWhen, 'ExceptionPredicate', 'UniversalVocabularyMt', vStrDef).
  708exactlyAssertedEL_first(isa, exceptWhen, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  709exactlyAssertedEL_first(isa, exceptMt, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  710exactlyAssertedEL_first(isa, exceptFor, 'ExceptionPredicate', 'UniversalVocabularyMt', vStrDef).
  711exactlyAssertedEL_first(isa, exceptFor, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  712exactlyAssertedEL_first(isa, except, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  713exactlyAssertedEL_first(isa, exampleAssertions, 'DocumentationPredicate', 'UniversalVocabularyMt', vStrDef).
  714exactlyAssertedEL_first(isa, exampleAssertions, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  715exactlyAssertedEL_first(isa, exactlyAssertedEL_next, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  716exactlyAssertedEL_first(isa, evaluationResultQuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  717exactlyAssertedEL_first(isa, evaluationResultQuotedIsa, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  718exactlyAssertedEL_first(isa, evaluationDefn, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  719exactlyAssertedEL_first(isa, evaluationDefn, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  720exactlyAssertedEL_first(isa, evaluationDefn, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  721exactlyAssertedEL_first(isa, evaluateImmediately, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  722exactlyAssertedEL_first(isa, evaluateAtEL, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  723exactlyAssertedEL_first(isa, evaluate, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  724exactlyAssertedEL_first(isa, equiv, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  725exactlyAssertedEL_first(isa, equiv, 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
  726exactlyAssertedEL_first(isa, equiv, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  727exactlyAssertedEL_first(isa, equiv, 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
  728exactlyAssertedEL_first(isa, equiv, 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
  729exactlyAssertedEL_first(isa, equalSymbols, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  730exactlyAssertedEL_first(isa, equalSymbols, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  731exactlyAssertedEL_first(isa, equalSymbols, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  732exactlyAssertedEL_first(isa, equals, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  733exactlyAssertedEL_first(isa, equals, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  734exactlyAssertedEL_first(isa, equals, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  735exactlyAssertedEL_first(isa, equals, tPred, 'LogicalTruthMt', vStrDef).
  736exactlyAssertedEL_first(isa, equals, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  737exactlyAssertedEL_first(isa, ephemeralTerm, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  738exactlyAssertedEL_first(isa, ephemeralTerm, 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
  739exactlyAssertedEL_first(isa, elInverse, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  740exactlyAssertedEL_first(isa, elInverse, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  741exactlyAssertedEL_first(isa, elInverse, 'AntiTransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  742exactlyAssertedEL_first(isa, elementOf, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  743exactlyAssertedEL_first(isa, distributesOutOfArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  744exactlyAssertedEL_first(isa, disjointWith, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  745exactlyAssertedEL_first(isa, disjointWith, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  746exactlyAssertedEL_first(isa, disjointWith, tPred, 'LogicalTruthMt', vStrDef).
  747exactlyAssertedEL_first(isa, disjointWith, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  748exactlyAssertedEL_first(isa, differentSymbols, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  749exactlyAssertedEL_first(isa, differentSymbols, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  750exactlyAssertedEL_first(isa, differentSymbols, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  751exactlyAssertedEL_first(isa, different, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  752exactlyAssertedEL_first(isa, different, 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
  753exactlyAssertedEL_first(isa, different, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  754exactlyAssertedEL_first(isa, denotes, tPred, 'LogicalTruthMt', vStrDef).
  755exactlyAssertedEL_first(isa, denotes, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  756exactlyAssertedEL_first(isa, denotes, 'AntiTransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  757exactlyAssertedEL_first(isa, defnSufficient, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  758exactlyAssertedEL_first(isa, defnSufficient, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  759exactlyAssertedEL_first(isa, defnSufficient, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  760exactlyAssertedEL_first(isa, defnNecessary, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  761exactlyAssertedEL_first(isa, defnNecessary, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  762exactlyAssertedEL_first(isa, defnNecessary, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  763exactlyAssertedEL_first(isa, defnIff, 'WFFConstraintSatisfactionPredicate', 'UniversalVocabularyMt', vStrDef).
  764exactlyAssertedEL_first(isa, defnIff, tPred, 'LogicalTruthImplementationMt', vStrDef).
  765exactlyAssertedEL_first(isa, defnIff, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  766exactlyAssertedEL_first(isa, defnIff, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  767exactlyAssertedEL_first(isa, definingMt, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  768exactlyAssertedEL_first(isa, definingMt, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  769exactlyAssertedEL_first(isa, defaultReformulatorModePrecedence, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  770exactlyAssertedEL_first(isa, defaultReformulatorModePrecedence, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  771exactlyAssertedEL_first(isa, defaultReformulationDirectionInModeForPred, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  772exactlyAssertedEL_first(isa, defaultReformulationDirectionInModeForPred, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
  773exactlyAssertedEL_first(isa, decontextualizedPredicate, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  774exactlyAssertedEL_first(isa, decontextualizedPredicate, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  775exactlyAssertedEL_first(isa, decontextualizedCollection, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  776exactlyAssertedEL_first(isa, cycTransformationProofRule, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  777exactlyAssertedEL_first(isa, cycTransformationProofBindings, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  778exactlyAssertedEL_first(isa, cycTacticID, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  779exactlyAssertedEL_first(isa, cycProofID, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  780exactlyAssertedEL_first(isa, cycProblemStoreTerms, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  781exactlyAssertedEL_first(isa, cycProblemStoreProofs, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  782exactlyAssertedEL_first(isa, cycProblemStoreProofCount, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  783exactlyAssertedEL_first(isa, cycProblemStoreProblems, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  784exactlyAssertedEL_first(isa, cycProblemStoreProblemCount, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  785exactlyAssertedEL_first(isa, cycProblemStoreLinks, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  786exactlyAssertedEL_first(isa, cycProblemStoreLinkCount, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  787exactlyAssertedEL_first(isa, cycProblemStoreInferences, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  788exactlyAssertedEL_first(isa, cycProblemStoreInferenceCount, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  789exactlyAssertedEL_first(isa, cycProblemStoreID, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  790exactlyAssertedEL_first(isa, cycProblemQueryTerms, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  791exactlyAssertedEL_first(isa, cycProblemQuerySentence, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  792exactlyAssertedEL_first(isa, cycProblemProvabilityStatus, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  793exactlyAssertedEL_first(isa, cycProblemLinkID, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  794exactlyAssertedEL_first(isa, cycProblemID, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  795exactlyAssertedEL_first(isa, cycProblemDependentLinks, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  796exactlyAssertedEL_first(isa, cycProblemArgumentLinks, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  797exactlyAssertedEL_first(isa, cycInferenceRelevantProblems, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  798exactlyAssertedEL_first(isa, cycInferenceAnswerLink, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  799exactlyAssertedEL_first(isa, constraint, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  800exactlyAssertedEL_first(isa, constrainsArg, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  801exactlyAssertedEL_first(isa, constrainsArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  802exactlyAssertedEL_first(isa, constantName, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  803exactlyAssertedEL_first(isa, constantID, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  804exactlyAssertedEL_first(isa, constantGUID, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  805exactlyAssertedEL_first(isa, consistent, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  806exactlyAssertedEL_first(isa, conceptuallyRelated, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  807exactlyAssertedEL_first(isa, completelyEnumerableCollection, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  808exactlyAssertedEL_first(isa, completelyDecidableCollection, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  809exactlyAssertedEL_first(isa, completeExtentEnumerableViaBackchain, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  810exactlyAssertedEL_first(isa, completeExtentEnumerableViaBackchain, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  811exactlyAssertedEL_first(isa, completeExtentEnumerableForValueInArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  812exactlyAssertedEL_first(isa, completeExtentEnumerableForArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  813exactlyAssertedEL_first(isa, completeExtentEnumerable, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  814exactlyAssertedEL_first(isa, completeExtentEnumerable, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  815exactlyAssertedEL_first(isa, completeExtentDecidableForValueInArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  816exactlyAssertedEL_first(isa, completeExtentDecidable, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  817exactlyAssertedEL_first(isa, completeExtentAssertedForValueInArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  818exactlyAssertedEL_first(isa, completeExtentAsserted, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  819exactlyAssertedEL_first(isa, commutativeInArgsAndRest, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  820exactlyAssertedEL_first(isa, commutativeInArgsAndRest, tPred, 'UniversalVocabularyMt', vStrDef).
  821exactlyAssertedEL_first(isa, commutativeInArgsAndRest, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  822exactlyAssertedEL_first(isa, commutativeInArgs, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  823exactlyAssertedEL_first(isa, commutativeInArgs, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  824exactlyAssertedEL_first(isa, commutativeInArgs, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  825exactlyAssertedEL_first(isa, comment, 'DocumentationPredicate', 'UniversalVocabularyMt', vStrDef).
  826exactlyAssertedEL_first(isa, comment, 'DistributingMetaKnowledgePredicate', 'UniversalVocabularyMt', vStrDef).
  827exactlyAssertedEL_first(isa, comment, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  828exactlyAssertedEL_first(isa, comment, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  829exactlyAssertedEL_first(isa, collectionIsaBackchainRequired, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  830exactlyAssertedEL_first(isa, collectionIsaBackchainRequired, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  831exactlyAssertedEL_first(isa, collectionIsaBackchainEncouraged, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  832exactlyAssertedEL_first(isa, collectionIsaBackchainEncouraged, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  833exactlyAssertedEL_first(isa, collectionGenlsBackchainRequired, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  834exactlyAssertedEL_first(isa, collectionGenlsBackchainRequired, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  835exactlyAssertedEL_first(isa, collectionGenlsBackchainEncouraged, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  836exactlyAssertedEL_first(isa, collectionGenlsBackchainEncouraged, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  837exactlyAssertedEL_first(isa, collectionExpansion, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  838exactlyAssertedEL_first(isa, collectionConventionMt, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  839exactlyAssertedEL_first(isa, collectionCompletelyEnumerableViaBackchain, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  840exactlyAssertedEL_first(isa, collectionBackchainRequired, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  841exactlyAssertedEL_first(isa, collectionBackchainRequired, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  842exactlyAssertedEL_first(isa, collectionBackchainEncouraged, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  843exactlyAssertedEL_first(isa, collectionBackchainEncouraged, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  844exactlyAssertedEL_first(isa, coExtensional, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  845exactlyAssertedEL_first(isa, coExtensional, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  846exactlyAssertedEL_first(isa, coExtensional, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  847exactlyAssertedEL_first(isa, canonicalizerDirectiveForArgAndRest, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  848exactlyAssertedEL_first(isa, canonicalizerDirectiveForArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  849exactlyAssertedEL_first(isa, canonicalizerDirectiveForAllArgs, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  850exactlyAssertedEL_first(isa, backchainRequired, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  851exactlyAssertedEL_first(isa, backchainRequired, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  852exactlyAssertedEL_first(isa, backchainForbiddenWhenUnboundInArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  853exactlyAssertedEL_first(isa, backchainForbidden, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  854exactlyAssertedEL_first(isa, backchainForbidden, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  855exactlyAssertedEL_first(isa, assertionUtility, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  856exactlyAssertedEL_first(isa, assertionDirection, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  857exactlyAssertedEL_first(isa, assertionDirection, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  858exactlyAssertedEL_first(isa, assertedTermSentences, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  859exactlyAssertedEL_first(isa, knownSentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
  860exactlyAssertedEL_first(isa, assertedPredicateArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  861exactlyAssertedEL_first(isa, arityMin, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  862exactlyAssertedEL_first(isa, arityMin, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  863exactlyAssertedEL_first(isa, arityMax, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  864exactlyAssertedEL_first(isa, arityMax, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  865exactlyAssertedEL_first(isa, arity, tPred, 'LogicalTruthMt', vStrDef).
  866exactlyAssertedEL_first(isa, arity, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  867exactlyAssertedEL_first(isa, arity, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  868exactlyAssertedEL_first(isa, argsQuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  869exactlyAssertedEL_first(isa, argsQuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  870exactlyAssertedEL_first(isa, argSometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  871exactlyAssertedEL_first(isa, argSometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  872exactlyAssertedEL_first(isa, argSometimesIsa, 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  873exactlyAssertedEL_first(isa, argSometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  874exactlyAssertedEL_first(isa, argsIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  875exactlyAssertedEL_first(isa, argsIsa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  876exactlyAssertedEL_first(isa, argsGenl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  877exactlyAssertedEL_first(isa, argsGenl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  878exactlyAssertedEL_first(isa, argQuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  879exactlyAssertedEL_first(isa, argQuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  880exactlyAssertedEL_first(isa, argQuotedIsa, 'ArgQuotedIsaTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  881exactlyAssertedEL_first(isa, argIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  882exactlyAssertedEL_first(isa, argIsa, tPred, 'LogicalTruthMt', vStrDef).
  883exactlyAssertedEL_first(isa, argIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  884exactlyAssertedEL_first(isa, argIsa, 'ArgIsaTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  885exactlyAssertedEL_first(isa, argAndRestQuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  886exactlyAssertedEL_first(isa, argAndRestQuotedIsa, 'ArgQuotedIsaTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  887exactlyAssertedEL_first(isa, argAndRestIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  888exactlyAssertedEL_first(isa, argAndRestIsa, tPred, 'LogicalTruthMt', vStrDef).
  889exactlyAssertedEL_first(isa, argAndRestIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  890exactlyAssertedEL_first(isa, argAndRestIsa, 'ArgIsaTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  891exactlyAssertedEL_first(isa, argAndRestGenl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  892exactlyAssertedEL_first(isa, argAndRestGenl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  893exactlyAssertedEL_first(isa, argAndRestGenl, 'ArgGenlTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
  894exactlyAssertedEL_first(isa, arg6SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  895exactlyAssertedEL_first(isa, arg6SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  896exactlyAssertedEL_first(isa, arg6SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  897exactlyAssertedEL_first(isa, arg6SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  898exactlyAssertedEL_first(isa, arg6QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  899exactlyAssertedEL_first(isa, arg6QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  900exactlyAssertedEL_first(isa, arg6QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  901exactlyAssertedEL_first(isa, arg6Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  902exactlyAssertedEL_first(isa, arg6Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  903exactlyAssertedEL_first(isa, arg6Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  904exactlyAssertedEL_first(isa, arg6Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  905exactlyAssertedEL_first(isa, arg6Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  906exactlyAssertedEL_first(isa, arg6Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  907exactlyAssertedEL_first(isa, arg5SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  908exactlyAssertedEL_first(isa, arg5SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  909exactlyAssertedEL_first(isa, arg5SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  910exactlyAssertedEL_first(isa, arg5SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  911exactlyAssertedEL_first(isa, arg5QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  912exactlyAssertedEL_first(isa, arg5QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  913exactlyAssertedEL_first(isa, arg5QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  914exactlyAssertedEL_first(isa, arg5Isa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  915exactlyAssertedEL_first(isa, arg5Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  916exactlyAssertedEL_first(isa, arg5Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  917exactlyAssertedEL_first(isa, arg5Genl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  918exactlyAssertedEL_first(isa, arg5Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  919exactlyAssertedEL_first(isa, arg5Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  920exactlyAssertedEL_first(isa, arg5Format, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  921exactlyAssertedEL_first(isa, arg5Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  922exactlyAssertedEL_first(isa, arg5Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  923exactlyAssertedEL_first(isa, arg4SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  924exactlyAssertedEL_first(isa, arg4SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  925exactlyAssertedEL_first(isa, arg4SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  926exactlyAssertedEL_first(isa, arg4SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  927exactlyAssertedEL_first(isa, arg4QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  928exactlyAssertedEL_first(isa, arg4QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  929exactlyAssertedEL_first(isa, arg4QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  930exactlyAssertedEL_first(isa, arg4Isa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  931exactlyAssertedEL_first(isa, arg4Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  932exactlyAssertedEL_first(isa, arg4Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  933exactlyAssertedEL_first(isa, arg4Genl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  934exactlyAssertedEL_first(isa, arg4Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  935exactlyAssertedEL_first(isa, arg4Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  936exactlyAssertedEL_first(isa, arg4Format, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  937exactlyAssertedEL_first(isa, arg4Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  938exactlyAssertedEL_first(isa, arg4Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  939exactlyAssertedEL_first(isa, arg3SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  940exactlyAssertedEL_first(isa, arg3SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  941exactlyAssertedEL_first(isa, arg3SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  942exactlyAssertedEL_first(isa, arg3SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  943exactlyAssertedEL_first(isa, arg3QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  944exactlyAssertedEL_first(isa, arg3QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  945exactlyAssertedEL_first(isa, arg3QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  946exactlyAssertedEL_first(isa, arg3Isa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  947exactlyAssertedEL_first(isa, arg3Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  948exactlyAssertedEL_first(isa, arg3Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  949exactlyAssertedEL_first(isa, arg3Genl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  950exactlyAssertedEL_first(isa, arg3Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  951exactlyAssertedEL_first(isa, arg3Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  952exactlyAssertedEL_first(isa, arg3Format, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  953exactlyAssertedEL_first(isa, arg3Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  954exactlyAssertedEL_first(isa, arg3Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  955exactlyAssertedEL_first(isa, arg2SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  956exactlyAssertedEL_first(isa, arg2SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  957exactlyAssertedEL_first(isa, arg2SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  958exactlyAssertedEL_first(isa, arg2SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  959exactlyAssertedEL_first(isa, arg2QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  960exactlyAssertedEL_first(isa, arg2QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  961exactlyAssertedEL_first(isa, arg2QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  962exactlyAssertedEL_first(isa, arg2Isa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  963exactlyAssertedEL_first(isa, arg2Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  964exactlyAssertedEL_first(isa, arg2Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  965exactlyAssertedEL_first(isa, arg2Genl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  966exactlyAssertedEL_first(isa, arg2Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  967exactlyAssertedEL_first(isa, arg2Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  968exactlyAssertedEL_first(isa, arg2Format, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  969exactlyAssertedEL_first(isa, arg2Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  970exactlyAssertedEL_first(isa, arg2Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  971exactlyAssertedEL_first(isa, arg1SometimesIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  972exactlyAssertedEL_first(isa, arg1SometimesIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  973exactlyAssertedEL_first(isa, arg1SometimesIsa, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  974exactlyAssertedEL_first(isa, arg1SometimesIsa, 'ArgSometimesIsaPredicate', 'UniversalVocabularyMt', vStrDef).
  975exactlyAssertedEL_first(isa, arg1QuotedIsa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  976exactlyAssertedEL_first(isa, arg1QuotedIsa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  977exactlyAssertedEL_first(isa, arg1QuotedIsa, 'ArgQuotedIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  978exactlyAssertedEL_first(isa, arg1Isa, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  979exactlyAssertedEL_first(isa, arg1Isa, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  980exactlyAssertedEL_first(isa, arg1Isa, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  981exactlyAssertedEL_first(isa, arg1Genl, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  982exactlyAssertedEL_first(isa, arg1Genl, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
  983exactlyAssertedEL_first(isa, arg1Genl, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  984exactlyAssertedEL_first(isa, arg1Format, 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  985exactlyAssertedEL_first(isa, arg1Format, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  986exactlyAssertedEL_first(isa, arg1Format, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
  987exactlyAssertedEL_first(isa, and, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
  988exactlyAssertedEL_first(isa, and, 'VariableArityRelation', 'LogicalTruthMt', vStrDef).
  989exactlyAssertedEL_first(isa, and, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
  990exactlyAssertedEL_first(isa, and, 'LogicalConnective', 'LogicalTruthMt', vStrDef).
  991exactlyAssertedEL_first(isa, and, 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
  992exactlyAssertedEL_first(isa, and, 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
  993exactlyAssertedEL_first(isa, afterRemoving, tPred, 'LogicalTruthImplementationMt', vStrDef).
  994exactlyAssertedEL_first(isa, afterRemoving, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  995exactlyAssertedEL_first(isa, afterRemoving, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  996exactlyAssertedEL_first(isa, afterAdding, tPred, 'LogicalTruthImplementationMt', vStrDef).
  997exactlyAssertedEL_first(isa, afterAdding, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrDef).
  998exactlyAssertedEL_first(isa, afterAdding, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
  999exactlyAssertedEL_first(isa, admittedSentence, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1000exactlyAssertedEL_first(isa, admittedNAT, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1001exactlyAssertedEL_first(isa, admittedArgument, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1002exactlyAssertedEL_first(isa, admittedAllArgument, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1003exactlyAssertedEL_first(isa, abnormal, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
 1004exactlyAssertedEL_first(isa, abnormal, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1005exactlyAssertedEL_first(isa, 'wsl-NonFunctionalParameter', tCol, 'UniversalVocabularyMt', vStrDef).
 1006exactlyAssertedEL_first(isa, 'wsl-ClassificationRoot', tCol, 'UniversalVocabularyMt', vStrDef).
 1007exactlyAssertedEL_first(isa, 'WFFSupportedTerm', tCol, 'UniversalVocabularyMt', vStrDef).
 1008exactlyAssertedEL_first(isa, 'WFFSupportedPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1009exactlyAssertedEL_first(isa, 'WFFDirectivePredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1010exactlyAssertedEL_first(isa, 'WFFConstraintSatisfactionPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1011exactlyAssertedEL_first(isa, 'WFFConstraintPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1012exactlyAssertedEL_first(isa, 'Wednesday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1013exactlyAssertedEL_first(isa, 'VariableAritySkolemFunction', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1014exactlyAssertedEL_first(isa, 'VariableAritySkolemFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1015exactlyAssertedEL_first(isa, 'VariableAritySkolemFuncN', tCol, 'UniversalVocabularyMt', vStrDef).
 1016exactlyAssertedEL_first(isa, 'VariableAritySkolemFuncN', tCol, 'CoreCycLImplementationMt', vStrDef).
 1017exactlyAssertedEL_first(isa, 'VariableArityRelation', tCol, 'LogicalTruthMt', vStrDef).
 1018exactlyAssertedEL_first(isa, 'VariableArityRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1019exactlyAssertedEL_first(isa, 'UnreifiableFunction', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1020exactlyAssertedEL_first(isa, 'UnreifiableFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1021exactlyAssertedEL_first(isa, 'Unknown-HLTruthValue', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1022exactlyAssertedEL_first(isa, 'Unknown-HLTruthValue', 'CycHLTruthValue', 'UniversalVocabularyMt', vStrDef).
 1023exactlyAssertedEL_first(isa, 'UniversalVocabularyMt', 'BroadMicrotheory', 'UniversalVocabularyMt', vStrDef).
 1024exactlyAssertedEL_first(isa, 'UniversalVocabularyImplementationMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1025exactlyAssertedEL_first(isa, 'Unity', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 1026exactlyAssertedEL_first(isa, 'UnitProductFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1027exactlyAssertedEL_first(isa, 'UnitProductFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1028exactlyAssertedEL_first(isa, 'UnitProductFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1029exactlyAssertedEL_first(isa, 'UnitProductFn', 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
 1030exactlyAssertedEL_first(isa, 'UnitOfMeasure', tCol, 'CoreCycLMt', vStrDef).
 1031exactlyAssertedEL_first(isa, 'UnitOfMeasure', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1032exactlyAssertedEL_first(isa, 'UncanonicalizerAssertionFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1033exactlyAssertedEL_first(isa, 'UncanonicalizerAssertionFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1034exactlyAssertedEL_first(isa, 'UnaryRelation', tCol, 'CoreCycLMt', vStrDef).
 1035exactlyAssertedEL_first(isa, 'UnaryRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1036exactlyAssertedEL_first(isa, 'UnaryPredicate', 'PredicateTypeByArity', 'UniversalVocabularyMt', vStrDef).
 1037exactlyAssertedEL_first(isa, 'UnaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1038exactlyAssertedEL_first(isa, 'UnaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1039exactlyAssertedEL_first(isa, 'UnaryFunction', tCol, 'CoreCycLMt', vStrDef).
 1040exactlyAssertedEL_first(isa, 'UnaryFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1041exactlyAssertedEL_first(isa, 'Tuesday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1042exactlyAssertedEL_first(isa, 'TruthValue', tCol, 'UniversalVocabularyMt', vStrDef).
 1043exactlyAssertedEL_first(isa, 'TruthValue', tCol, 'LogicalTruthMt', vStrDef).
 1044exactlyAssertedEL_first(isa, 'TruthFunction', tCol, 'LogicalTruthMt', vStrDef).
 1045exactlyAssertedEL_first(isa, 'TruthFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1046exactlyAssertedEL_first(isa, 'True', 'TruthValue', 'UniversalVocabularyMt', vStrDef).
 1047exactlyAssertedEL_first(isa, 'True', 'TruthValue', 'LogicalTruthMt', vStrDef).
 1048exactlyAssertedEL_first(isa, 'TransitiveBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1049exactlyAssertedEL_first(isa, 'TransitiveBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1050exactlyAssertedEL_first(isa, 'TransformationModuleSupportedPredicate', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1051exactlyAssertedEL_first(isa, 'TransformationModuleSupportedPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1052exactlyAssertedEL_first(isa, 'TransformationModuleSupportedCollection', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1053exactlyAssertedEL_first(isa, 'TransformationModuleSupportedCollection', tCol, 'UniversalVocabularyMt', vStrDef).
 1054exactlyAssertedEL_first(isa, 'TLVariableFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1055exactlyAssertedEL_first(isa, 'TLVariableFn', 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 1056exactlyAssertedEL_first(isa, 'TLVariableFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1057exactlyAssertedEL_first(isa, 'TLReifiedNatFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1058exactlyAssertedEL_first(isa, 'TLReifiedNatFn', 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 1059exactlyAssertedEL_first(isa, 'TLAssertionFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1060exactlyAssertedEL_first(isa, 'TLAssertionFn', 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 1061exactlyAssertedEL_first(isa, 'TLAssertionFn', 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 1062exactlyAssertedEL_first(isa, 'TLAssertionFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1063exactlyAssertedEL_first(isa, 'TimesFn', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1064exactlyAssertedEL_first(isa, 'TimesFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1065exactlyAssertedEL_first(isa, 'TimesFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1066exactlyAssertedEL_first(isa, 'TimesFn', 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
 1067exactlyAssertedEL_first(isa, 'Thursday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1068exactlyAssertedEL_first(isa, 'Thing', tCol, 'LogicalTruthMt', vStrDef).
 1069exactlyAssertedEL_first(isa, 'Thing', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1070exactlyAssertedEL_first(isa, 'TheUser', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1071exactlyAssertedEL_first(isa, 'TheUser', 'HumanCyclist', 'UniversalVocabularyMt', vStrDef).
 1072exactlyAssertedEL_first(isa, 'TheUser', 'Cyclist', 'UniversalVocabularyMt', vStrDef).
 1073exactlyAssertedEL_first(isa, 'TheTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1074exactlyAssertedEL_first(isa, 'TheTerm', tCol, 'CoreCycLImplementationMt', vStrDef).
 1075exactlyAssertedEL_first(isa, 'TheTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1076exactlyAssertedEL_first(isa, 'TheSetOf', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1077exactlyAssertedEL_first(isa, 'TheSetOf', 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 1078exactlyAssertedEL_first(isa, 'TheSetOf', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1079exactlyAssertedEL_first(isa, 'TheSet', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1080exactlyAssertedEL_first(isa, 'TheSet', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1081exactlyAssertedEL_first(isa, 'TheSet', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1082exactlyAssertedEL_first(isa, 'ThePrototypicalTransitiveBinaryPredicate', 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1083exactlyAssertedEL_first(isa, 'ThePrototypicalCollection', tCol, 'UniversalVocabularyMt', vStrDef).
 1084exactlyAssertedEL_first(isa, 'ThePrototypicalBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1085exactlyAssertedEL_first(isa, 'TheList', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1086exactlyAssertedEL_first(isa, 'TheList', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1087exactlyAssertedEL_first(isa, 'TheEmptySet', 'Set-Mathematical', 'UniversalVocabularyMt', vStrDef).
 1088exactlyAssertedEL_first(isa, 'TheEmptyList', 'List', 'UniversalVocabularyMt', vStrDef).
 1089exactlyAssertedEL_first(isa, 'TheCollectionOf', 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 1090exactlyAssertedEL_first(isa, 'TheCollectionOf', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1091exactlyAssertedEL_first(isa, 'TheCollectionOf', 'ReifiableFunction', 'CoreCycLMt', vStrDef).
 1092exactlyAssertedEL_first(isa, 'TheCollectionOf', 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1093exactlyAssertedEL_first(isa, 'TheCollectionOf', 'CollectionDenotingFunction', 'CoreCycLMt', vStrDef).
 1094exactlyAssertedEL_first(isa, 'TheCollectionOf', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1095exactlyAssertedEL_first(isa, 'TheCollectionOf', 'BinaryFunction', 'CoreCycLMt', vStrDef).
 1096exactlyAssertedEL_first(isa, 'TernaryRelation', tCol, 'CoreCycLMt', vStrDef).
 1097exactlyAssertedEL_first(isa, 'TernaryRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1098exactlyAssertedEL_first(isa, 'TernaryPredicate', 'PredicateTypeByArity', 'UniversalVocabularyMt', vStrDef).
 1099exactlyAssertedEL_first(isa, 'TernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1100exactlyAssertedEL_first(isa, 'TernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1101exactlyAssertedEL_first(isa, 'TernaryFunction', tCol, 'CoreCycLMt', vStrDef).
 1102exactlyAssertedEL_first(isa, 'TernaryFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1103exactlyAssertedEL_first(isa, 'TemporaryEnglishParaphraseMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1104exactlyAssertedEL_first(isa, 'TemporaryEnglishParaphraseMt', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1105exactlyAssertedEL_first(isa, 'SymmetricBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1106exactlyAssertedEL_first(isa, 'SymmetricBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1107exactlyAssertedEL_first(isa, 'Sunday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1108exactlyAssertedEL_first(isa, 'substring-CaseInsensitive', 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1109exactlyAssertedEL_first(isa, 'substring-CaseInsensitive', 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1110exactlyAssertedEL_first(isa, 'substring-CaseInsensitive', 'EvaluatablePredicate', 'UniversalVocabularyMt', vStrDef).
 1111exactlyAssertedEL_first(isa, 'substring-CaseInsensitive', 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1112exactlyAssertedEL_first(isa, 'SubLSymbol', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 1113exactlyAssertedEL_first(isa, 'SubLSymbol', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1114exactlyAssertedEL_first(isa, 'SubLSymbol', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1115exactlyAssertedEL_first(isa, 'SubLString', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1116exactlyAssertedEL_first(isa, 'SubLString', tCol, 'CoreCycLImplementationMt', vStrDef).
 1117exactlyAssertedEL_first(isa, 'SubLString', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1118exactlyAssertedEL_first(isa, 'SubLSExpression', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 1119exactlyAssertedEL_first(isa, 'SubLSExpression', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1120exactlyAssertedEL_first(isa, 'SubLRealNumber', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1121exactlyAssertedEL_first(isa, 'SubLRealNumber', tCol, 'CoreCycLImplementationMt', vStrDef).
 1122exactlyAssertedEL_first(isa, 'SubLRealNumber', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1123exactlyAssertedEL_first(isa, 'SubLQuoteFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1124exactlyAssertedEL_first(isa, 'SubLQuoteFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1125exactlyAssertedEL_first(isa, 'SubLPositiveInteger', 'SubLExpressionType', 'LogicalTruthImplementationMt', vStrDef).
 1126exactlyAssertedEL_first(isa, 'SubLPositiveInteger', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1127exactlyAssertedEL_first(isa, 'SubLPositiveInteger', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1128exactlyAssertedEL_first(isa, 'SubLPositiveInteger', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1129exactlyAssertedEL_first(isa, 'SubLNonVariableSymbol', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1130exactlyAssertedEL_first(isa, 'SubLNonVariableSymbol', tCol, 'CoreCycLImplementationMt', vStrDef).
 1131exactlyAssertedEL_first(isa, 'SubLNonVariableSymbol', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1132exactlyAssertedEL_first(isa, 'SubLNonVariableNonKeywordSymbol', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1133exactlyAssertedEL_first(isa, 'SubLNonVariableNonKeywordSymbol', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1134exactlyAssertedEL_first(isa, 'SubLNonNegativeInteger', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1135exactlyAssertedEL_first(isa, 'SubLNonNegativeInteger', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1136exactlyAssertedEL_first(isa, 'SubLNonNegativeInteger', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1137exactlyAssertedEL_first(isa, 'SubLList', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 1138exactlyAssertedEL_first(isa, 'SubLList', tCol, 'CoreCycLImplementationMt', vStrDef).
 1139exactlyAssertedEL_first(isa, 'SubLList', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1140exactlyAssertedEL_first(isa, 'SubLKeyword', 'SubLExpressionType', 'CoreCycLImplementationMt', vStrDef).
 1141exactlyAssertedEL_first(isa, 'SubLKeyword', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1142exactlyAssertedEL_first(isa, 'SubLKeyword', tCol, 'CoreCycLImplementationMt', vStrDef).
 1143exactlyAssertedEL_first(isa, 'SubLKeyword', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1144exactlyAssertedEL_first(isa, 'SubLInteger', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1145exactlyAssertedEL_first(isa, 'SubLInteger', tCol, 'CoreCycLImplementationMt', vStrDef).
 1146exactlyAssertedEL_first(isa, 'SubLInteger', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1147exactlyAssertedEL_first(isa, 'SubLExpressionType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1148exactlyAssertedEL_first(isa, 'SubLCharacter', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1149exactlyAssertedEL_first(isa, 'SubLCharacter', tCol, 'CoreCycLImplementationMt', vStrDef).
 1150exactlyAssertedEL_first(isa, 'SubLCharacter', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1151exactlyAssertedEL_first(isa, 'SubLAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1152exactlyAssertedEL_first(isa, 'SubLAtomicTerm', tCol, 'CoreCycLImplementationMt', vStrDef).
 1153exactlyAssertedEL_first(isa, 'SubLAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1154exactlyAssertedEL_first(isa, 'SubLAtom', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 1155exactlyAssertedEL_first(isa, 'SubLAtom', tCol, 'CoreCycLImplementationMt', vStrDef).
 1156exactlyAssertedEL_first(isa, 'SubLAtom', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1157exactlyAssertedEL_first(isa, 'SkolemFunctionFn', 'TernaryFunction', 'UniversalVocabularyMt', vStrDef).
 1158exactlyAssertedEL_first(isa, 'SkolemFunctionFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1159exactlyAssertedEL_first(isa, 'SkolemFunctionFn', 'ReformulatorIrrelevantFORT', 'UniversalVocabularyMt', vStrDef).
 1160exactlyAssertedEL_first(isa, 'SkolemFunction', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1161exactlyAssertedEL_first(isa, 'SkolemFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1162exactlyAssertedEL_first(isa, 'SkolemFuncNFn', 'QuaternaryFunction', 'UniversalVocabularyMt', vStrDef).
 1163exactlyAssertedEL_first(isa, 'SkolemFuncN', tCol, 'UniversalVocabularyMt', vStrDef).
 1164exactlyAssertedEL_first(isa, 'SkolemFuncN', tCol, 'CoreCycLImplementationMt', vStrDef).
 1165exactlyAssertedEL_first(isa, 'SingleEntry', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1166exactlyAssertedEL_first(isa, 'SingleEntry', 'Format', 'UniversalVocabularyMt', vStrDef).
 1167exactlyAssertedEL_first(isa, 'SiblingDisjointCollectionType', tCol, 'CoreCycLMt', vStrDef).
 1168exactlyAssertedEL_first(isa, 'SiblingDisjointCollectionType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1169exactlyAssertedEL_first(isa, 'SiblingDisjointAttributeType', tCol, 'CoreCycLMt', vStrDef).
 1170exactlyAssertedEL_first(isa, 'SiblingDisjointAttributeType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1171exactlyAssertedEL_first(isa, 'SetTheFormat', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1172exactlyAssertedEL_first(isa, 'SetTheFormat', 'Format', 'UniversalVocabularyMt', vStrDef).
 1173exactlyAssertedEL_first(isa, 'SetOrCollection', tCol, 'CoreCycLMt', vStrDef).
 1174exactlyAssertedEL_first(isa, 'SetOrCollection', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1175exactlyAssertedEL_first(isa, 'Set-Mathematical', tCol, 'CoreCycLMt', vStrDef).
 1176exactlyAssertedEL_first(isa, 'Set-Mathematical', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1177exactlyAssertedEL_first(isa, 'September', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1178exactlyAssertedEL_first(isa, 'September', tCol, 'CoreCycLMt', vStrDef).
 1179exactlyAssertedEL_first(isa, 'SententialRelation', tCol, 'LogicalTruthMt', vStrDef).
 1180exactlyAssertedEL_first(isa, 'SententialRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1181exactlyAssertedEL_first(isa, 'ScopingRelation', tCol, 'CoreCycLMt', vStrDef).
 1182exactlyAssertedEL_first(isa, 'ScopingRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1183exactlyAssertedEL_first(isa, 'ScalarPointValue', tCol, 'CoreCycLMt', vStrDef).
 1184exactlyAssertedEL_first(isa, 'ScalarPointValue', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1185exactlyAssertedEL_first(isa, 'ScalarInterval', tCol, 'CoreCycLMt', vStrDef).
 1186exactlyAssertedEL_first(isa, 'ScalarInterval', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1187exactlyAssertedEL_first(isa, 'ScalarIntegralValue', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1188exactlyAssertedEL_first(isa, 'Saturday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1189exactlyAssertedEL_first(isa, 'RuleTemplate', tCol, 'UniversalVocabularyMt', vStrDef).
 1190exactlyAssertedEL_first(isa, 'RuleTemplate', tCol, 'CoreCycLImplementationMt', vStrDef).
 1191exactlyAssertedEL_first(isa, 'RoundUpFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1192exactlyAssertedEL_first(isa, 'RoundUpFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1193exactlyAssertedEL_first(isa, 'RoundDownFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1194exactlyAssertedEL_first(isa, 'RoundDownFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1195exactlyAssertedEL_first(isa, 'RoundClosestFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1196exactlyAssertedEL_first(isa, 'RoundClosestFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1197exactlyAssertedEL_first(isa, 'RemovalModuleSupportedPredicate-Specific', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1198exactlyAssertedEL_first(isa, 'RemovalModuleSupportedPredicate-Specific', tCol, 'UniversalVocabularyMt', vStrDef).
 1199exactlyAssertedEL_first(isa, 'RemovalModuleSupportedPredicate-Generic', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1200exactlyAssertedEL_first(isa, 'RemovalModuleSupportedPredicate-Generic', tCol, 'UniversalVocabularyMt', vStrDef).
 1201exactlyAssertedEL_first(isa, 'RemovalModuleSupportedCollection-Generic', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1202exactlyAssertedEL_first(isa, 'RemovalModuleSupportedCollection-Generic', tCol, 'UniversalVocabularyMt', vStrDef).
 1203exactlyAssertedEL_first(isa, 'RelaxArgTypeConstraintsForVariables', 'WFFDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
 1204exactlyAssertedEL_first(isa, 'RelaxArgTypeConstraintsForVariables', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1205exactlyAssertedEL_first(isa, 'RelationInstanceExistsFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1206exactlyAssertedEL_first(isa, 'RelationInstanceExistsFn', 'TernaryFunction', 'UniversalVocabularyMt', vStrDef).
 1207exactlyAssertedEL_first(isa, 'RelationInstanceExistsFn', 'IndeterminateTermDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1208exactlyAssertedEL_first(isa, 'RelationExistsInstanceFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1209exactlyAssertedEL_first(isa, 'RelationExistsInstanceFn', 'TernaryFunction', 'UniversalVocabularyMt', vStrDef).
 1210exactlyAssertedEL_first(isa, 'RelationExistsInstanceFn', 'IndeterminateTermDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1211exactlyAssertedEL_first(isa, 'RelationExistsAllFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1212exactlyAssertedEL_first(isa, 'RelationExistsAllFn', 'QuaternaryFunction', 'UniversalVocabularyMt', vStrDef).
 1213exactlyAssertedEL_first(isa, 'RelationExistsAllFn', 'IndeterminateTermDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1214exactlyAssertedEL_first(isa, 'RelationAllExistsFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1215exactlyAssertedEL_first(isa, 'RelationAllExistsFn', 'QuaternaryFunction', 'UniversalVocabularyMt', vStrDef).
 1216exactlyAssertedEL_first(isa, 'RelationAllExistsFn', 'IndeterminateTermDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1217exactlyAssertedEL_first(isa, tRelation, tCol, 'LogicalTruthMt', vStrDef).
 1218exactlyAssertedEL_first(isa, tRelation, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1219exactlyAssertedEL_first(isa, 'ReifiableFunction', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1220exactlyAssertedEL_first(isa, 'ReifiableFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1221exactlyAssertedEL_first(isa, 'ReformulatorIrrelevantFORT', tCol, 'UniversalVocabularyMt', vStrDef).
 1222exactlyAssertedEL_first(isa, 'ReformulatorIrrelevantFORT', tCol, 'CoreCycLImplementationMt', vStrDef).
 1223exactlyAssertedEL_first(isa, 'ReformulatorHighlyRelevantFORT', tCol, 'UniversalVocabularyMt', vStrDef).
 1224exactlyAssertedEL_first(isa, 'ReformulatorHighlyRelevantFORT', tCol, 'CoreCycLImplementationMt', vStrDef).
 1225exactlyAssertedEL_first(isa, 'ReformulatorDirectivePredicate', tCol, 'CoreCycLImplementationMt', vStrDef).
 1226exactlyAssertedEL_first(isa, 'ReformulatorDirectivePredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1227exactlyAssertedEL_first(isa, 'ReformulationNeitherDirection', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1228exactlyAssertedEL_first(isa, 'ReformulationForwardDirection', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1229exactlyAssertedEL_first(isa, 'ReformulationBackwardDirection', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1230exactlyAssertedEL_first(isa, 'ReflexiveBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1231exactlyAssertedEL_first(isa, 'ReflexiveBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1232exactlyAssertedEL_first(isa, 'RealNumber', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1233exactlyAssertedEL_first(isa, 'QuotientFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1234exactlyAssertedEL_first(isa, 'QuotientFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1235exactlyAssertedEL_first(isa, 'Quote', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1236exactlyAssertedEL_first(isa, 'Quote', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1237exactlyAssertedEL_first(isa, 'Quote', 'UnreifiableFunction', 'LogicalTruthImplementationMt', vStrDef).
 1238exactlyAssertedEL_first(isa, 'Quote', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1239exactlyAssertedEL_first(isa, 'QuintaryRelation', tCol, 'CoreCycLMt', vStrDef).
 1240exactlyAssertedEL_first(isa, 'QuintaryRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1241exactlyAssertedEL_first(isa, 'QuintaryPredicate', 'PredicateTypeByArity', 'UniversalVocabularyMt', vStrDef).
 1242exactlyAssertedEL_first(isa, 'QuintaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1243exactlyAssertedEL_first(isa, 'QuintaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1244exactlyAssertedEL_first(isa, 'QuintaryFunction', tCol, 'CoreCycLMt', vStrDef).
 1245exactlyAssertedEL_first(isa, 'QuintaryFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1246exactlyAssertedEL_first(isa, 'QueryMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1247exactlyAssertedEL_first(isa, 'QuaternaryRelation', tCol, 'CoreCycLMt', vStrDef).
 1248exactlyAssertedEL_first(isa, 'QuaternaryRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1249exactlyAssertedEL_first(isa, 'QuaternaryPredicate', 'PredicateTypeByArity', 'UniversalVocabularyMt', vStrDef).
 1250exactlyAssertedEL_first(isa, 'QuaternaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1251exactlyAssertedEL_first(isa, 'QuaternaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1252exactlyAssertedEL_first(isa, 'QuaternaryFunction', tCol, 'CoreCycLMt', vStrDef).
 1253exactlyAssertedEL_first(isa, 'QuaternaryFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1254exactlyAssertedEL_first(isa, 'QuasiQuote', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1255exactlyAssertedEL_first(isa, 'QuasiQuote', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1256exactlyAssertedEL_first(isa, 'QuasiQuote', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1257exactlyAssertedEL_first(isa, 'QuasiQuote', tFunction, 'LogicalTruthMt', vStrDef).
 1258exactlyAssertedEL_first(isa, 'QuantityConversionFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1259exactlyAssertedEL_first(isa, 'QuantityConversionFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1260exactlyAssertedEL_first(isa, 'Quantifier', tCol, 'LogicalTruthMt', vStrDef).
 1261exactlyAssertedEL_first(isa, 'Quantifier', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1262exactlyAssertedEL_first(isa, 'ProblemSolvingCntxt', tCol, 'CoreCycLMt', vStrDef).
 1263exactlyAssertedEL_first(isa, 'ProblemSolvingCntxt', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1264exactlyAssertedEL_first(isa, 'prettyString-Canonical', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1265exactlyAssertedEL_first(isa, 'PredicateTypeByArity', 'DisjointCollectionType', 'UniversalVocabularyMt', vStrDef).
 1266exactlyAssertedEL_first(isa, tPred, tCol, 'LogicalTruthMt', vStrDef).
 1267exactlyAssertedEL_first(isa, tPred, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1268exactlyAssertedEL_first(isa, 'PositiveInteger', tCol, 'LogicalTruthMt', vStrDef).
 1269exactlyAssertedEL_first(isa, 'PositiveInteger', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1270exactlyAssertedEL_first(isa, 'PlusFn', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1271exactlyAssertedEL_first(isa, 'PlusFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1272exactlyAssertedEL_first(isa, 'PlusFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1273exactlyAssertedEL_first(isa, 'PlusFn', 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
 1274exactlyAssertedEL_first(isa, 'PlusAll', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1275exactlyAssertedEL_first(isa, 'PlusAll', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1276exactlyAssertedEL_first(isa, 'PerFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1277exactlyAssertedEL_first(isa, 'PerFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1278exactlyAssertedEL_first(isa, 'Percent', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1279exactlyAssertedEL_first(isa, 'Percent', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1280exactlyAssertedEL_first(isa, 'PartiallyCommutativeRelation', tCol, 'CoreCycLMt', vStrDef).
 1281exactlyAssertedEL_first(isa, 'PartiallyCommutativeRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1282exactlyAssertedEL_first(isa, 'Open-InferenceProblemLinkStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1283exactlyAssertedEL_first(isa, 'October', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1284exactlyAssertedEL_first(isa, 'October', tCol, 'CoreCycLMt', vStrDef).
 1285exactlyAssertedEL_first(isa, 'November', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1286exactlyAssertedEL_first(isa, 'November', tCol, 'CoreCycLMt', vStrDef).
 1287exactlyAssertedEL_first(isa, 'NonNegativeScalarInterval', tCol, 'CoreCycLMt', vStrDef).
 1288exactlyAssertedEL_first(isa, 'NonNegativeScalarInterval', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1289exactlyAssertedEL_first(isa, 'NonNegativeInteger', tCol, 'LogicalTruthMt', vStrDef).
 1290exactlyAssertedEL_first(isa, 'NonNegativeInteger', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1291exactlyAssertedEL_first(isa, 'NoGood-ProblemProvabilityStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1292exactlyAssertedEL_first(isa, 'Neutral-ProblemProvabilityStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1293exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'HypotheticalContext']), 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 1294exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'HypotheticalContext']), 'RuleTemplate', 'BaseKB', vStrDef).
 1295exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'HypotheticalContext']), 'Individual', 'UniversalVocabularyMt', vStrDef).
 1296exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 1297exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), 'RuleTemplate', 'BaseKB', vStrDef).
 1298exactlyAssertedEL_first(isa, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), 'Individual', 'UniversalVocabularyMt', vStrDef).
 1299exactlyAssertedEL_first(isa, 'Multigraph', tCol, 'CoreCycLMt', vStrDef).
 1300exactlyAssertedEL_first(isa, 'Multigraph', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1301exactlyAssertedEL_first(isa, 'MtUnionFn', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1302exactlyAssertedEL_first(isa, 'MtUnionFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1303exactlyAssertedEL_first(isa, 'MtUnionFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1304exactlyAssertedEL_first(isa, 'MtUnionFn', 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
 1305exactlyAssertedEL_first(isa, 'MtTimeWithGranularityDimFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1306exactlyAssertedEL_first(isa, 'MtTimeWithGranularityDimFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1307exactlyAssertedEL_first(isa, 'MtTimeDimFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1308exactlyAssertedEL_first(isa, 'MtTimeDimFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1309exactlyAssertedEL_first(isa, 'MtSpace', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1310exactlyAssertedEL_first(isa, 'MtSpace', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1311exactlyAssertedEL_first(isa, 'MtSpace', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1312exactlyAssertedEL_first(isa, 'MonthOfYearType', 'SiblingDisjointCollectionType', 'UniversalVocabularyMt', vStrDef).
 1313exactlyAssertedEL_first(isa, 'MonthOfYearType', tCol, 'CoreCycLMt', vStrDef).
 1314exactlyAssertedEL_first(isa, 'MonthOfYearType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1315exactlyAssertedEL_first(isa, 'MonotonicallyTrue', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1316exactlyAssertedEL_first(isa, 'MonotonicallyTrue', 'CycHLTruthValue', 'UniversalVocabularyMt', vStrDef).
 1317exactlyAssertedEL_first(isa, 'MonotonicallyFalse', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1318exactlyAssertedEL_first(isa, 'MonotonicallyFalse', 'CycHLTruthValue', 'UniversalVocabularyMt', vStrDef).
 1319exactlyAssertedEL_first(isa, 'Monday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1320exactlyAssertedEL_first(isa, 'ModuloFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1321exactlyAssertedEL_first(isa, 'ModuloFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1322exactlyAssertedEL_first(isa, 'MinRangeFn', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1323exactlyAssertedEL_first(isa, 'MinRangeFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1324exactlyAssertedEL_first(isa, 'MinRangeFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1325exactlyAssertedEL_first(isa, 'MinRangeFn', 'AssociativeRelation', 'UniversalVocabularyMt', vStrDef).
 1326exactlyAssertedEL_first(isa, 'Minimum', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1327exactlyAssertedEL_first(isa, 'Minimum', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1328exactlyAssertedEL_first(isa, 'MicrotheoryDesignatingRelation', tCol, 'CoreCycLMt', vStrDef).
 1329exactlyAssertedEL_first(isa, 'MicrotheoryDesignatingRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1330exactlyAssertedEL_first(isa, 'Microtheory', tCol, 'LogicalTruthMt', vStrDef).
 1331exactlyAssertedEL_first(isa, 'Microtheory', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1332exactlyAssertedEL_first(isa, 'MeaningInSystemFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1333exactlyAssertedEL_first(isa, 'MeaningInSystemFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1334exactlyAssertedEL_first(isa, 'May', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1335exactlyAssertedEL_first(isa, 'May', tCol, 'CoreCycLMt', vStrDef).
 1336exactlyAssertedEL_first(isa, 'MaxRangeFn', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1337exactlyAssertedEL_first(isa, 'MaxRangeFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1338exactlyAssertedEL_first(isa, 'MaxRangeFn', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1339exactlyAssertedEL_first(isa, 'Maximum', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1340exactlyAssertedEL_first(isa, 'Maximum', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1341exactlyAssertedEL_first(isa, 'March', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1342exactlyAssertedEL_first(isa, 'March', tCol, 'CoreCycLMt', vStrDef).
 1343exactlyAssertedEL_first(isa, 'LogicalTruthMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1344exactlyAssertedEL_first(isa, 'LogicalTruthMt', 'Microtheory', 'LogicalTruthMt', vStrDef).
 1345exactlyAssertedEL_first(isa, 'LogicalTruthImplementationMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1346exactlyAssertedEL_first(isa, 'LogicalTruthImplementationMt', 'Microtheory', 'LogicalTruthImplementationMt', vStrDef).
 1347exactlyAssertedEL_first(isa, 'LogicalConnective', tCol, 'LogicalTruthMt', vStrDef).
 1348exactlyAssertedEL_first(isa, 'LogicalConnective', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1349exactlyAssertedEL_first(isa, 'LogFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1350exactlyAssertedEL_first(isa, 'LogFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1351exactlyAssertedEL_first(isa, 'List', tCol, 'CoreCycLMt', vStrDef).
 1352exactlyAssertedEL_first(isa, 'List', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1353exactlyAssertedEL_first(isa, 'LeaveVariablesAtEL', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1354exactlyAssertedEL_first(isa, 'LeaveSomeTermsAtELAndAllowKeywordVariables', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1355exactlyAssertedEL_first(isa, 'LeaveSomeTermsAtEL', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1356exactlyAssertedEL_first(isa, 'larkc-VariableBinding', tCol, 'UniversalVocabularyMt', vStrDef).
 1357exactlyAssertedEL_first(isa, 'larkc-TriplePatternQuery', tCol, 'UniversalVocabularyMt', vStrDef).
 1358exactlyAssertedEL_first(isa, 'larkc-SPARQLQuery', tCol, 'UniversalVocabularyMt', vStrDef).
 1359exactlyAssertedEL_first(isa, 'larkc-SetOfStatements', tCol, 'UniversalVocabularyMt', vStrDef).
 1360exactlyAssertedEL_first(isa, 'larkc-Selecter', tCol, 'UniversalVocabularyMt', vStrDef).
 1361exactlyAssertedEL_first(isa, 'larkc-Scalability', tCol, 'UniversalVocabularyMt', vStrDef).
 1362exactlyAssertedEL_first(isa, 'larkc-Resource', tCol, 'UniversalVocabularyMt', vStrDef).
 1363exactlyAssertedEL_first(isa, 'larkc-Reasoner', tCol, 'UniversalVocabularyMt', vStrDef).
 1364exactlyAssertedEL_first(isa, 'larkc-RdfGraph', tCol, 'UniversalVocabularyMt', vStrDef).
 1365exactlyAssertedEL_first(isa, 'larkc-QueryTransformer', tCol, 'UniversalVocabularyMt', vStrDef).
 1366exactlyAssertedEL_first(isa, 'larkc-Query', tCol, 'UniversalVocabularyMt', vStrDef).
 1367exactlyAssertedEL_first(isa, 'larkc-pluginByDataConnectsTo', 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1368exactlyAssertedEL_first(isa, 'larkc-Plugin', 'wsl-ClassificationRoot', 'BaseKB', vStrDef).
 1369exactlyAssertedEL_first(isa, 'larkc-Plugin', tCol, 'UniversalVocabularyMt', vStrDef).
 1370exactlyAssertedEL_first(isa, 'larkc-NaturalLanguageDocument', tCol, 'UniversalVocabularyMt', vStrDef).
 1371exactlyAssertedEL_first(isa, 'larkc-LabelledGroupOfStatements', tCol, 'UniversalVocabularyMt', vStrDef).
 1372exactlyAssertedEL_first(isa, 'larkc-KeywordQuery', tCol, 'UniversalVocabularyMt', vStrDef).
 1373exactlyAssertedEL_first(isa, 'larkc-InformationSetTransformer', tCol, 'UniversalVocabularyMt', vStrDef).
 1374exactlyAssertedEL_first(isa, 'larkc-InformationSet', tCol, 'UniversalVocabularyMt', vStrDef).
 1375exactlyAssertedEL_first(isa, 'larkc-Identifier', tCol, 'UniversalVocabularyMt', vStrDef).
 1376exactlyAssertedEL_first(isa, 'larkc-hasUri', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1377exactlyAssertedEL_first(isa, 'larkc-hasScalability', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1378exactlyAssertedEL_first(isa, 'larkc-hasOutputType', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1379exactlyAssertedEL_first(isa, 'larkc-hasInputType', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1380exactlyAssertedEL_first(isa, 'larkc-hasEndpoint', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1381exactlyAssertedEL_first(isa, 'larkc-hasCostPerInvocation', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1382exactlyAssertedEL_first(isa, 'larkc-GateTransformer', tCol, 'UniversalVocabularyMt', vStrDef).
 1383exactlyAssertedEL_first(isa, 'larkc-euro', tCol, 'UniversalVocabularyMt', vStrDef).
 1384exactlyAssertedEL_first(isa, 'larkc-Decider', tCol, 'UniversalVocabularyMt', vStrDef).
 1385exactlyAssertedEL_first(isa, 'larkc-DataSet', tCol, 'UniversalVocabularyMt', vStrDef).
 1386exactlyAssertedEL_first(isa, 'larkc-CycSelecter', tCol, 'UniversalVocabularyMt', vStrDef).
 1387exactlyAssertedEL_first(isa, 'larkc-CycReasoner', tCol, 'UniversalVocabularyMt', vStrDef).
 1388exactlyAssertedEL_first(isa, 'larkc-CycGateDecider', tCol, 'UniversalVocabularyMt', vStrDef).
 1389exactlyAssertedEL_first(isa, 'larkc-Cost', tCol, 'UniversalVocabularyMt', vStrDef).
 1390exactlyAssertedEL_first(isa, 'larkc-BooleanInformationSet', tCol, 'UniversalVocabularyMt', vStrDef).
 1391exactlyAssertedEL_first(isa, 'larkc-ArticleIdentifier', tCol, 'UniversalVocabularyMt', vStrDef).
 1392exactlyAssertedEL_first(isa, 'KnowledgeBase', tCol, 'UniversalVocabularyMt', vStrDef).
 1393exactlyAssertedEL_first(isa, 'KnowledgeBase', tCol, 'CoreCycLMt', vStrDef).
 1394exactlyAssertedEL_first(isa, 'Kappa', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1395exactlyAssertedEL_first(isa, 'Kappa', 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 1396exactlyAssertedEL_first(isa, 'Kappa', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1397exactlyAssertedEL_first(isa, 'June', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1398exactlyAssertedEL_first(isa, 'June', tCol, 'CoreCycLMt', vStrDef).
 1399exactlyAssertedEL_first(isa, 'July', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1400exactlyAssertedEL_first(isa, 'July', tCol, 'CoreCycLMt', vStrDef).
 1401exactlyAssertedEL_first(isa, 'January', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1402exactlyAssertedEL_first(isa, 'January', tCol, 'CoreCycLMt', vStrDef).
 1403exactlyAssertedEL_first(isa, 'ist-Asserted', 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 1404exactlyAssertedEL_first(isa, 'ist-Asserted', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1405exactlyAssertedEL_first(isa, 'IrreflexiveBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1406exactlyAssertedEL_first(isa, 'IrreflexiveBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1407exactlyAssertedEL_first(isa, 'IntervalMinFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1408exactlyAssertedEL_first(isa, 'IntervalMinFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1409exactlyAssertedEL_first(isa, 'IntervalMaxFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1410exactlyAssertedEL_first(isa, 'IntervalMaxFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1411exactlyAssertedEL_first(isa, 'IntervalEntry', 'Format', 'UniversalVocabularyMt', vStrDef).
 1412exactlyAssertedEL_first(isa, 'InterArgIsaPredicate', tCol, 'CoreCycLMt', vStrDef).
 1413exactlyAssertedEL_first(isa, 'InterArgIsaPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1414exactlyAssertedEL_first(isa, 'interArgIsa5-4', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1415exactlyAssertedEL_first(isa, 'interArgIsa5-4', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1416exactlyAssertedEL_first(isa, 'interArgIsa5-4', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1417exactlyAssertedEL_first(isa, 'interArgIsa5-3', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1418exactlyAssertedEL_first(isa, 'interArgIsa5-3', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1419exactlyAssertedEL_first(isa, 'interArgIsa5-3', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1420exactlyAssertedEL_first(isa, 'interArgIsa5-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1421exactlyAssertedEL_first(isa, 'interArgIsa5-2', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1422exactlyAssertedEL_first(isa, 'interArgIsa5-2', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1423exactlyAssertedEL_first(isa, 'interArgIsa5-1', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1424exactlyAssertedEL_first(isa, 'interArgIsa5-1', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1425exactlyAssertedEL_first(isa, 'interArgIsa5-1', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1426exactlyAssertedEL_first(isa, 'interArgIsa4-5', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1427exactlyAssertedEL_first(isa, 'interArgIsa4-5', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1428exactlyAssertedEL_first(isa, 'interArgIsa4-5', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1429exactlyAssertedEL_first(isa, 'interArgIsa4-3', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1430exactlyAssertedEL_first(isa, 'interArgIsa4-3', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1431exactlyAssertedEL_first(isa, 'interArgIsa4-3', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1432exactlyAssertedEL_first(isa, 'interArgIsa4-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1433exactlyAssertedEL_first(isa, 'interArgIsa4-2', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1434exactlyAssertedEL_first(isa, 'interArgIsa4-2', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1435exactlyAssertedEL_first(isa, 'interArgIsa4-1', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1436exactlyAssertedEL_first(isa, 'interArgIsa4-1', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1437exactlyAssertedEL_first(isa, 'interArgIsa4-1', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1438exactlyAssertedEL_first(isa, 'interArgIsa3-5', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1439exactlyAssertedEL_first(isa, 'interArgIsa3-5', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1440exactlyAssertedEL_first(isa, 'interArgIsa3-5', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1441exactlyAssertedEL_first(isa, 'interArgIsa3-4', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1442exactlyAssertedEL_first(isa, 'interArgIsa3-4', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1443exactlyAssertedEL_first(isa, 'interArgIsa3-4', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1444exactlyAssertedEL_first(isa, 'interArgIsa3-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1445exactlyAssertedEL_first(isa, 'interArgIsa3-2', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1446exactlyAssertedEL_first(isa, 'interArgIsa3-2', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1447exactlyAssertedEL_first(isa, 'interArgIsa3-1', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1448exactlyAssertedEL_first(isa, 'interArgIsa3-1', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1449exactlyAssertedEL_first(isa, 'interArgIsa3-1', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1450exactlyAssertedEL_first(isa, 'interArgIsa2-5', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1451exactlyAssertedEL_first(isa, 'interArgIsa2-5', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1452exactlyAssertedEL_first(isa, 'interArgIsa2-5', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1453exactlyAssertedEL_first(isa, 'interArgIsa2-4', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1454exactlyAssertedEL_first(isa, 'interArgIsa2-4', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1455exactlyAssertedEL_first(isa, 'interArgIsa2-4', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1456exactlyAssertedEL_first(isa, 'interArgIsa2-3', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1457exactlyAssertedEL_first(isa, 'interArgIsa2-3', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1458exactlyAssertedEL_first(isa, 'interArgIsa2-3', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1459exactlyAssertedEL_first(isa, 'interArgIsa2-1', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1460exactlyAssertedEL_first(isa, 'interArgIsa2-1', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1461exactlyAssertedEL_first(isa, 'interArgIsa2-1', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1462exactlyAssertedEL_first(isa, 'interArgIsa1-5', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1463exactlyAssertedEL_first(isa, 'interArgIsa1-5', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1464exactlyAssertedEL_first(isa, 'interArgIsa1-5', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1465exactlyAssertedEL_first(isa, 'interArgIsa1-4', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1466exactlyAssertedEL_first(isa, 'interArgIsa1-4', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1467exactlyAssertedEL_first(isa, 'interArgIsa1-4', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1468exactlyAssertedEL_first(isa, 'interArgIsa1-3', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1469exactlyAssertedEL_first(isa, 'interArgIsa1-3', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1470exactlyAssertedEL_first(isa, 'interArgIsa1-3', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1471exactlyAssertedEL_first(isa, 'interArgIsa1-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1472exactlyAssertedEL_first(isa, 'interArgIsa1-2', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1473exactlyAssertedEL_first(isa, 'interArgIsa1-2', 'InterArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 1474exactlyAssertedEL_first(isa, 'interArgGenl1-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1475exactlyAssertedEL_first(isa, 'interArgGenl1-2', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1476exactlyAssertedEL_first(isa, 'interArgGenl1-2', 'ArgTypePredicate', 'UniversalVocabularyMt', vStrDef).
 1477exactlyAssertedEL_first(isa, 'InterArgFormatPredicate', tCol, 'CoreCycLMt', vStrDef).
 1478exactlyAssertedEL_first(isa, 'InterArgFormatPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1479exactlyAssertedEL_first(isa, 'interArgFormat1-2', 'WFFConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 1480exactlyAssertedEL_first(isa, 'interArgFormat1-2', 'InterArgFormatPredicate', 'UniversalVocabularyMt', vStrDef).
 1481exactlyAssertedEL_first(isa, 'Integer', tCol, 'CoreCycLMt', vStrDef).
 1482exactlyAssertedEL_first(isa, 'Integer', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1483exactlyAssertedEL_first(isa, 'InferenceSupportedTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1484exactlyAssertedEL_first(isa, 'InferenceSupportedTerm', tCol, 'UniversalVocabularyMt', vStrDef).
 1485exactlyAssertedEL_first(isa, 'InferenceSupportedPredicate', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1486exactlyAssertedEL_first(isa, 'InferenceSupportedPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1487exactlyAssertedEL_first(isa, 'InferenceSupportedFunction', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1488exactlyAssertedEL_first(isa, 'InferenceSupportedFunction', tCol, 'UniversalVocabularyMt', vStrDef).
 1489exactlyAssertedEL_first(isa, 'InferenceSupportedCollection', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1490exactlyAssertedEL_first(isa, 'InferenceRelatedBookkeepingPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1491exactlyAssertedEL_first(isa, 'InferenceRelatedBookkeepingPredicate', tCol, 'CoreCycLImplementationMt', vStrDef).
 1492exactlyAssertedEL_first(isa, 'InferencePSC', 'ProblemSolvingCntxt', 'UniversalVocabularyMt', vStrDef).
 1493exactlyAssertedEL_first(isa, 'Individual', tCol, 'LogicalTruthMt', vStrDef).
 1494exactlyAssertedEL_first(isa, 'Individual', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1495exactlyAssertedEL_first(isa, 'IndeterminateTermDenotingFunction', tCol, 'UniversalVocabularyMt', vStrDef).
 1496exactlyAssertedEL_first(isa, 'IndeterminateTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1497exactlyAssertedEL_first(isa, 'HypotheticalContext', tCol, 'CoreCycLMt', vStrDef).
 1498exactlyAssertedEL_first(isa, 'HypotheticalContext', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1499exactlyAssertedEL_first(isa, 'HumanCyclist', tCol, 'UniversalVocabularyMt', vStrDef).
 1500exactlyAssertedEL_first(isa, 'HumanCyclist', tCol, 'CoreCycLMt', vStrDef).
 1501exactlyAssertedEL_first(isa, 'HLPrototypicalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1502exactlyAssertedEL_first(isa, 'HLExternalIDString', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1503exactlyAssertedEL_first(isa, 'HLAssertedArgumentKeywordDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1504exactlyAssertedEL_first(isa, 'Guest', 'HumanCyclist', 'UniversalVocabularyMt', vStrDef).
 1505exactlyAssertedEL_first(isa, 'Good-ProblemProvabilityStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1506exactlyAssertedEL_first(isa, 'genls-SpecDenotesGenlInstances', 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
 1507exactlyAssertedEL_first(isa, 'genls-SpecDenotesGenlInstances', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1508exactlyAssertedEL_first(isa, 'genls-GenlDenotesSpecInstances', 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', vStrDef).
 1509exactlyAssertedEL_first(isa, 'genls-GenlDenotesSpecInstances', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1510exactlyAssertedEL_first(isa, 'FunctionToArg', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1511exactlyAssertedEL_first(isa, 'FunctionToArg', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1512exactlyAssertedEL_first(isa, tFunction, tCol, 'LogicalTruthMt', vStrDef).
 1513exactlyAssertedEL_first(isa, tFunction, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1514exactlyAssertedEL_first(isa, 'Friday', 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 1515exactlyAssertedEL_first(isa, 'Forward-AssertionDirection', 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 1516exactlyAssertedEL_first(isa, 'FormulaArityFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1517exactlyAssertedEL_first(isa, 'FormulaArityFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1518exactlyAssertedEL_first(isa, 'FormulaArgSetFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1519exactlyAssertedEL_first(isa, 'FormulaArgSetFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1520exactlyAssertedEL_first(isa, 'FormulaArgListFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1521exactlyAssertedEL_first(isa, 'FormulaArgListFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1522exactlyAssertedEL_first(isa, 'FormulaArgFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1523exactlyAssertedEL_first(isa, 'FormulaArgFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1524exactlyAssertedEL_first(isa, 'Format', tCol, 'CoreCycLMt', vStrDef).
 1525exactlyAssertedEL_first(isa, 'Format', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1526exactlyAssertedEL_first(isa, 'FOL-TermFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1527exactlyAssertedEL_first(isa, 'FOL-TermFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1528exactlyAssertedEL_first(isa, 'FOL-PredicateFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1529exactlyAssertedEL_first(isa, 'FOL-PredicateFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1530exactlyAssertedEL_first(isa, 'FOL-FunctionFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1531exactlyAssertedEL_first(isa, 'FOL-FunctionFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1532exactlyAssertedEL_first(isa, 'FixedAritySkolemFunction', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1533exactlyAssertedEL_first(isa, 'FixedAritySkolemFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1534exactlyAssertedEL_first(isa, 'FixedAritySkolemFuncN', tCol, 'CoreCycLImplementationMt', vStrDef).
 1535exactlyAssertedEL_first(isa, 'FixedAritySkolemFuncN', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1536exactlyAssertedEL_first(isa, 'FixedArityRelation', tCol, 'LogicalTruthMt', vStrDef).
 1537exactlyAssertedEL_first(isa, 'FixedArityRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1538exactlyAssertedEL_first(isa, 'February', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1539exactlyAssertedEL_first(isa, 'February', tCol, 'CoreCycLMt', vStrDef).
 1540exactlyAssertedEL_first(isa, 'False', 'TruthValue', 'UniversalVocabularyMt', vStrDef).
 1541exactlyAssertedEL_first(isa, 'False', 'TruthValue', 'LogicalTruthMt', vStrDef).
 1542exactlyAssertedEL_first(isa, 'ExpFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1543exactlyAssertedEL_first(isa, 'ExpFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1544exactlyAssertedEL_first(isa, 'ExpandSubLFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1545exactlyAssertedEL_first(isa, 'ExpandSubLFn', tFunction, 'LogicalTruthMt', vStrDef).
 1546exactlyAssertedEL_first(isa, 'ExpandSubLFn', 'FixedArityRelation', 'LogicalTruthMt', vStrDef).
 1547exactlyAssertedEL_first(isa, 'ExpandSubLFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1548exactlyAssertedEL_first(isa, 'ExistentialQuantifier-Bounded', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1549exactlyAssertedEL_first(isa, 'ExistentialQuantifier', tCol, 'CoreCycLMt', vStrDef).
 1550exactlyAssertedEL_first(isa, 'ExistentialQuantifier', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1551exactlyAssertedEL_first(isa, 'ExceptionPredicate', tCol, 'CoreCycLMt', vStrDef).
 1552exactlyAssertedEL_first(isa, 'ExceptionPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1553exactlyAssertedEL_first(isa, 'EverythingPSC', 'ProblemSolvingCntxt', 'UniversalVocabularyMt', vStrDef).
 1554exactlyAssertedEL_first(isa, 'EvaluateSubLFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1555exactlyAssertedEL_first(isa, 'EvaluateSubLFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1556exactlyAssertedEL_first(isa, 'EvaluatableRelation', tCol, 'CoreCycLMt', vStrDef).
 1557exactlyAssertedEL_first(isa, 'EvaluatableRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1558exactlyAssertedEL_first(isa, 'EvaluatablePredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1559exactlyAssertedEL_first(isa, 'EvaluatableFunction', tCol, 'CoreCycLMt', vStrDef).
 1560exactlyAssertedEL_first(isa, 'EvaluatableFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1561exactlyAssertedEL_first(isa, 'EscapeQuote', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1562exactlyAssertedEL_first(isa, 'EscapeQuote', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1563exactlyAssertedEL_first(isa, 'EscapeQuote', 'UnreifiableFunction', 'LogicalTruthImplementationMt', vStrDef).
 1564exactlyAssertedEL_first(isa, 'EscapeQuote', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1565exactlyAssertedEL_first(isa, 'equalStrings-CaseInsensitive', 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1566exactlyAssertedEL_first(isa, 'EnglishParaphraseMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1567exactlyAssertedEL_first(isa, 'ELRelation-Reversible', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1568exactlyAssertedEL_first(isa, 'ELRelation-OneWay', tCol, 'CoreCycLImplementationMt', vStrDef).
 1569exactlyAssertedEL_first(isa, 'ELRelation-OneWay', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1570exactlyAssertedEL_first(isa, 'ELRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1571exactlyAssertedEL_first(isa, 'DontReOrderCommutativeTerms', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1572exactlyAssertedEL_first(isa, 'DocumentationPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1573exactlyAssertedEL_first(isa, 'DocumentationPredicate', tCol, 'CoreCycLMt', vStrDef).
 1574exactlyAssertedEL_first(isa, 'DocumentationConstant', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1575exactlyAssertedEL_first(isa, 'DocumentationConstant', tCol, 'CoreCycLMt', vStrDef).
 1576exactlyAssertedEL_first(isa, 'DistributingMetaKnowledgePredicate', tCol, 'CoreCycLMt', vStrDef).
 1577exactlyAssertedEL_first(isa, 'DistributingMetaKnowledgePredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1578exactlyAssertedEL_first(isa, 'DisjointCollectionType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1579exactlyAssertedEL_first(isa, 'DirectedMultigraph', tCol, 'CoreCycLMt', vStrDef).
 1580exactlyAssertedEL_first(isa, 'DirectedMultigraph', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1581exactlyAssertedEL_first(isa, 'DifferenceFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1582exactlyAssertedEL_first(isa, 'DifferenceFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1583exactlyAssertedEL_first(isa, 'DefaultTrue', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1584exactlyAssertedEL_first(isa, 'DefaultTrue', 'CycHLTruthValue', 'UniversalVocabularyMt', vStrDef).
 1585exactlyAssertedEL_first(isa, 'DefaultMonotonicPredicate', tCol, 'CoreCycLImplementationMt', vStrDef).
 1586exactlyAssertedEL_first(isa, 'DefaultMonotonicPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1587exactlyAssertedEL_first(isa, 'DefaultFalse', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1588exactlyAssertedEL_first(isa, 'DefaultFalse', 'CycHLTruthValue', 'UniversalVocabularyMt', vStrDef).
 1589exactlyAssertedEL_first(isa, 'December', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1590exactlyAssertedEL_first(isa, 'December', tCol, 'CoreCycLMt', vStrDef).
 1591exactlyAssertedEL_first(isa, 'DayOfWeekType', 'SiblingDisjointCollectionType', 'UniversalVocabularyMt', vStrDef).
 1592exactlyAssertedEL_first(isa, 'DateEncodeStringFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1593exactlyAssertedEL_first(isa, 'DateEncodeStringFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1594exactlyAssertedEL_first(isa, 'DateDecodeStringFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1595exactlyAssertedEL_first(isa, 'DateDecodeStringFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1596exactlyAssertedEL_first(isa, 'CycTransformationProof', tCol, 'UniversalVocabularyMt', vStrDef).
 1597exactlyAssertedEL_first(isa, 'CycTacticFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1598exactlyAssertedEL_first(isa, 'CycTacticFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1599exactlyAssertedEL_first(isa, 'CycTactic', tCol, 'UniversalVocabularyMt', vStrDef).
 1600exactlyAssertedEL_first(isa, 'CycSupportDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1601exactlyAssertedEL_first(isa, 'CycProvabilityStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1602exactlyAssertedEL_first(isa, 'CycProofFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1603exactlyAssertedEL_first(isa, 'CycProofFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1604exactlyAssertedEL_first(isa, 'CycProof', tCol, 'UniversalVocabularyMt', vStrDef).
 1605exactlyAssertedEL_first(isa, 'CycProblemStoreFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1606exactlyAssertedEL_first(isa, 'CycProblemStoreFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1607exactlyAssertedEL_first(isa, 'CycProblemStore', tCol, 'UniversalVocabularyMt', vStrDef).
 1608exactlyAssertedEL_first(isa, 'CycProblemLinkFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1609exactlyAssertedEL_first(isa, 'CycProblemLinkFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1610exactlyAssertedEL_first(isa, 'CycProblemLink-Union', tCol, 'UniversalVocabularyMt', vStrDef).
 1611exactlyAssertedEL_first(isa, 'CycProblemLink-Transformation', tCol, 'UniversalVocabularyMt', vStrDef).
 1612exactlyAssertedEL_first(isa, 'CycProblemLink-Structural', tCol, 'UniversalVocabularyMt', vStrDef).
 1613exactlyAssertedEL_first(isa, 'CycProblemLink-Split', tCol, 'UniversalVocabularyMt', vStrDef).
 1614exactlyAssertedEL_first(isa, 'CycProblemLink-Restriction', tCol, 'UniversalVocabularyMt', vStrDef).
 1615exactlyAssertedEL_first(isa, 'CycProblemLink-Removal', tCol, 'UniversalVocabularyMt', vStrDef).
 1616exactlyAssertedEL_first(isa, 'CycProblemLink-Logical', tCol, 'UniversalVocabularyMt', vStrDef).
 1617exactlyAssertedEL_first(isa, 'CycProblemLink-JoinOrdered', tCol, 'UniversalVocabularyMt', vStrDef).
 1618exactlyAssertedEL_first(isa, 'CycProblemLink-Join', tCol, 'UniversalVocabularyMt', vStrDef).
 1619exactlyAssertedEL_first(isa, 'CycProblemLink-Disjunctive', tCol, 'UniversalVocabularyMt', vStrDef).
 1620exactlyAssertedEL_first(isa, 'CycProblemLink-Content', tCol, 'UniversalVocabularyMt', vStrDef).
 1621exactlyAssertedEL_first(isa, 'CycProblemLink-Conjunctive', tCol, 'UniversalVocabularyMt', vStrDef).
 1622exactlyAssertedEL_first(isa, 'CycProblemLink-AnswerLink', tCol, 'UniversalVocabularyMt', vStrDef).
 1623exactlyAssertedEL_first(isa, 'CycProblemLink', tCol, 'UniversalVocabularyMt', vStrDef).
 1624exactlyAssertedEL_first(isa, 'CycProblemFn', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1625exactlyAssertedEL_first(isa, 'CycProblemFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1626exactlyAssertedEL_first(isa, 'CycProblem', tCol, 'UniversalVocabularyMt', vStrDef).
 1627exactlyAssertedEL_first(isa, ftVar, ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1628exactlyAssertedEL_first(isa, ftVar, tCol, 'LogicalTruthMt', vStrDef).
 1629exactlyAssertedEL_first(isa, ftVar, tCol, 'CoreCycLMt', vStrDef).
 1630exactlyAssertedEL_first(isa, ftVar, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1631exactlyAssertedEL_first(isa, 'CycLTruthValueSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1632exactlyAssertedEL_first(isa, 'CycLTruthValueSentence', tCol, 'CoreCycLMt', vStrDef).
 1633exactlyAssertedEL_first(isa, 'CycLTruthValueSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1634exactlyAssertedEL_first(isa, 'CycLTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1635exactlyAssertedEL_first(isa, 'CycLTerm', tCol, 'CoreCycLMt', vStrDef).
 1636exactlyAssertedEL_first(isa, 'CycLTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1637exactlyAssertedEL_first(isa, 'CycLSentence-ClosedPredicate', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1638exactlyAssertedEL_first(isa, 'CycLSentence-ClosedPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1639exactlyAssertedEL_first(isa, 'CycLSentence-ClosedPredicate', tCol, 'CoreCycLMt', vStrDef).
 1640exactlyAssertedEL_first(isa, 'CycLSentence-Assertible', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1641exactlyAssertedEL_first(isa, 'CycLSentence-Assertible', tCol, 'LogicalTruthMt', vStrDef).
 1642exactlyAssertedEL_first(isa, 'CycLSentence-Assertible', tCol, 'CoreCycLMt', vStrDef).
 1643exactlyAssertedEL_first(isa, 'CycLSentence-Assertible', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1644exactlyAssertedEL_first(isa, 'CycLSentence-Askable', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1645exactlyAssertedEL_first(isa, 'CycLSentence-Askable', tCol, 'CoreCycLMt', vStrDef).
 1646exactlyAssertedEL_first(isa, 'CycLSentence-Askable', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1647exactlyAssertedEL_first(isa, 'CycLSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1648exactlyAssertedEL_first(isa, 'CycLSentence', tCol, 'CoreCycLMt', vStrDef).
 1649exactlyAssertedEL_first(isa, 'CycLSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1650exactlyAssertedEL_first(isa, 'CycLRuleAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1651exactlyAssertedEL_first(isa, 'CycLRuleAssertion', tCol, 'CoreCycLMt', vStrDef).
 1652exactlyAssertedEL_first(isa, 'CycLRuleAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1653exactlyAssertedEL_first(isa, 'CycLRepresentedTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1654exactlyAssertedEL_first(isa, 'CycLRepresentedTerm', tCol, 'CoreCycLMt', vStrDef).
 1655exactlyAssertedEL_first(isa, 'CycLRepresentedTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1656exactlyAssertedEL_first(isa, 'CycLRepresentedAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1657exactlyAssertedEL_first(isa, 'CycLRepresentedAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1658exactlyAssertedEL_first(isa, 'CycLRepresentedAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1659exactlyAssertedEL_first(isa, 'CycLReifiedDenotationalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1660exactlyAssertedEL_first(isa, 'CycLReifiedDenotationalTerm', tCol, 'CoreCycLMt', vStrDef).
 1661exactlyAssertedEL_first(isa, 'CycLReifiedDenotationalTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1662exactlyAssertedEL_first(isa, 'CycLReifiableNonAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1663exactlyAssertedEL_first(isa, 'CycLReifiableNonAtomicTerm', tCol, 'LogicalTruthImplementationMt', vStrDef).
 1664exactlyAssertedEL_first(isa, 'CycLReifiableNonAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1665exactlyAssertedEL_first(isa, 'CycLReifiableDenotationalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1666exactlyAssertedEL_first(isa, 'CycLReifiableDenotationalTerm', tCol, 'CoreCycLMt', vStrDef).
 1667exactlyAssertedEL_first(isa, 'CycLReifiableDenotationalTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1668exactlyAssertedEL_first(isa, 'CycLReformulationRulePredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1669exactlyAssertedEL_first(isa, 'CycLReformulationRulePredicate', tCol, 'CoreCycLImplementationMt', vStrDef).
 1670exactlyAssertedEL_first(isa, 'CycLPropositionalSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1671exactlyAssertedEL_first(isa, 'CycLPropositionalSentence', tCol, 'CoreCycLMt', vStrDef).
 1672exactlyAssertedEL_first(isa, 'CycLPropositionalSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1673exactlyAssertedEL_first(isa, 'CycLOpenSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1674exactlyAssertedEL_first(isa, 'CycLOpenSentence', tCol, 'CoreCycLMt', vStrDef).
 1675exactlyAssertedEL_first(isa, 'CycLOpenSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1676exactlyAssertedEL_first(isa, 'CycLOpenNonAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1677exactlyAssertedEL_first(isa, 'CycLOpenNonAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1678exactlyAssertedEL_first(isa, 'CycLOpenNonAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1679exactlyAssertedEL_first(isa, 'CycLOpenFormula', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1680exactlyAssertedEL_first(isa, 'CycLOpenFormula', tCol, 'CoreCycLMt', vStrDef).
 1681exactlyAssertedEL_first(isa, 'CycLOpenFormula', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1682exactlyAssertedEL_first(isa, 'CycLOpenExpression', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1683exactlyAssertedEL_first(isa, 'CycLOpenExpression', tCol, 'CoreCycLMt', vStrDef).
 1684exactlyAssertedEL_first(isa, 'CycLOpenExpression', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1685exactlyAssertedEL_first(isa, 'CycLOpenDenotationalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1686exactlyAssertedEL_first(isa, 'CycLOpenDenotationalTerm', tCol, 'CoreCycLMt', vStrDef).
 1687exactlyAssertedEL_first(isa, 'CycLOpenDenotationalTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1688exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-ClosedFunctor', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1689exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-ClosedFunctor', tCol, 'UniversalVocabularyMt', vStrDef).
 1690exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-ClosedFunctor', tCol, 'CoreCycLMt', vStrDef).
 1691exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Assertible', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1692exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Assertible', tCol, 'CoreCycLMt', vStrDef).
 1693exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Assertible', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1694exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Askable', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1695exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Askable', tCol, 'CoreCycLMt', vStrDef).
 1696exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm-Askable', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1697exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1698exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1699exactlyAssertedEL_first(isa, 'CycLNonAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1700exactlyAssertedEL_first(isa, 'CycLNonAtomicReifiedTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1701exactlyAssertedEL_first(isa, 'CycLNonAtomicReifiedTerm', tCol, 'CoreCycLMt', vStrDef).
 1702exactlyAssertedEL_first(isa, 'CycLNonAtomicReifiedTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1703exactlyAssertedEL_first(isa, 'CyclistDefinitionalMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1704exactlyAssertedEL_first(isa, 'Cyclist', tCol, 'UniversalVocabularyMt', vStrDef).
 1705exactlyAssertedEL_first(isa, 'Cyclist', tCol, 'CoreCycLMt', vStrDef).
 1706exactlyAssertedEL_first(isa, 'CycLIndexedTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1707exactlyAssertedEL_first(isa, 'CycLIndexedTerm', tCol, 'CoreCycLImplementationMt', vStrDef).
 1708exactlyAssertedEL_first(isa, 'CycLIndexedTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1709exactlyAssertedEL_first(isa, 'CycLGenericRelationFormula', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1710exactlyAssertedEL_first(isa, 'CycLGenericRelationFormula', tCol, 'CoreCycLMt', vStrDef).
 1711exactlyAssertedEL_first(isa, 'CycLGenericRelationFormula', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1712exactlyAssertedEL_first(isa, 'CycLGAFAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1713exactlyAssertedEL_first(isa, 'CycLGAFAssertion', tCol, 'CoreCycLMt', vStrDef).
 1714exactlyAssertedEL_first(isa, 'CycLGAFAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1715exactlyAssertedEL_first(isa, 'CycLFormulaicSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1716exactlyAssertedEL_first(isa, 'CycLFormulaicSentence', tCol, 'CoreCycLMt', vStrDef).
 1717exactlyAssertedEL_first(isa, 'CycLFormulaicSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1718exactlyAssertedEL_first(isa, 'CycLFormula', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1719exactlyAssertedEL_first(isa, 'CycLFormula', tCol, 'CoreCycLMt', vStrDef).
 1720exactlyAssertedEL_first(isa, 'CycLFormula', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1721exactlyAssertedEL_first(isa, ttExpressionType, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1722exactlyAssertedEL_first(isa, 'CycLExpression-Assertible', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1723exactlyAssertedEL_first(isa, 'CycLExpression-Assertible', tCol, 'CoreCycLMt', vStrDef).
 1724exactlyAssertedEL_first(isa, 'CycLExpression-Assertible', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1725exactlyAssertedEL_first(isa, 'CycLExpression-Askable', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1726exactlyAssertedEL_first(isa, 'CycLExpression-Askable', tCol, 'CoreCycLMt', vStrDef).
 1727exactlyAssertedEL_first(isa, 'CycLExpression-Askable', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1728exactlyAssertedEL_first(isa, 'CycLExpression', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1729exactlyAssertedEL_first(isa, 'CycLExpression', tCol, 'LogicalTruthMt', vStrDef).
 1730exactlyAssertedEL_first(isa, 'CycLExpression', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1731exactlyAssertedEL_first(isa, 'CycLDenotationalTerm-Assertible', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1732exactlyAssertedEL_first(isa, 'CycLDenotationalTerm-Assertible', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1733exactlyAssertedEL_first(isa, 'CycLDenotationalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1734exactlyAssertedEL_first(isa, 'CycLDenotationalTerm', tCol, 'CoreCycLMt', vStrDef).
 1735exactlyAssertedEL_first(isa, 'CycLDenotationalTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1736exactlyAssertedEL_first(isa, 'CycLDeducedAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1737exactlyAssertedEL_first(isa, 'CycLDeducedAssertion', tCol, 'CoreCycLMt', vStrDef).
 1738exactlyAssertedEL_first(isa, 'CycLDeducedAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1739exactlyAssertedEL_first(isa, 'CycLConstant', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1740exactlyAssertedEL_first(isa, 'CycLConstant', tCol, 'CoreCycLMt', vStrDef).
 1741exactlyAssertedEL_first(isa, 'CycLConstant', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1742exactlyAssertedEL_first(isa, 'CycLClosedSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1743exactlyAssertedEL_first(isa, 'CycLClosedSentence', tCol, 'CoreCycLMt', vStrDef).
 1744exactlyAssertedEL_first(isa, 'CycLClosedSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1745exactlyAssertedEL_first(isa, 'CycLClosedNonAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1746exactlyAssertedEL_first(isa, 'CycLClosedNonAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1747exactlyAssertedEL_first(isa, 'CycLClosedNonAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1748exactlyAssertedEL_first(isa, 'CycLClosedFormula', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1749exactlyAssertedEL_first(isa, 'CycLClosedFormula', tCol, 'CoreCycLMt', vStrDef).
 1750exactlyAssertedEL_first(isa, 'CycLClosedFormula', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1751exactlyAssertedEL_first(isa, 'CycLClosedExpression', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1752exactlyAssertedEL_first(isa, 'CycLClosedExpression', tCol, 'CoreCycLMt', vStrDef).
 1753exactlyAssertedEL_first(isa, 'CycLClosedExpression', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1754exactlyAssertedEL_first(isa, 'CycLClosedDenotationalTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1755exactlyAssertedEL_first(isa, 'CycLClosedDenotationalTerm', tCol, 'CoreCycLMt', vStrDef).
 1756exactlyAssertedEL_first(isa, 'CycLClosedDenotationalTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1757exactlyAssertedEL_first(isa, 'CycLClosedAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1758exactlyAssertedEL_first(isa, 'CycLClosedAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1759exactlyAssertedEL_first(isa, 'CycLClosedAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1760exactlyAssertedEL_first(isa, 'CycLClosedAtomicSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1761exactlyAssertedEL_first(isa, 'CycLClosedAtomicSentence', tCol, 'CoreCycLMt', vStrDef).
 1762exactlyAssertedEL_first(isa, 'CycLClosedAtomicSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1763exactlyAssertedEL_first(isa, 'CycLAtomicTerm', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1764exactlyAssertedEL_first(isa, 'CycLAtomicTerm', tCol, 'CoreCycLMt', vStrDef).
 1765exactlyAssertedEL_first(isa, 'CycLAtomicTerm', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1766exactlyAssertedEL_first(isa, 'CycLAtomicSentence', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1767exactlyAssertedEL_first(isa, 'CycLAtomicSentence', tCol, 'CoreCycLMt', vStrDef).
 1768exactlyAssertedEL_first(isa, 'CycLAtomicSentence', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1769exactlyAssertedEL_first(isa, 'CycLAtomicAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1770exactlyAssertedEL_first(isa, 'CycLAtomicAssertion', tCol, 'CoreCycLMt', vStrDef).
 1771exactlyAssertedEL_first(isa, 'CycLAtomicAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1772exactlyAssertedEL_first(isa, 'CycLAssertionDirection', 'SiblingDisjointCollectionType', 'UniversalVocabularyMt', vStrDef).
 1773exactlyAssertedEL_first(isa, 'CycLAssertionDirection', tCol, 'CoreCycLImplementationMt', vStrDef).
 1774exactlyAssertedEL_first(isa, 'CycLAssertionDirection', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1775exactlyAssertedEL_first(isa, 'CycLAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1776exactlyAssertedEL_first(isa, 'CycLAssertion', tCol, 'CoreCycLMt', vStrDef).
 1777exactlyAssertedEL_first(isa, 'CycLAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1778exactlyAssertedEL_first(isa, 'CycLAssertedAssertion', ttExpressionType, 'UniversalVocabularyMt', vStrDef).
 1779exactlyAssertedEL_first(isa, 'CycLAssertedAssertion', tCol, 'CoreCycLMt', vStrDef).
 1780exactlyAssertedEL_first(isa, 'CycLAssertedAssertion', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1781exactlyAssertedEL_first(isa, 'CycKBDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1782exactlyAssertedEL_first(isa, 'CycInferenceProblemLinkStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1783exactlyAssertedEL_first(isa, 'CycInferenceFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1784exactlyAssertedEL_first(isa, 'CycInferenceFn', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1785exactlyAssertedEL_first(isa, 'CycInferenceDataStructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1786exactlyAssertedEL_first(isa, 'CycInferenceBindingsDataStructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1787exactlyAssertedEL_first(isa, 'CycInferenceAnswerJustification', tCol, 'UniversalVocabularyMt', vStrDef).
 1788exactlyAssertedEL_first(isa, 'CycInferenceAnswer', tCol, 'UniversalVocabularyMt', vStrDef).
 1789exactlyAssertedEL_first(isa, 'CycInference', tCol, 'UniversalVocabularyMt', vStrDef).
 1790exactlyAssertedEL_first(isa, 'CycHLTruthValue', tCol, 'UniversalVocabularyMt', vStrDef).
 1791exactlyAssertedEL_first(isa, 'CycHLTruthValue', tCol, 'CoreCycLImplementationMt', vStrDef).
 1792exactlyAssertedEL_first(isa, 'CycHLSupportDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1793exactlyAssertedEL_first(isa, 'CycDeductionDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1794exactlyAssertedEL_first(isa, 'CycArgumentDatastructure', tCol, 'UniversalVocabularyMt', vStrDef).
 1795exactlyAssertedEL_first(isa, 'CycAdministrator', 'HumanCyclist', 'UniversalVocabularyMt', vStrDef).
 1796exactlyAssertedEL_first(isa, 'CurrentWorldDataCollectorMt-NonHomocentric', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1797exactlyAssertedEL_first(isa, 'CoreCycLMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1798exactlyAssertedEL_first(isa, 'CoreCycLImplementationMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1799exactlyAssertedEL_first(isa, 'CommutativeRelation', tCol, 'CoreCycLMt', vStrDef).
 1800exactlyAssertedEL_first(isa, 'CommutativeRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1801exactlyAssertedEL_first(isa, 'CollectionRuleTemplateFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1802exactlyAssertedEL_first(isa, 'CollectionRuleTemplateFn', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1803exactlyAssertedEL_first(isa, 'CollectionDenotingFunction', tCol, 'CoreCycLMt', vStrDef).
 1804exactlyAssertedEL_first(isa, 'CollectionDenotingFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1805exactlyAssertedEL_first(isa, tCol, tCol, 'LogicalTruthMt', vStrDef).
 1806exactlyAssertedEL_first(isa, tCol, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1807exactlyAssertedEL_first(isa, 'Code-AssertionDirection', 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 1808exactlyAssertedEL_first(isa, 'Closed-InferenceProblemLinkStatus', tCol, 'UniversalVocabularyMt', vStrDef).
 1809exactlyAssertedEL_first(isa, 'CharacterString', tCol, 'UniversalVocabularyMt', vStrDef).
 1810exactlyAssertedEL_first(isa, 'CanonicalizerDirective', tCol, 'UniversalVocabularyMt', vStrDef).
 1811exactlyAssertedEL_first(isa, 'BroadMicrotheory', tCol, 'CoreCycLImplementationMt', vStrDef).
 1812exactlyAssertedEL_first(isa, 'BroadMicrotheory', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1813exactlyAssertedEL_first(isa, 'BookkeepingPredicate', tCol, 'CoreCycLMt', vStrDef).
 1814exactlyAssertedEL_first(isa, 'BookkeepingPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1815exactlyAssertedEL_first(isa, 'BookkeepingMt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 1816exactlyAssertedEL_first(isa, 'BookkeepingMt', 'BroadMicrotheory', 'UniversalVocabularyMt', vStrDef).
 1817exactlyAssertedEL_first(isa, 'BinaryRelation', tCol, 'CoreCycLMt', vStrDef).
 1818exactlyAssertedEL_first(isa, 'BinaryRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1819exactlyAssertedEL_first(isa, 'BinaryPredicate', 'PredicateTypeByArity', 'UniversalVocabularyMt', vStrDef).
 1820exactlyAssertedEL_first(isa, 'BinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1821exactlyAssertedEL_first(isa, 'BinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1822exactlyAssertedEL_first(isa, 'BinaryFunction', tCol, 'CoreCycLMt', vStrDef).
 1823exactlyAssertedEL_first(isa, 'BinaryFunction', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1824exactlyAssertedEL_first(isa, 'BaseKB', 'BroadMicrotheory', 'BaseKB', vStrDef).
 1825exactlyAssertedEL_first(isa, 'Backward-AssertionDirection', 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 1826exactlyAssertedEL_first(isa, 'Average', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1827exactlyAssertedEL_first(isa, 'Average', 'BinaryFunction', 'UniversalVocabularyMt', vStrDef).
 1828exactlyAssertedEL_first(isa, 'August', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1829exactlyAssertedEL_first(isa, 'August', tCol, 'CoreCycLMt', vStrDef).
 1830exactlyAssertedEL_first(isa, 'AtemporalNecessarilyEssentialCollectionType', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1831exactlyAssertedEL_first(isa, 'AsymmetricBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1832exactlyAssertedEL_first(isa, 'AsymmetricBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1833exactlyAssertedEL_first(isa, 'AssociativeRelation', tCol, 'CoreCycLMt', vStrDef).
 1834exactlyAssertedEL_first(isa, 'AssociativeRelation', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1835exactlyAssertedEL_first(isa, 'assertionUtility-1', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1836exactlyAssertedEL_first(isa, 'AssertedTrueMonotonic', 'HLAssertedArgumentKeywordDatastructure', 'UniversalVocabularyMt', vStrDef).
 1837exactlyAssertedEL_first(isa, 'AssertedTrueDefault', 'HLAssertedArgumentKeywordDatastructure', 'UniversalVocabularyMt', vStrDef).
 1838exactlyAssertedEL_first(isa, 'AssertedFalseMonotonic', 'HLAssertedArgumentKeywordDatastructure', 'UniversalVocabularyMt', vStrDef).
 1839exactlyAssertedEL_first(isa, 'AssertedFalseDefault', 'HLAssertedArgumentKeywordDatastructure', 'UniversalVocabularyMt', vStrDef).
 1840exactlyAssertedEL_first(isa, 'ArgTypeTernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1841exactlyAssertedEL_first(isa, 'ArgTypeTernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1842exactlyAssertedEL_first(isa, 'ArgTypePredicate', tCol, 'CoreCycLMt', vStrDef).
 1843exactlyAssertedEL_first(isa, 'ArgTypePredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1844exactlyAssertedEL_first(isa, 'ArgTypeBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1845exactlyAssertedEL_first(isa, 'ArgTypeBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1846exactlyAssertedEL_first(isa, 'ArgSometimesIsaPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1847exactlyAssertedEL_first(isa, 'ArgQuotedIsaTernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1848exactlyAssertedEL_first(isa, 'ArgQuotedIsaTernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1849exactlyAssertedEL_first(isa, 'ArgQuotedIsaPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1850exactlyAssertedEL_first(isa, 'ArgQuotedIsaBinaryPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1851exactlyAssertedEL_first(isa, 'ArgIsaTernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1852exactlyAssertedEL_first(isa, 'ArgIsaTernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1853exactlyAssertedEL_first(isa, 'ArgIsaPredicate', tCol, 'UniversalVocabularyMt', vStrDef).
 1854exactlyAssertedEL_first(isa, 'ArgIsaBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1855exactlyAssertedEL_first(isa, 'ArgIsaBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1856exactlyAssertedEL_first(isa, 'ArgGenlTernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1857exactlyAssertedEL_first(isa, 'ArgGenlTernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1858exactlyAssertedEL_first(isa, 'ArgGenlQuantityTernaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1859exactlyAssertedEL_first(isa, 'ArgGenlQuantityTernaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1860exactlyAssertedEL_first(isa, 'ArgGenlQuantityBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1861exactlyAssertedEL_first(isa, 'ArgGenlQuantityBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1862exactlyAssertedEL_first(isa, 'ArgGenlBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1863exactlyAssertedEL_first(isa, 'ArgGenlBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1864exactlyAssertedEL_first(isa, 'ArgConstraintPredicate', tCol, 'CoreCycLMt', vStrDef).
 1865exactlyAssertedEL_first(isa, 'ArgConstraintPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1866exactlyAssertedEL_first(isa, 'April', 'MonthOfYearType', 'UniversalVocabularyMt', vStrDef).
 1867exactlyAssertedEL_first(isa, 'April', tCol, 'CoreCycLMt', vStrDef).
 1868exactlyAssertedEL_first(isa, 'AntiTransitiveBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1869exactlyAssertedEL_first(isa, 'AntiTransitiveBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1870exactlyAssertedEL_first(isa, 'AntiSymmetricBinaryPredicate', tCol, 'CoreCycLMt', vStrDef).
 1871exactlyAssertedEL_first(isa, 'AntiSymmetricBinaryPredicate', 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 1872exactlyAssertedEL_first(isa, 'AllowKeywordVariables', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1873exactlyAssertedEL_first(isa, 'AllowGenericArgVariables', 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 1874exactlyAssertedEL_first(isa, 'AbsoluteValueFn', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 1875exactlyAssertedEL_first(isa, 'AbsoluteValueFn', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 1876exactlyAssertedEL_first(genls, 'WFFSupportedPredicate', 'WFFSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 1877exactlyAssertedEL_first(genls, 'WFFDirectivePredicate', 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1878exactlyAssertedEL_first(genls, 'WFFConstraintSatisfactionPredicate', 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1879exactlyAssertedEL_first(genls, 'WFFConstraintPredicate', 'WFFSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1880exactlyAssertedEL_first(genls, 'Wednesday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1881exactlyAssertedEL_first(genls, 'VariableAritySkolemFunction', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1882exactlyAssertedEL_first(genls, 'VariableAritySkolemFunction', 'VariableArityRelation', 'LogicalTruthImplementationMt', vStrDef).
 1883exactlyAssertedEL_first(genls, 'VariableAritySkolemFunction', 'SkolemFunction', 'UniversalVocabularyMt', vStrDef).
 1884exactlyAssertedEL_first(genls, 'VariableAritySkolemFunction', 'SkolemFunction', 'LogicalTruthImplementationMt', vStrDef).
 1885exactlyAssertedEL_first(genls, 'VariableAritySkolemFuncN', 'VariableAritySkolemFunction', 'UniversalVocabularyMt', vStrDef).
 1886exactlyAssertedEL_first(genls, 'VariableAritySkolemFuncN', 'VariableAritySkolemFunction', 'CoreCycLImplementationMt', vStrDef).
 1887exactlyAssertedEL_first(genls, 'VariableAritySkolemFuncN', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1888exactlyAssertedEL_first(genls, 'VariableAritySkolemFuncN', 'SkolemFuncN', 'UniversalVocabularyMt', vStrDef).
 1889exactlyAssertedEL_first(genls, 'VariableAritySkolemFuncN', 'SkolemFuncN', 'CoreCycLImplementationMt', vStrDef).
 1890exactlyAssertedEL_first(genls, 'VariableArityRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 1891exactlyAssertedEL_first(genls, 'VariableArityRelation', tRelation, 'LogicalTruthMt', vStrDef).
 1892exactlyAssertedEL_first(genls, 'UnreifiableFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 1893exactlyAssertedEL_first(genls, 'UnreifiableFunction', tFunction, 'LogicalTruthImplementationMt', vStrDef).
 1894exactlyAssertedEL_first(genls, 'UnitOfMeasure', 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 1895exactlyAssertedEL_first(genls, 'UnitOfMeasure', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1896exactlyAssertedEL_first(genls, 'UnaryRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 1897exactlyAssertedEL_first(genls, 'UnaryRelation', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 1898exactlyAssertedEL_first(genls, 'UnaryPredicate', 'UnaryRelation', 'UniversalVocabularyMt', vStrDef).
 1899exactlyAssertedEL_first(genls, 'UnaryPredicate', 'UnaryRelation', 'CoreCycLMt', vStrDef).
 1900exactlyAssertedEL_first(genls, 'UnaryPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 1901exactlyAssertedEL_first(genls, 'UnaryPredicate', tPred, 'CoreCycLMt', vStrDef).
 1902exactlyAssertedEL_first(genls, 'UnaryFunction', 'UnaryRelation', 'UniversalVocabularyMt', vStrDef).
 1903exactlyAssertedEL_first(genls, 'UnaryFunction', 'UnaryRelation', 'CoreCycLMt', vStrDef).
 1904exactlyAssertedEL_first(genls, 'UnaryFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 1905exactlyAssertedEL_first(genls, 'UnaryFunction', tFunction, 'CoreCycLMt', vStrDef).
 1906exactlyAssertedEL_first(genls, 'Tuesday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1907exactlyAssertedEL_first(genls, 'TruthValue', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1908exactlyAssertedEL_first(genls, 'TruthFunction', tRelation, 'UniversalVocabularyMt', vStrDef).
 1909exactlyAssertedEL_first(genls, 'TruthFunction', tRelation, 'LogicalTruthMt', vStrDef).
 1910exactlyAssertedEL_first(genls, 'TransitiveBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1911exactlyAssertedEL_first(genls, 'TransitiveBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 1912exactlyAssertedEL_first(genls, 'TransformationModuleSupportedPredicate', 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1913exactlyAssertedEL_first(genls, 'TransformationModuleSupportedPredicate', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1914exactlyAssertedEL_first(genls, 'TransformationModuleSupportedCollection', 'InferenceSupportedCollection', 'UniversalVocabularyMt', vStrDef).
 1915exactlyAssertedEL_first(genls, 'Thursday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1916exactlyAssertedEL_first(genls, 'TheTerm', 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 1917exactlyAssertedEL_first(genls, 'TernaryRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 1918exactlyAssertedEL_first(genls, 'TernaryRelation', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 1919exactlyAssertedEL_first(genls, 'TernaryPredicate', 'TernaryRelation', 'UniversalVocabularyMt', vStrDef).
 1920exactlyAssertedEL_first(genls, 'TernaryPredicate', 'TernaryRelation', 'CoreCycLMt', vStrDef).
 1921exactlyAssertedEL_first(genls, 'TernaryPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 1922exactlyAssertedEL_first(genls, 'TernaryPredicate', tPred, 'CoreCycLMt', vStrDef).
 1923exactlyAssertedEL_first(genls, 'TernaryFunction', 'TernaryRelation', 'UniversalVocabularyMt', vStrDef).
 1924exactlyAssertedEL_first(genls, 'TernaryFunction', 'TernaryRelation', 'CoreCycLMt', vStrDef).
 1925exactlyAssertedEL_first(genls, 'TernaryFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 1926exactlyAssertedEL_first(genls, 'TernaryFunction', tFunction, 'CoreCycLMt', vStrDef).
 1927exactlyAssertedEL_first(genls, 'SymmetricBinaryPredicate', 'CommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 1928exactlyAssertedEL_first(genls, 'SymmetricBinaryPredicate', 'CommutativeRelation', 'CoreCycLMt', vStrDef).
 1929exactlyAssertedEL_first(genls, 'SymmetricBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 1930exactlyAssertedEL_first(genls, 'SymmetricBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 1931exactlyAssertedEL_first(genls, 'Sunday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1932exactlyAssertedEL_first(genls, 'SubLSymbol', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1933exactlyAssertedEL_first(genls, 'SubLSymbol', 'SubLAtom', 'UniversalVocabularyMt', vStrDef).
 1934exactlyAssertedEL_first(genls, 'SubLSymbol', 'SubLAtom', 'CoreCycLImplementationMt', vStrDef).
 1935exactlyAssertedEL_first(genls, 'SubLSymbol', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 1936exactlyAssertedEL_first(genls, 'SubLSymbol', 'CycLExpression', 'LogicalTruthImplementationMt', vStrDef).
 1937exactlyAssertedEL_first(genls, 'SubLString', 'SubLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 1938exactlyAssertedEL_first(genls, 'SubLString', 'SubLAtomicTerm', 'CoreCycLImplementationMt', vStrDef).
 1939exactlyAssertedEL_first(genls, 'SubLString', 'SubLAtom', 'UniversalVocabularyMt', vStrDef).
 1940exactlyAssertedEL_first(genls, 'SubLString', 'SubLAtom', 'CoreCycLImplementationMt', vStrDef).
 1941exactlyAssertedEL_first(genls, 'SubLRealNumber', 'SubLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 1942exactlyAssertedEL_first(genls, 'SubLRealNumber', 'SubLAtomicTerm', 'CoreCycLImplementationMt', vStrDef).
 1943exactlyAssertedEL_first(genls, 'SubLRealNumber', 'SubLAtom', 'UniversalVocabularyMt', vStrDef).
 1944exactlyAssertedEL_first(genls, 'SubLPositiveInteger', 'SubLNonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 1945exactlyAssertedEL_first(genls, 'SubLPositiveInteger', 'SubLNonNegativeInteger', 'LogicalTruthImplementationMt', vStrDef).
 1946exactlyAssertedEL_first(genls, 'SubLPositiveInteger', 'SubLInteger', 'UniversalVocabularyMt', vStrDef).
 1947exactlyAssertedEL_first(genls, 'SubLPositiveInteger', 'SubLInteger', 'CoreCycLImplementationMt', vStrDef).
 1948exactlyAssertedEL_first(genls, 'SubLNonVariableSymbol', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1949exactlyAssertedEL_first(genls, 'SubLNonVariableSymbol', 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 1950exactlyAssertedEL_first(genls, 'SubLNonVariableSymbol', 'SubLSymbol', 'CoreCycLImplementationMt', vStrDef).
 1951exactlyAssertedEL_first(genls, 'SubLNonVariableSymbol', 'SubLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 1952exactlyAssertedEL_first(genls, 'SubLNonVariableSymbol', 'SubLAtomicTerm', 'CoreCycLImplementationMt', vStrDef).
 1953exactlyAssertedEL_first(genls, 'SubLNonVariableNonKeywordSymbol', 'SubLNonVariableSymbol', 'UniversalVocabularyMt', vStrDef).
 1954exactlyAssertedEL_first(genls, 'SubLNonNegativeInteger', 'SubLInteger', 'UniversalVocabularyMt', vStrDef).
 1955exactlyAssertedEL_first(genls, 'SubLNonNegativeInteger', 'SubLInteger', 'CoreCycLImplementationMt', vStrDef).
 1956exactlyAssertedEL_first(genls, 'SubLNonNegativeInteger', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 1957exactlyAssertedEL_first(genls, 'SubLNonNegativeInteger', 'CycLExpression', 'LogicalTruthImplementationMt', vStrDef).
 1958exactlyAssertedEL_first(genls, 'SubLList', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1959exactlyAssertedEL_first(genls, 'SubLKeyword', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1960exactlyAssertedEL_first(genls, 'SubLKeyword', 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 1961exactlyAssertedEL_first(genls, 'SubLKeyword', 'SubLNonVariableSymbol', 'UniversalVocabularyMt', vStrDef).
 1962exactlyAssertedEL_first(genls, 'SubLInteger', 'SubLRealNumber', 'UniversalVocabularyMt', vStrDef).
 1963exactlyAssertedEL_first(genls, 'SubLInteger', 'SubLRealNumber', 'CoreCycLImplementationMt', vStrDef).
 1964exactlyAssertedEL_first(genls, 'SubLExpressionType', tCol, 'UniversalVocabularyMt', vStrDef).
 1965exactlyAssertedEL_first(genls, 'SubLCharacter', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1966exactlyAssertedEL_first(genls, 'SubLCharacter', 'SubLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 1967exactlyAssertedEL_first(genls, 'SubLCharacter', 'SubLAtomicTerm', 'CoreCycLImplementationMt', vStrDef).
 1968exactlyAssertedEL_first(genls, 'SubLAtomicTerm', 'CycLClosedAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 1969exactlyAssertedEL_first(genls, 'SubLAtomicTerm', 'CycLClosedAtomicTerm', 'CoreCycLImplementationMt', vStrDef).
 1970exactlyAssertedEL_first(genls, 'SubLAtom', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1971exactlyAssertedEL_first(genls, 'SkolemFunction', 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 1972exactlyAssertedEL_first(genls, 'SkolemFunction', 'ReifiableFunction', 'LogicalTruthImplementationMt', vStrDef).
 1973exactlyAssertedEL_first(genls, 'SkolemFunction', 'IndeterminateTermDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 1974exactlyAssertedEL_first(genls, 'SkolemFuncN', 'SkolemFunction', 'UniversalVocabularyMt', vStrDef).
 1975exactlyAssertedEL_first(genls, 'SkolemFuncN', 'SkolemFunction', 'CoreCycLImplementationMt', vStrDef).
 1976exactlyAssertedEL_first(genls, 'SiblingDisjointCollectionType', tCol, 'UniversalVocabularyMt', vStrDef).
 1977exactlyAssertedEL_first(genls, 'SiblingDisjointAttributeType', tCol, 'UniversalVocabularyMt', vStrDef).
 1978exactlyAssertedEL_first(genls, 'SetOrCollection', 'Thing', 'UniversalVocabularyMt', vStrDef).
 1979exactlyAssertedEL_first(genls, 'SetOrCollection', 'Thing', 'CoreCycLMt', vStrDef).
 1980exactlyAssertedEL_first(genls, 'Set-Mathematical', 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 1981exactlyAssertedEL_first(genls, 'Set-Mathematical', 'SetOrCollection', 'CoreCycLMt', vStrDef).
 1982exactlyAssertedEL_first(genls, 'September', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1983exactlyAssertedEL_first(genls, 'SententialRelation', 'TruthFunction', 'UniversalVocabularyMt', vStrDef).
 1984exactlyAssertedEL_first(genls, 'SententialRelation', 'TruthFunction', 'LogicalTruthMt', vStrDef).
 1985exactlyAssertedEL_first(genls, 'ScopingRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 1986exactlyAssertedEL_first(genls, 'ScopingRelation', tRelation, 'CoreCycLMt', vStrDef).
 1987exactlyAssertedEL_first(genls, 'ScalarPointValue', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 1988exactlyAssertedEL_first(genls, 'ScalarPointValue', 'ScalarInterval', 'CoreCycLMt', vStrDef).
 1989exactlyAssertedEL_first(genls, 'ScalarInterval', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1990exactlyAssertedEL_first(genls, 'ScalarIntegralValue', 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 1991exactlyAssertedEL_first(genls, 'Saturday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1992exactlyAssertedEL_first(genls, 'RuleTemplate', 'Individual', 'UniversalVocabularyMt', vStrDef).
 1993exactlyAssertedEL_first(genls, 'RemovalModuleSupportedPredicate-Specific', 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1994exactlyAssertedEL_first(genls, 'RemovalModuleSupportedPredicate-Specific', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1995exactlyAssertedEL_first(genls, 'RemovalModuleSupportedPredicate-Generic', 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 1996exactlyAssertedEL_first(genls, 'RemovalModuleSupportedPredicate-Generic', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 1997exactlyAssertedEL_first(genls, 'RemovalModuleSupportedCollection-Generic', 'InferenceSupportedCollection', 'UniversalVocabularyMt', vStrDef).
 1998exactlyAssertedEL_first(genls, tRelation, 'Individual', 'UniversalVocabularyMt', vStrDef).
 1999exactlyAssertedEL_first(genls, 'ReifiableFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2000exactlyAssertedEL_first(genls, 'ReifiableFunction', tFunction, 'LogicalTruthImplementationMt', vStrDef).
 2001exactlyAssertedEL_first(genls, 'ReformulatorIrrelevantFORT', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2002exactlyAssertedEL_first(genls, 'ReformulatorHighlyRelevantFORT', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2003exactlyAssertedEL_first(genls, 'ReformulatorDirectivePredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2004exactlyAssertedEL_first(genls, 'ReflexiveBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2005exactlyAssertedEL_first(genls, 'ReflexiveBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 2006exactlyAssertedEL_first(genls, 'RealNumber', 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 2007exactlyAssertedEL_first(genls, 'RealNumber', 'ScalarPointValue', 'CoreCycLMt', vStrDef).
 2008exactlyAssertedEL_first(genls, 'QuintaryRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 2009exactlyAssertedEL_first(genls, 'QuintaryRelation', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 2010exactlyAssertedEL_first(genls, 'QuintaryPredicate', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 2011exactlyAssertedEL_first(genls, 'QuintaryPredicate', 'QuintaryRelation', 'CoreCycLMt', vStrDef).
 2012exactlyAssertedEL_first(genls, 'QuintaryPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2013exactlyAssertedEL_first(genls, 'QuintaryPredicate', tPred, 'CoreCycLMt', vStrDef).
 2014exactlyAssertedEL_first(genls, 'QuintaryFunction', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 2015exactlyAssertedEL_first(genls, 'QuintaryFunction', 'QuintaryRelation', 'CoreCycLMt', vStrDef).
 2016exactlyAssertedEL_first(genls, 'QuintaryFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2017exactlyAssertedEL_first(genls, 'QuintaryFunction', tFunction, 'CoreCycLMt', vStrDef).
 2018exactlyAssertedEL_first(genls, 'QuaternaryRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 2019exactlyAssertedEL_first(genls, 'QuaternaryRelation', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 2020exactlyAssertedEL_first(genls, 'QuaternaryPredicate', 'QuaternaryRelation', 'UniversalVocabularyMt', vStrDef).
 2021exactlyAssertedEL_first(genls, 'QuaternaryPredicate', 'QuaternaryRelation', 'CoreCycLMt', vStrDef).
 2022exactlyAssertedEL_first(genls, 'QuaternaryPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2023exactlyAssertedEL_first(genls, 'QuaternaryPredicate', tPred, 'CoreCycLMt', vStrDef).
 2024exactlyAssertedEL_first(genls, 'QuaternaryFunction', 'QuaternaryRelation', 'UniversalVocabularyMt', vStrDef).
 2025exactlyAssertedEL_first(genls, 'QuaternaryFunction', 'QuaternaryRelation', 'CoreCycLMt', vStrDef).
 2026exactlyAssertedEL_first(genls, 'QuaternaryFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2027exactlyAssertedEL_first(genls, 'QuaternaryFunction', tFunction, 'CoreCycLMt', vStrDef).
 2028exactlyAssertedEL_first(genls, 'Quantifier', 'SententialRelation', 'UniversalVocabularyMt', vStrDef).
 2029exactlyAssertedEL_first(genls, 'Quantifier', 'SententialRelation', 'LogicalTruthMt', vStrDef).
 2030exactlyAssertedEL_first(genls, 'Quantifier', 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 2031exactlyAssertedEL_first(genls, 'Quantifier', 'ScopingRelation', 'CoreCycLMt', vStrDef).
 2032exactlyAssertedEL_first(genls, 'ProblemSolvingCntxt', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2033exactlyAssertedEL_first(genls, 'ProblemSolvingCntxt', 'Microtheory', 'CoreCycLMt', vStrDef).
 2034exactlyAssertedEL_first(genls, 'PredicateTypeByArity', tCol, 'UniversalVocabularyMt', vStrDef).
 2035exactlyAssertedEL_first(genls, tPred, 'TruthFunction', 'UniversalVocabularyMt', vStrDef).
 2036exactlyAssertedEL_first(genls, tPred, 'TruthFunction', 'LogicalTruthMt', vStrDef).
 2037exactlyAssertedEL_first(genls, 'PositiveInteger', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 2038exactlyAssertedEL_first(genls, 'PositiveInteger', 'NonNegativeInteger', 'LogicalTruthMt', vStrDef).
 2039exactlyAssertedEL_first(genls, 'PositiveInteger', 'Integer', 'CoreCycLMt', vStrDef).
 2040exactlyAssertedEL_first(genls, 'PartiallyCommutativeRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2041exactlyAssertedEL_first(genls, 'PartiallyCommutativeRelation', tRelation, 'CoreCycLMt', vStrDef).
 2042exactlyAssertedEL_first(genls, 'Open-InferenceProblemLinkStatus', 'CycInferenceProblemLinkStatus', 'UniversalVocabularyMt', vStrDef).
 2043exactlyAssertedEL_first(genls, 'October', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2044exactlyAssertedEL_first(genls, 'November', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2045exactlyAssertedEL_first(genls, 'NonNegativeScalarInterval', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2046exactlyAssertedEL_first(genls, 'NonNegativeScalarInterval', 'ScalarInterval', 'CoreCycLMt', vStrDef).
 2047exactlyAssertedEL_first(genls, 'NonNegativeInteger', 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2048exactlyAssertedEL_first(genls, 'NonNegativeInteger', 'Integer', 'UniversalVocabularyMt', vStrDef).
 2049exactlyAssertedEL_first(genls, 'NonNegativeInteger', 'Integer', 'CoreCycLMt', vStrDef).
 2050exactlyAssertedEL_first(genls, 'NoGood-ProblemProvabilityStatus', 'CycProvabilityStatus', 'UniversalVocabularyMt', vStrDef).
 2051exactlyAssertedEL_first(genls, 'Neutral-ProblemProvabilityStatus', 'CycProvabilityStatus', 'UniversalVocabularyMt', vStrDef).
 2052exactlyAssertedEL_first(genls, 'Multigraph', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2053exactlyAssertedEL_first(genls, 'MonthOfYearType', tCol, 'UniversalVocabularyMt', vStrDef).
 2054exactlyAssertedEL_first(genls, 'Monday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2055exactlyAssertedEL_first(genls, 'MicrotheoryDesignatingRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2056exactlyAssertedEL_first(genls, 'MicrotheoryDesignatingRelation', tRelation, 'CoreCycLMt', vStrDef).
 2057exactlyAssertedEL_first(genls, 'Microtheory', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2058exactlyAssertedEL_first(genls, 'May', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2059exactlyAssertedEL_first(genls, 'March', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2060exactlyAssertedEL_first(genls, 'LogicalConnective', 'SententialRelation', 'UniversalVocabularyMt', vStrDef).
 2061exactlyAssertedEL_first(genls, 'LogicalConnective', 'SententialRelation', 'LogicalTruthMt', vStrDef).
 2062exactlyAssertedEL_first(genls, 'List', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2063exactlyAssertedEL_first(genls, 'larkc-VariableBinding', 'larkc-InformationSet', 'BaseKB', vStrDef).
 2064exactlyAssertedEL_first(genls, 'larkc-TriplePatternQuery', 'larkc-Query', 'BaseKB', vStrDef).
 2065exactlyAssertedEL_first(genls, 'larkc-SPARQLQuery', 'larkc-Query', 'BaseKB', vStrDef).
 2066exactlyAssertedEL_first(genls, 'larkc-SetOfStatements', 'larkc-InformationSet', 'BaseKB', vStrDef).
 2067exactlyAssertedEL_first(genls, 'larkc-Selecter', 'larkc-Plugin', 'BaseKB', vStrDef).
 2068exactlyAssertedEL_first(genls, 'larkc-Scalability', 'wsl-NonFunctionalParameter', 'BaseKB', vStrDef).
 2069exactlyAssertedEL_first(genls, 'larkc-Reasoner', 'larkc-Plugin', 'BaseKB', vStrDef).
 2070exactlyAssertedEL_first(genls, 'larkc-RdfGraph', 'larkc-SetOfStatements', 'BaseKB', vStrDef).
 2071exactlyAssertedEL_first(genls, 'larkc-QueryTransformer', 'larkc-Plugin', 'BaseKB', vStrDef).
 2072exactlyAssertedEL_first(genls, 'larkc-Query', 'larkc-Resource', 'BaseKB', vStrDef).
 2073exactlyAssertedEL_first(genls, 'larkc-NaturalLanguageDocument', 'larkc-InformationSet', 'BaseKB', vStrDef).
 2074exactlyAssertedEL_first(genls, 'larkc-LabelledGroupOfStatements', 'larkc-SetOfStatements', 'BaseKB', vStrDef).
 2075exactlyAssertedEL_first(genls, 'larkc-KeywordQuery', 'larkc-Query', 'BaseKB', vStrDef).
 2076exactlyAssertedEL_first(genls, 'larkc-InformationSetTransformer', 'larkc-Plugin', 'BaseKB', vStrDef).
 2077exactlyAssertedEL_first(genls, 'larkc-InformationSet', 'larkc-Resource', 'BaseKB', vStrDef).
 2078exactlyAssertedEL_first(genls, 'larkc-Identifier', 'larkc-Plugin', 'BaseKB', vStrDef).
 2079exactlyAssertedEL_first(genls, 'larkc-GateTransformer', 'larkc-InformationSetTransformer', 'BaseKB', vStrDef).
 2080exactlyAssertedEL_first(genls, 'larkc-Decider', 'larkc-Plugin', 'BaseKB', vStrDef).
 2081exactlyAssertedEL_first(genls, 'larkc-DataSet', 'larkc-SetOfStatements', 'BaseKB', vStrDef).
 2082exactlyAssertedEL_first(genls, 'larkc-CycSelecter', 'larkc-Selecter', 'BaseKB', vStrDef).
 2083exactlyAssertedEL_first(genls, 'larkc-CycReasoner', 'larkc-Reasoner', 'BaseKB', vStrDef).
 2084exactlyAssertedEL_first(genls, 'larkc-CycGateDecider', 'larkc-Decider', 'BaseKB', vStrDef).
 2085exactlyAssertedEL_first(genls, 'larkc-Cost', 'wsl-NonFunctionalParameter', 'BaseKB', vStrDef).
 2086exactlyAssertedEL_first(genls, 'larkc-BooleanInformationSet', 'larkc-InformationSet', 'BaseKB', vStrDef).
 2087exactlyAssertedEL_first(genls, 'larkc-ArticleIdentifier', 'larkc-Identifier', 'BaseKB', vStrDef).
 2088exactlyAssertedEL_first(genls, 'KnowledgeBase', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2089exactlyAssertedEL_first(genls, 'June', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2090exactlyAssertedEL_first(genls, 'July', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2091exactlyAssertedEL_first(genls, 'January', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2092exactlyAssertedEL_first(genls, 'IrreflexiveBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2093exactlyAssertedEL_first(genls, 'IrreflexiveBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 2094exactlyAssertedEL_first(genls, 'InterArgIsaPredicate', 'ArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 2095exactlyAssertedEL_first(genls, 'InterArgFormatPredicate', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2096exactlyAssertedEL_first(genls, 'InterArgFormatPredicate', 'TernaryPredicate', 'CoreCycLMt', vStrDef).
 2097exactlyAssertedEL_first(genls, 'InterArgFormatPredicate', 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 2098exactlyAssertedEL_first(genls, 'Integer', 'ScalarIntegralValue', 'UniversalVocabularyMt', vStrDef).
 2099exactlyAssertedEL_first(genls, 'Integer', 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 2100exactlyAssertedEL_first(genls, 'InferenceSupportedTerm', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2101exactlyAssertedEL_first(genls, 'InferenceSupportedPredicate', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 2102exactlyAssertedEL_first(genls, 'InferenceSupportedFunction', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2103exactlyAssertedEL_first(genls, 'InferenceSupportedCollection', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 2104exactlyAssertedEL_first(genls, 'InferenceRelatedBookkeepingPredicate', 'BookkeepingPredicate', 'UniversalVocabularyMt', vStrDef).
 2105exactlyAssertedEL_first(genls, 'Individual', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2106exactlyAssertedEL_first(genls, 'Individual', 'Thing', 'LogicalTruthMt', vStrDef).
 2107exactlyAssertedEL_first(genls, 'IndeterminateTermDenotingFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2108exactlyAssertedEL_first(genls, 'IndeterminateTerm', 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2109exactlyAssertedEL_first(genls, 'HypotheticalContext', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2110exactlyAssertedEL_first(genls, 'HypotheticalContext', 'Microtheory', 'CoreCycLMt', vStrDef).
 2111exactlyAssertedEL_first(genls, 'HumanCyclist', 'Cyclist', 'UniversalVocabularyMt', vStrDef).
 2112exactlyAssertedEL_first(genls, 'HumanCyclist', 'Cyclist', 'CoreCycLMt', vStrDef).
 2113exactlyAssertedEL_first(genls, 'HLPrototypicalTerm', 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 2114exactlyAssertedEL_first(genls, 'HLExternalIDString', 'SubLAtom', 'UniversalVocabularyMt', vStrDef).
 2115exactlyAssertedEL_first(genls, 'HLAssertedArgumentKeywordDatastructure', 'CycArgumentDatastructure', 'UniversalVocabularyMt', vStrDef).
 2116exactlyAssertedEL_first(genls, 'Good-ProblemProvabilityStatus', 'CycProvabilityStatus', 'UniversalVocabularyMt', vStrDef).
 2117exactlyAssertedEL_first(genls, tFunction, tRelation, 'UniversalVocabularyMt', vStrDef).
 2118exactlyAssertedEL_first(genls, tFunction, tRelation, 'LogicalTruthMt', vStrDef).
 2119exactlyAssertedEL_first(genls, 'Friday', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2120exactlyAssertedEL_first(genls, 'Forward-AssertionDirection', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2121exactlyAssertedEL_first(genls, 'Format', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2122exactlyAssertedEL_first(genls, 'FixedAritySkolemFunction', 'SkolemFunction', 'UniversalVocabularyMt', vStrDef).
 2123exactlyAssertedEL_first(genls, 'FixedAritySkolemFunction', 'SkolemFunction', 'LogicalTruthImplementationMt', vStrDef).
 2124exactlyAssertedEL_first(genls, 'FixedAritySkolemFunction', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 2125exactlyAssertedEL_first(genls, 'FixedAritySkolemFunction', 'FixedArityRelation', 'LogicalTruthImplementationMt', vStrDef).
 2126exactlyAssertedEL_first(genls, 'FixedAritySkolemFuncN', 'SkolemFuncN', 'UniversalVocabularyMt', vStrDef).
 2127exactlyAssertedEL_first(genls, 'FixedAritySkolemFuncN', 'SkolemFuncN', 'CoreCycLImplementationMt', vStrDef).
 2128exactlyAssertedEL_first(genls, 'FixedAritySkolemFuncN', 'FixedAritySkolemFunction', 'UniversalVocabularyMt', vStrDef).
 2129exactlyAssertedEL_first(genls, 'FixedAritySkolemFuncN', 'FixedAritySkolemFunction', 'CoreCycLImplementationMt', vStrDef).
 2130exactlyAssertedEL_first(genls, 'FixedArityRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2131exactlyAssertedEL_first(genls, 'FixedArityRelation', tRelation, 'LogicalTruthMt', vStrDef).
 2132exactlyAssertedEL_first(genls, 'February', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2133exactlyAssertedEL_first(genls, 'ExistentialQuantifier-Bounded', 'TernaryRelation', 'UniversalVocabularyMt', vStrDef).
 2134exactlyAssertedEL_first(genls, 'ExistentialQuantifier-Bounded', 'ExistentialQuantifier', 'UniversalVocabularyMt', vStrDef).
 2135exactlyAssertedEL_first(genls, 'ExistentialQuantifier', 'Quantifier', 'UniversalVocabularyMt', vStrDef).
 2136exactlyAssertedEL_first(genls, 'ExistentialQuantifier', 'Quantifier', 'CoreCycLMt', vStrDef).
 2137exactlyAssertedEL_first(genls, 'ExceptionPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2138exactlyAssertedEL_first(genls, 'EvaluatableRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2139exactlyAssertedEL_first(genls, 'EvaluatableRelation', tRelation, 'CoreCycLMt', vStrDef).
 2140exactlyAssertedEL_first(genls, 'EvaluatablePredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2141exactlyAssertedEL_first(genls, 'EvaluatablePredicate', 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 2142exactlyAssertedEL_first(genls, 'EvaluatableFunction', 'UnreifiableFunction', 'UniversalVocabularyMt', vStrDef).
 2143exactlyAssertedEL_first(genls, 'EvaluatableFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2144exactlyAssertedEL_first(genls, 'EvaluatableFunction', tFunction, 'CoreCycLMt', vStrDef).
 2145exactlyAssertedEL_first(genls, 'EvaluatableFunction', 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 2146exactlyAssertedEL_first(genls, 'EvaluatableFunction', 'EvaluatableRelation', 'CoreCycLMt', vStrDef).
 2147exactlyAssertedEL_first(genls, 'ELRelation-Reversible', 'ELRelation', 'UniversalVocabularyMt', vStrDef).
 2148exactlyAssertedEL_first(genls, 'ELRelation-OneWay', 'ELRelation', 'UniversalVocabularyMt', vStrDef).
 2149exactlyAssertedEL_first(genls, 'ELRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2150exactlyAssertedEL_first(genls, 'DocumentationPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2151exactlyAssertedEL_first(genls, 'DocumentationConstant', 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 2152exactlyAssertedEL_first(genls, 'DocumentationConstant', 'CycLConstant', 'CoreCycLMt', vStrDef).
 2153exactlyAssertedEL_first(genls, 'DistributingMetaKnowledgePredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2154exactlyAssertedEL_first(genls, 'DisjointCollectionType', 'SiblingDisjointCollectionType', 'UniversalVocabularyMt', vStrDef).
 2155exactlyAssertedEL_first(genls, 'DirectedMultigraph', 'Multigraph', 'UniversalVocabularyMt', vStrDef).
 2156exactlyAssertedEL_first(genls, 'DirectedMultigraph', 'Multigraph', 'CoreCycLMt', vStrDef).
 2157exactlyAssertedEL_first(genls, 'DefaultMonotonicPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2158exactlyAssertedEL_first(genls, 'December', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2159exactlyAssertedEL_first(genls, 'DayOfWeekType', tCol, 'UniversalVocabularyMt', vStrDef).
 2160exactlyAssertedEL_first(genls, 'CycTransformationProof', 'CycProof', 'UniversalVocabularyMt', vStrDef).
 2161exactlyAssertedEL_first(genls, 'CycTactic', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2162exactlyAssertedEL_first(genls, 'CycSupportDatastructure', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2163exactlyAssertedEL_first(genls, 'CycProvabilityStatus', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2164exactlyAssertedEL_first(genls, 'CycProof', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2165exactlyAssertedEL_first(genls, 'CycProblemStore', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2166exactlyAssertedEL_first(genls, 'CycProblemLink-Union', 'CycProblemLink-Disjunctive', 'UniversalVocabularyMt', vStrDef).
 2167exactlyAssertedEL_first(genls, 'CycProblemLink-Transformation', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2168exactlyAssertedEL_first(genls, 'CycProblemLink-Structural', 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 2169exactlyAssertedEL_first(genls, 'CycProblemLink-Split', 'CycProblemLink-Conjunctive', 'UniversalVocabularyMt', vStrDef).
 2170exactlyAssertedEL_first(genls, 'CycProblemLink-Restriction', 'CycProblemLink-Structural', 'UniversalVocabularyMt', vStrDef).
 2171exactlyAssertedEL_first(genls, 'CycProblemLink-Removal', 'CycProblemLink-Content', 'UniversalVocabularyMt', vStrDef).
 2172exactlyAssertedEL_first(genls, 'CycProblemLink-Logical', 'CycProblemLink-Structural', 'UniversalVocabularyMt', vStrDef).
 2173exactlyAssertedEL_first(genls, 'CycProblemLink-JoinOrdered', 'CycProblemLink-Conjunctive', 'UniversalVocabularyMt', vStrDef).
 2174exactlyAssertedEL_first(genls, 'CycProblemLink-Join', 'CycProblemLink-Conjunctive', 'UniversalVocabularyMt', vStrDef).
 2175exactlyAssertedEL_first(genls, 'CycProblemLink-Disjunctive', 'CycProblemLink-Logical', 'UniversalVocabularyMt', vStrDef).
 2176exactlyAssertedEL_first(genls, 'CycProblemLink-Content', 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 2177exactlyAssertedEL_first(genls, 'CycProblemLink-Conjunctive', 'CycProblemLink-Logical', 'UniversalVocabularyMt', vStrDef).
 2178exactlyAssertedEL_first(genls, 'CycProblemLink-AnswerLink', 'CycProblemLink-Structural', 'UniversalVocabularyMt', vStrDef).
 2179exactlyAssertedEL_first(genls, 'CycProblemLink', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2180exactlyAssertedEL_first(genls, 'CycProblem', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2181exactlyAssertedEL_first(genls, ftVar, 'CycLRepresentedAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2182exactlyAssertedEL_first(genls, ftVar, 'CycLRepresentedAtomicTerm', 'CoreCycLMt', vStrDef).
 2183exactlyAssertedEL_first(genls, ftVar, 'CycLOpenDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2184exactlyAssertedEL_first(genls, ftVar, 'CycLOpenDenotationalTerm', 'CoreCycLMt', vStrDef).
 2185exactlyAssertedEL_first(genls, ftVar, 'CycLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2186exactlyAssertedEL_first(genls, ftVar, 'CycLAtomicTerm', 'CoreCycLMt', vStrDef).
 2187exactlyAssertedEL_first(genls, 'CycLTruthValueSentence', 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 2188exactlyAssertedEL_first(genls, 'CycLTruthValueSentence', 'CycLClosedSentence', 'UniversalVocabularyMt', vStrDef).
 2189exactlyAssertedEL_first(genls, 'CycLTruthValueSentence', 'CycLClosedSentence', 'CoreCycLMt', vStrDef).
 2190exactlyAssertedEL_first(genls, 'CycLTerm', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2191exactlyAssertedEL_first(genls, 'CycLTerm', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2192exactlyAssertedEL_first(genls, 'CycLSentence-ClosedPredicate', 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 2193exactlyAssertedEL_first(genls, 'CycLSentence-ClosedPredicate', 'CycLSentence', 'CoreCycLMt', vStrDef).
 2194exactlyAssertedEL_first(genls, 'CycLSentence-Assertible', 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 2195exactlyAssertedEL_first(genls, 'CycLSentence-Assertible', 'CycLSentence-Askable', 'CoreCycLMt', vStrDef).
 2196exactlyAssertedEL_first(genls, 'CycLSentence-Assertible', 'CycLExpression-Assertible', 'UniversalVocabularyMt', vStrDef).
 2197exactlyAssertedEL_first(genls, 'CycLSentence-Assertible', 'CycLExpression-Assertible', 'CoreCycLMt', vStrDef).
 2198exactlyAssertedEL_first(genls, 'CycLSentence-Askable', 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 2199exactlyAssertedEL_first(genls, 'CycLSentence-Askable', 'CycLSentence', 'CoreCycLMt', vStrDef).
 2200exactlyAssertedEL_first(genls, 'CycLSentence-Askable', 'CycLExpression-Askable', 'UniversalVocabularyMt', vStrDef).
 2201exactlyAssertedEL_first(genls, 'CycLSentence-Askable', 'CycLExpression-Askable', 'CoreCycLMt', vStrDef).
 2202exactlyAssertedEL_first(genls, 'CycLSentence', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2203exactlyAssertedEL_first(genls, 'CycLSentence', 'CycLTerm', 'CoreCycLMt', vStrDef).
 2204exactlyAssertedEL_first(genls, 'CycLSentence', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2205exactlyAssertedEL_first(genls, 'CycLRuleAssertion', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2206exactlyAssertedEL_first(genls, 'CycLRuleAssertion', 'CycLAssertion', 'CoreCycLMt', vStrDef).
 2207exactlyAssertedEL_first(genls, 'CycLRepresentedTerm', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2208exactlyAssertedEL_first(genls, 'CycLRepresentedTerm', 'CycLDenotationalTerm', 'CoreCycLMt', vStrDef).
 2209exactlyAssertedEL_first(genls, 'CycLRepresentedAtomicTerm', 'CycLRepresentedTerm', 'UniversalVocabularyMt', vStrDef).
 2210exactlyAssertedEL_first(genls, 'CycLRepresentedAtomicTerm', 'CycLRepresentedTerm', 'CoreCycLMt', vStrDef).
 2211exactlyAssertedEL_first(genls, 'CycLRepresentedAtomicTerm', 'CycLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2212exactlyAssertedEL_first(genls, 'CycLRepresentedAtomicTerm', 'CycLAtomicTerm', 'CoreCycLMt', vStrDef).
 2213exactlyAssertedEL_first(genls, 'CycLReifiedDenotationalTerm', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2214exactlyAssertedEL_first(genls, 'CycLReifiedDenotationalTerm', 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2215exactlyAssertedEL_first(genls, 'CycLReifiedDenotationalTerm', 'CycLReifiableDenotationalTerm', 'CoreCycLMt', vStrDef).
 2216exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2217exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2218exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 2219exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLIndexedTerm', 'CoreCycLImplementationMt', vStrDef).
 2220exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2221exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLExpression', 'LogicalTruthImplementationMt', vStrDef).
 2222exactlyAssertedEL_first(genls, 'CycLReifiableNonAtomicTerm', 'CycLClosedNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2223exactlyAssertedEL_first(genls, 'CycLReifiableDenotationalTerm', 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 2224exactlyAssertedEL_first(genls, 'CycLReifiableDenotationalTerm', 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2225exactlyAssertedEL_first(genls, 'CycLReifiableDenotationalTerm', 'CycLClosedDenotationalTerm', 'CoreCycLMt', vStrDef).
 2226exactlyAssertedEL_first(genls, 'CycLReformulationRulePredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2227exactlyAssertedEL_first(genls, 'CycLPropositionalSentence', 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 2228exactlyAssertedEL_first(genls, 'CycLPropositionalSentence', 'CycLSentence-Askable', 'CoreCycLMt', vStrDef).
 2229exactlyAssertedEL_first(genls, 'CycLPropositionalSentence', 'CycLClosedSentence', 'UniversalVocabularyMt', vStrDef).
 2230exactlyAssertedEL_first(genls, 'CycLPropositionalSentence', 'CycLClosedSentence', 'CoreCycLMt', vStrDef).
 2231exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 2232exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLSentence', 'CoreCycLMt', vStrDef).
 2233exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLOpenFormula', 'UniversalVocabularyMt', vStrDef).
 2234exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLOpenFormula', 'CoreCycLMt', vStrDef).
 2235exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLOpenExpression', 'UniversalVocabularyMt', vStrDef).
 2236exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLFormulaicSentence', 'UniversalVocabularyMt', vStrDef).
 2237exactlyAssertedEL_first(genls, 'CycLOpenSentence', 'CycLFormulaicSentence', 'CoreCycLMt', vStrDef).
 2238exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2239exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLOpenFormula', 'UniversalVocabularyMt', vStrDef).
 2240exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLOpenFormula', 'CoreCycLMt', vStrDef).
 2241exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLOpenDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2242exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLOpenDenotationalTerm', 'CoreCycLMt', vStrDef).
 2243exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2244exactlyAssertedEL_first(genls, 'CycLOpenNonAtomicTerm', 'CycLNonAtomicTerm', 'CoreCycLMt', vStrDef).
 2245exactlyAssertedEL_first(genls, 'CycLOpenFormula', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2246exactlyAssertedEL_first(genls, 'CycLOpenFormula', 'CycLOpenExpression', 'UniversalVocabularyMt', vStrDef).
 2247exactlyAssertedEL_first(genls, 'CycLOpenFormula', 'CycLOpenExpression', 'CoreCycLMt', vStrDef).
 2248exactlyAssertedEL_first(genls, 'CycLOpenFormula', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 2249exactlyAssertedEL_first(genls, 'CycLOpenFormula', 'CycLFormula', 'CoreCycLMt', vStrDef).
 2250exactlyAssertedEL_first(genls, 'CycLOpenExpression', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2251exactlyAssertedEL_first(genls, 'CycLOpenExpression', 'CycLTerm', 'CoreCycLMt', vStrDef).
 2252exactlyAssertedEL_first(genls, 'CycLOpenExpression', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2253exactlyAssertedEL_first(genls, 'CycLOpenExpression', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2254exactlyAssertedEL_first(genls, 'CycLOpenDenotationalTerm', 'CycLOpenExpression', 'UniversalVocabularyMt', vStrDef).
 2255exactlyAssertedEL_first(genls, 'CycLOpenDenotationalTerm', 'CycLOpenExpression', 'CoreCycLMt', vStrDef).
 2256exactlyAssertedEL_first(genls, 'CycLOpenDenotationalTerm', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2257exactlyAssertedEL_first(genls, 'CycLOpenDenotationalTerm', 'CycLDenotationalTerm', 'CoreCycLMt', vStrDef).
 2258exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-ClosedFunctor', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2259exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-ClosedFunctor', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2260exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-ClosedFunctor', 'CycLNonAtomicTerm', 'CoreCycLMt', vStrDef).
 2261exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2262exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'CycLNonAtomicTerm-Askable', 'UniversalVocabularyMt', vStrDef).
 2263exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'CycLNonAtomicTerm-Askable', 'CoreCycLMt', vStrDef).
 2264exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'CycLExpression-Assertible', 'UniversalVocabularyMt', vStrDef).
 2265exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'CycLExpression-Assertible', 'CoreCycLMt', vStrDef).
 2266exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Assertible', 'CycLDenotationalTerm-Assertible', 'UniversalVocabularyMt', vStrDef).
 2267exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Askable', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2268exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Askable', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2269exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Askable', 'CycLNonAtomicTerm', 'CoreCycLMt', vStrDef).
 2270exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Askable', 'CycLExpression-Askable', 'UniversalVocabularyMt', vStrDef).
 2271exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm-Askable', 'CycLExpression-Askable', 'CoreCycLMt', vStrDef).
 2272exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLRepresentedTerm', 'UniversalVocabularyMt', vStrDef).
 2273exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLRepresentedTerm', 'CoreCycLMt', vStrDef).
 2274exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 2275exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLFormula', 'CoreCycLMt', vStrDef).
 2276exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2277exactlyAssertedEL_first(genls, 'CycLNonAtomicTerm', 'CycLDenotationalTerm', 'CoreCycLMt', vStrDef).
 2278exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycLReifiedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2279exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycLReifiedDenotationalTerm', 'CoreCycLMt', vStrDef).
 2280exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2281exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycLClosedNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2282exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycLClosedNonAtomicTerm', 'CoreCycLMt', vStrDef).
 2283exactlyAssertedEL_first(genls, 'CycLNonAtomicReifiedTerm', 'CycKBDatastructure', 'UniversalVocabularyMt', vStrDef).
 2284exactlyAssertedEL_first(genls, 'Cyclist', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2285exactlyAssertedEL_first(genls, 'CycLIndexedTerm', 'CycLClosedExpression', 'UniversalVocabularyMt', vStrDef).
 2286exactlyAssertedEL_first(genls, 'CycLGenericRelationFormula', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2287exactlyAssertedEL_first(genls, 'CycLGenericRelationFormula', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 2288exactlyAssertedEL_first(genls, 'CycLGenericRelationFormula', 'CycLFormula', 'CoreCycLMt', vStrDef).
 2289exactlyAssertedEL_first(genls, 'CycLGAFAssertion', 'CycLClosedAtomicSentence', 'UniversalVocabularyMt', vStrDef).
 2290exactlyAssertedEL_first(genls, 'CycLGAFAssertion', 'CycLClosedAtomicSentence', 'CoreCycLMt', vStrDef).
 2291exactlyAssertedEL_first(genls, 'CycLGAFAssertion', 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 2292exactlyAssertedEL_first(genls, 'CycLGAFAssertion', 'CycLAtomicAssertion', 'CoreCycLMt', vStrDef).
 2293exactlyAssertedEL_first(genls, 'CycLGAFAssertion', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2294exactlyAssertedEL_first(genls, 'CycLFormulaicSentence', 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 2295exactlyAssertedEL_first(genls, 'CycLFormulaicSentence', 'CycLSentence', 'CoreCycLMt', vStrDef).
 2296exactlyAssertedEL_first(genls, 'CycLFormulaicSentence', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 2297exactlyAssertedEL_first(genls, 'CycLFormulaicSentence', 'CycLFormula', 'CoreCycLMt', vStrDef).
 2298exactlyAssertedEL_first(genls, 'CycLFormula', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2299exactlyAssertedEL_first(genls, 'CycLFormula', 'CycLTerm', 'CoreCycLMt', vStrDef).
 2300exactlyAssertedEL_first(genls, 'CycLFormula', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2301exactlyAssertedEL_first(genls, 'CycLFormula', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2302exactlyAssertedEL_first(genls, ttExpressionType, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 2303exactlyAssertedEL_first(genls, 'CycLExpression-Assertible', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2304exactlyAssertedEL_first(genls, 'CycLExpression-Assertible', 'CycLExpression-Askable', 'UniversalVocabularyMt', vStrDef).
 2305exactlyAssertedEL_first(genls, 'CycLExpression-Assertible', 'CycLExpression-Askable', 'CoreCycLMt', vStrDef).
 2306exactlyAssertedEL_first(genls, 'CycLExpression-Askable', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2307exactlyAssertedEL_first(genls, 'CycLExpression-Askable', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2308exactlyAssertedEL_first(genls, 'CycLExpression-Askable', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2309exactlyAssertedEL_first(genls, 'CycLExpression', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2310exactlyAssertedEL_first(genls, 'CycLExpression', 'Thing', 'LogicalTruthMt', vStrDef).
 2311exactlyAssertedEL_first(genls, 'CycLExpression', 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 2312exactlyAssertedEL_first(genls, 'CycLExpression', 'SubLSExpression', 'CoreCycLMt', vStrDef).
 2313exactlyAssertedEL_first(genls, 'CycLDenotationalTerm-Assertible', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2314exactlyAssertedEL_first(genls, 'CycLDenotationalTerm', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2315exactlyAssertedEL_first(genls, 'CycLDenotationalTerm', 'CycLTerm', 'CoreCycLMt', vStrDef).
 2316exactlyAssertedEL_first(genls, 'CycLDenotationalTerm', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2317exactlyAssertedEL_first(genls, 'CycLDenotationalTerm', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2318exactlyAssertedEL_first(genls, 'CycLDeducedAssertion', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2319exactlyAssertedEL_first(genls, 'CycLDeducedAssertion', 'CycLAssertion', 'CoreCycLMt', vStrDef).
 2320exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLRepresentedAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2321exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLRepresentedAtomicTerm', 'CoreCycLMt', vStrDef).
 2322exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLReifiedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2323exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLReifiedDenotationalTerm', 'CoreCycLMt', vStrDef).
 2324exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLReifiableDenotationalTerm', 'CoreCycLMt', vStrDef).
 2325exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLClosedAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2326exactlyAssertedEL_first(genls, 'CycLConstant', 'CycLClosedAtomicTerm', 'CoreCycLMt', vStrDef).
 2327exactlyAssertedEL_first(genls, 'CycLClosedSentence', 'CycLSentence-ClosedPredicate', 'UniversalVocabularyMt', vStrDef).
 2328exactlyAssertedEL_first(genls, 'CycLClosedSentence', 'CycLSentence-ClosedPredicate', 'CoreCycLMt', vStrDef).
 2329exactlyAssertedEL_first(genls, 'CycLClosedSentence', 'CycLClosedExpression', 'UniversalVocabularyMt', vStrDef).
 2330exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2331exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLNonAtomicTerm-ClosedFunctor', 'UniversalVocabularyMt', vStrDef).
 2332exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLNonAtomicTerm-ClosedFunctor', 'CoreCycLMt', vStrDef).
 2333exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2334exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLNonAtomicTerm', 'CoreCycLMt', vStrDef).
 2335exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLClosedFormula', 'UniversalVocabularyMt', vStrDef).
 2336exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2337exactlyAssertedEL_first(genls, 'CycLClosedNonAtomicTerm', 'CycLClosedDenotationalTerm', 'CoreCycLMt', vStrDef).
 2338exactlyAssertedEL_first(genls, 'CycLClosedFormula', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 2339exactlyAssertedEL_first(genls, 'CycLClosedFormula', 'CycLFormula', 'CoreCycLMt', vStrDef).
 2340exactlyAssertedEL_first(genls, 'CycLClosedFormula', 'CycLClosedExpression', 'UniversalVocabularyMt', vStrDef).
 2341exactlyAssertedEL_first(genls, 'CycLClosedFormula', 'CycLClosedExpression', 'CoreCycLMt', vStrDef).
 2342exactlyAssertedEL_first(genls, 'CycLClosedExpression', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2343exactlyAssertedEL_first(genls, 'CycLClosedExpression', 'CycLTerm', 'CoreCycLMt', vStrDef).
 2344exactlyAssertedEL_first(genls, 'CycLClosedExpression', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2345exactlyAssertedEL_first(genls, 'CycLClosedExpression', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2346exactlyAssertedEL_first(genls, 'CycLClosedDenotationalTerm', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2347exactlyAssertedEL_first(genls, 'CycLClosedDenotationalTerm', 'CycLDenotationalTerm', 'CoreCycLMt', vStrDef).
 2348exactlyAssertedEL_first(genls, 'CycLClosedDenotationalTerm', 'CycLClosedExpression', 'UniversalVocabularyMt', vStrDef).
 2349exactlyAssertedEL_first(genls, 'CycLClosedDenotationalTerm', 'CycLClosedExpression', 'CoreCycLMt', vStrDef).
 2350exactlyAssertedEL_first(genls, 'CycLClosedAtomicTerm', 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2351exactlyAssertedEL_first(genls, 'CycLClosedAtomicTerm', 'CycLClosedDenotationalTerm', 'CoreCycLMt', vStrDef).
 2352exactlyAssertedEL_first(genls, 'CycLClosedAtomicTerm', 'CycLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 2353exactlyAssertedEL_first(genls, 'CycLClosedAtomicTerm', 'CycLAtomicTerm', 'CoreCycLMt', vStrDef).
 2354exactlyAssertedEL_first(genls, 'CycLClosedAtomicSentence', 'CycLClosedSentence', 'UniversalVocabularyMt', vStrDef).
 2355exactlyAssertedEL_first(genls, 'CycLClosedAtomicSentence', 'CycLClosedFormula', 'UniversalVocabularyMt', vStrDef).
 2356exactlyAssertedEL_first(genls, 'CycLClosedAtomicSentence', 'CycLAtomicSentence', 'UniversalVocabularyMt', vStrDef).
 2357exactlyAssertedEL_first(genls, 'CycLClosedAtomicSentence', 'CycLAtomicSentence', 'CoreCycLMt', vStrDef).
 2358exactlyAssertedEL_first(genls, 'CycLAtomicTerm', 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2359exactlyAssertedEL_first(genls, 'CycLAtomicTerm', 'CycLExpression', 'CoreCycLMt', vStrDef).
 2360exactlyAssertedEL_first(genls, 'CycLAtomicTerm', 'CycLDenotationalTerm-Assertible', 'UniversalVocabularyMt', vStrDef).
 2361exactlyAssertedEL_first(genls, 'CycLAtomicTerm', 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2362exactlyAssertedEL_first(genls, 'CycLAtomicTerm', 'CycLDenotationalTerm', 'CoreCycLMt', vStrDef).
 2363exactlyAssertedEL_first(genls, 'CycLAtomicSentence', 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 2364exactlyAssertedEL_first(genls, 'CycLAtomicSentence', 'CycLSentence', 'CoreCycLMt', vStrDef).
 2365exactlyAssertedEL_first(genls, 'CycLAtomicSentence', 'CycLFormulaicSentence', 'UniversalVocabularyMt', vStrDef).
 2366exactlyAssertedEL_first(genls, 'CycLAtomicSentence', 'CycLFormulaicSentence', 'CoreCycLMt', vStrDef).
 2367exactlyAssertedEL_first(genls, 'CycLAtomicAssertion', 'CycLAtomicSentence', 'UniversalVocabularyMt', vStrDef).
 2368exactlyAssertedEL_first(genls, 'CycLAtomicAssertion', 'CycLAtomicSentence', 'CoreCycLMt', vStrDef).
 2369exactlyAssertedEL_first(genls, 'CycLAtomicAssertion', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2370exactlyAssertedEL_first(genls, 'CycLAtomicAssertion', 'CycLAssertion', 'CoreCycLMt', vStrDef).
 2371exactlyAssertedEL_first(genls, 'CycLAssertionDirection', tCol, 'UniversalVocabularyMt', vStrDef).
 2372exactlyAssertedEL_first(genls, 'CycLAssertion', 'CycSupportDatastructure', 'UniversalVocabularyMt', vStrDef).
 2373exactlyAssertedEL_first(genls, 'CycLAssertion', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 2374exactlyAssertedEL_first(genls, 'CycLAssertion', 'CycLSentence-Assertible', 'CoreCycLMt', vStrDef).
 2375exactlyAssertedEL_first(genls, 'CycLAssertion', 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 2376exactlyAssertedEL_first(genls, 'CycLAssertedAssertion', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2377exactlyAssertedEL_first(genls, 'CycLAssertedAssertion', 'CycLAssertion', 'CoreCycLMt', vStrDef).
 2378exactlyAssertedEL_first(genls, 'CycKBDatastructure', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2379exactlyAssertedEL_first(genls, 'CycInferenceProblemLinkStatus', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2380exactlyAssertedEL_first(genls, 'CycInferenceDataStructure', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2381exactlyAssertedEL_first(genls, 'CycInferenceBindingsDataStructure', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2382exactlyAssertedEL_first(genls, 'CycInferenceAnswerJustification', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2383exactlyAssertedEL_first(genls, 'CycInferenceAnswer', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2384exactlyAssertedEL_first(genls, 'CycInference', 'CycInferenceDataStructure', 'UniversalVocabularyMt', vStrDef).
 2385exactlyAssertedEL_first(genls, 'CycHLTruthValue', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2386exactlyAssertedEL_first(genls, 'CycHLSupportDatastructure', 'CycSupportDatastructure', 'UniversalVocabularyMt', vStrDef).
 2387exactlyAssertedEL_first(genls, 'CycHLSupportDatastructure', 'CycKBDatastructure', 'UniversalVocabularyMt', vStrDef).
 2388exactlyAssertedEL_first(genls, 'CycDeductionDatastructure', 'CycArgumentDatastructure', 'UniversalVocabularyMt', vStrDef).
 2389exactlyAssertedEL_first(genls, 'CycArgumentDatastructure', 'CycKBDatastructure', 'UniversalVocabularyMt', vStrDef).
 2390exactlyAssertedEL_first(genls, 'CommutativeRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2391exactlyAssertedEL_first(genls, 'CommutativeRelation', tRelation, 'CoreCycLMt', vStrDef).
 2392exactlyAssertedEL_first(genls, 'CollectionDenotingFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2393exactlyAssertedEL_first(genls, 'CollectionDenotingFunction', tFunction, 'CoreCycLMt', vStrDef).
 2394exactlyAssertedEL_first(genls, tCol, 'Thing', 'LogicalTruthMt', vStrDef).
 2395exactlyAssertedEL_first(genls, tCol, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 2396exactlyAssertedEL_first(genls, tCol, 'SetOrCollection', 'CoreCycLMt', vStrDef).
 2397exactlyAssertedEL_first(genls, 'Code-AssertionDirection', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2398exactlyAssertedEL_first(genls, 'Closed-InferenceProblemLinkStatus', 'CycInferenceProblemLinkStatus', 'UniversalVocabularyMt', vStrDef).
 2399exactlyAssertedEL_first(genls, 'CanonicalizerDirective', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2400exactlyAssertedEL_first(genls, 'BroadMicrotheory', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2401exactlyAssertedEL_first(genls, 'BookkeepingPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2402exactlyAssertedEL_first(genls, 'BookkeepingPredicate', tPred, 'CoreCycLMt', vStrDef).
 2403exactlyAssertedEL_first(genls, 'BinaryRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 2404exactlyAssertedEL_first(genls, 'BinaryRelation', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 2405exactlyAssertedEL_first(genls, 'BinaryPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2406exactlyAssertedEL_first(genls, 'BinaryPredicate', tPred, 'CoreCycLMt', vStrDef).
 2407exactlyAssertedEL_first(genls, 'BinaryPredicate', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 2408exactlyAssertedEL_first(genls, 'BinaryPredicate', 'FixedArityRelation', 'CoreCycLMt', vStrDef).
 2409exactlyAssertedEL_first(genls, 'BinaryPredicate', 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
 2410exactlyAssertedEL_first(genls, 'BinaryPredicate', 'BinaryRelation', 'CoreCycLMt', vStrDef).
 2411exactlyAssertedEL_first(genls, 'BinaryFunction', tFunction, 'UniversalVocabularyMt', vStrDef).
 2412exactlyAssertedEL_first(genls, 'BinaryFunction', tFunction, 'CoreCycLMt', vStrDef).
 2413exactlyAssertedEL_first(genls, 'BinaryFunction', 'BinaryRelation', 'UniversalVocabularyMt', vStrDef).
 2414exactlyAssertedEL_first(genls, 'BinaryFunction', 'BinaryRelation', 'CoreCycLMt', vStrDef).
 2415exactlyAssertedEL_first(genls, 'Backward-AssertionDirection', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2416exactlyAssertedEL_first(genls, 'August', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2417exactlyAssertedEL_first(genls, 'AtemporalNecessarilyEssentialCollectionType', tCol, 'UniversalVocabularyMt', vStrDef).
 2418exactlyAssertedEL_first(genls, 'AsymmetricBinaryPredicate', 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2419exactlyAssertedEL_first(genls, 'AsymmetricBinaryPredicate', 'IrreflexiveBinaryPredicate', 'CoreCycLMt', vStrDef).
 2420exactlyAssertedEL_first(genls, 'AsymmetricBinaryPredicate', 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2421exactlyAssertedEL_first(genls, 'AsymmetricBinaryPredicate', 'AntiSymmetricBinaryPredicate', 'CoreCycLMt', vStrDef).
 2422exactlyAssertedEL_first(genls, 'AssociativeRelation', tRelation, 'UniversalVocabularyMt', vStrDef).
 2423exactlyAssertedEL_first(genls, 'AssociativeRelation', tRelation, 'CoreCycLMt', vStrDef).
 2424exactlyAssertedEL_first(genls, 'ArgTypeTernaryPredicate', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2425exactlyAssertedEL_first(genls, 'ArgTypeTernaryPredicate', 'TernaryPredicate', 'CoreCycLMt', vStrDef).
 2426exactlyAssertedEL_first(genls, 'ArgTypeTernaryPredicate', 'ArgTypePredicate', 'UniversalVocabularyMt', vStrDef).
 2427exactlyAssertedEL_first(genls, 'ArgTypeTernaryPredicate', 'ArgTypePredicate', 'CoreCycLMt', vStrDef).
 2428exactlyAssertedEL_first(genls, 'ArgTypePredicate', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2429exactlyAssertedEL_first(genls, 'ArgTypePredicate', 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 2430exactlyAssertedEL_first(genls, 'ArgTypePredicate', 'ArgConstraintPredicate', 'CoreCycLMt', vStrDef).
 2431exactlyAssertedEL_first(genls, 'ArgTypeBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2432exactlyAssertedEL_first(genls, 'ArgTypeBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 2433exactlyAssertedEL_first(genls, 'ArgTypeBinaryPredicate', 'ArgTypePredicate', 'UniversalVocabularyMt', vStrDef).
 2434exactlyAssertedEL_first(genls, 'ArgTypeBinaryPredicate', 'ArgTypePredicate', 'CoreCycLMt', vStrDef).
 2435exactlyAssertedEL_first(genls, 'ArgSometimesIsaPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2436exactlyAssertedEL_first(genls, 'ArgQuotedIsaTernaryPredicate', 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2437exactlyAssertedEL_first(genls, 'ArgQuotedIsaTernaryPredicate', 'ArgTypeTernaryPredicate', 'CoreCycLMt', vStrDef).
 2438exactlyAssertedEL_first(genls, 'ArgQuotedIsaTernaryPredicate', 'ArgQuotedIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 2439exactlyAssertedEL_first(genls, 'ArgQuotedIsaPredicate', 'ArgTypePredicate', 'UniversalVocabularyMt', vStrDef).
 2440exactlyAssertedEL_first(genls, 'ArgQuotedIsaBinaryPredicate', 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2441exactlyAssertedEL_first(genls, 'ArgQuotedIsaBinaryPredicate', 'ArgTypeBinaryPredicate', 'CoreCycLMt', vStrDef).
 2442exactlyAssertedEL_first(genls, 'ArgQuotedIsaBinaryPredicate', 'ArgQuotedIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 2443exactlyAssertedEL_first(genls, 'ArgIsaTernaryPredicate', 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2444exactlyAssertedEL_first(genls, 'ArgIsaTernaryPredicate', 'ArgTypeTernaryPredicate', 'CoreCycLMt', vStrDef).
 2445exactlyAssertedEL_first(genls, 'ArgIsaTernaryPredicate', 'ArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 2446exactlyAssertedEL_first(genls, 'ArgIsaPredicate', 'ArgTypePredicate', 'UniversalVocabularyMt', vStrDef).
 2447exactlyAssertedEL_first(genls, 'ArgIsaBinaryPredicate', 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2448exactlyAssertedEL_first(genls, 'ArgIsaBinaryPredicate', 'ArgTypeBinaryPredicate', 'CoreCycLMt', vStrDef).
 2449exactlyAssertedEL_first(genls, 'ArgIsaBinaryPredicate', 'ArgIsaPredicate', 'UniversalVocabularyMt', vStrDef).
 2450exactlyAssertedEL_first(genls, 'ArgGenlTernaryPredicate', 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2451exactlyAssertedEL_first(genls, 'ArgGenlTernaryPredicate', 'ArgTypeTernaryPredicate', 'CoreCycLMt', vStrDef).
 2452exactlyAssertedEL_first(genls, 'ArgGenlQuantityTernaryPredicate', 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2453exactlyAssertedEL_first(genls, 'ArgGenlQuantityTernaryPredicate', 'ArgTypeTernaryPredicate', 'CoreCycLMt', vStrDef).
 2454exactlyAssertedEL_first(genls, 'ArgGenlQuantityBinaryPredicate', 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2455exactlyAssertedEL_first(genls, 'ArgGenlQuantityBinaryPredicate', 'ArgTypeBinaryPredicate', 'CoreCycLMt', vStrDef).
 2456exactlyAssertedEL_first(genls, 'ArgGenlBinaryPredicate', 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2457exactlyAssertedEL_first(genls, 'ArgGenlBinaryPredicate', 'ArgTypeBinaryPredicate', 'CoreCycLMt', vStrDef).
 2458exactlyAssertedEL_first(genls, 'ArgConstraintPredicate', tPred, 'UniversalVocabularyMt', vStrDef).
 2459exactlyAssertedEL_first(genls, 'April', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2460exactlyAssertedEL_first(genls, 'AntiTransitiveBinaryPredicate', 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2461exactlyAssertedEL_first(genls, 'AntiTransitiveBinaryPredicate', 'IrreflexiveBinaryPredicate', 'CoreCycLMt', vStrDef).
 2462exactlyAssertedEL_first(genls, 'AntiSymmetricBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 2463exactlyAssertedEL_first(genls, 'AntiSymmetricBinaryPredicate', 'BinaryPredicate', 'CoreCycLMt', vStrDef).
 2464exactlyAssertedEL_first(arityMin, differentSymbols, 2, 'UniversalVocabularyMt', vStrDef).
 2465exactlyAssertedEL_first(arityMin, different, 2, 'UniversalVocabularyMt', vStrDef).
 2466exactlyAssertedEL_first(arityMin, commutativeInArgsAndRest, 2, 'UniversalVocabularyMt', vStrDef).
 2467exactlyAssertedEL_first(arityMin, commutativeInArgs, 3, 'UniversalVocabularyMt', vStrDef).
 2468exactlyAssertedEL_first(arityMin, and, 1, 'UniversalVocabularyMt', vStrDef).
 2469exactlyAssertedEL_first(arityMin, 'Unity', 1, 'UniversalVocabularyMt', vStrDef).
 2470exactlyAssertedEL_first(arityMin, 'TimesFn', 1, 'UniversalVocabularyMt', vStrDef).
 2471exactlyAssertedEL_first(arityMin, 'TheSet', 0, 'UniversalVocabularyMt', vStrDef).
 2472exactlyAssertedEL_first(arityMin, 'PlusFn', 1, 'UniversalVocabularyMt', vStrDef).
 2473exactlyAssertedEL_first(arityMin, 'Percent', 1, 'UniversalVocabularyMt', vStrDef).
 2474exactlyAssertedEL_first(arityMin, 'MinRangeFn', 1, 'UniversalVocabularyMt', vStrDef).
 2475exactlyAssertedEL_first(arityMin, 'MaxRangeFn', 1, 'UniversalVocabularyMt', vStrDef).
 2476exactlyAssertedEL_first(arityMax, 'Unity', 2, 'UniversalVocabularyMt', vStrDef).
 2477exactlyAssertedEL_first(arityMax, 'Percent', 2, 'UniversalVocabularyMt', vStrDef).
 2478exactlyAssertedEL_first(arity, xor, 2, 'UniversalVocabularyMt', vStrDef).
 2479exactlyAssertedEL_first(arity, unknownSentence, 1, 'UniversalVocabularyMt', vStrDef).
 2480exactlyAssertedEL_first(arity, unitMultiplicationFactor, 3, 'UniversalVocabularyMt', vStrDef).
 2481exactlyAssertedEL_first(arity, trueSubL, 1, 'UniversalVocabularyMt', vStrDef).
 2482exactlyAssertedEL_first(arity, trueSentence, 1, 'UniversalVocabularyMt', vStrDef).
 2483exactlyAssertedEL_first(arity, trueRule, 2, 'UniversalVocabularyMt', vStrDef).
 2484exactlyAssertedEL_first(arity, transitiveViaArgInverse, 3, 'UniversalVocabularyMt', vStrDef).
 2485exactlyAssertedEL_first(arity, transitiveViaArg, 3, 'UniversalVocabularyMt', vStrDef).
 2486exactlyAssertedEL_first(arity, thereExists, 2, 'UniversalVocabularyMt', vStrDef).
 2487exactlyAssertedEL_first(arity, thereExists, 2, 'LogicalTruthMt', vStrDef).
 2488exactlyAssertedEL_first(arity, thereExistExactly, 3, 'UniversalVocabularyMt', vStrDef).
 2489exactlyAssertedEL_first(arity, thereExistAtMost, 3, 'UniversalVocabularyMt', vStrDef).
 2490exactlyAssertedEL_first(arity, thereExistAtLeast, 3, 'UniversalVocabularyMt', vStrDef).
 2491exactlyAssertedEL_first(arity, termOfUnit, 2, 'UniversalVocabularyMt', vStrDef).
 2492exactlyAssertedEL_first(arity, termOfUnit, 2, 'LogicalTruthImplementationMt', vStrDef).
 2493exactlyAssertedEL_first(arity, termExternalIDString, 2, 'UniversalVocabularyMt', vStrDef).
 2494exactlyAssertedEL_first(arity, termDependsOn, 2, 'UniversalVocabularyMt', vStrDef).
 2495exactlyAssertedEL_first(arity, termChosen, 1, 'UniversalVocabularyMt', vStrDef).
 2496exactlyAssertedEL_first(arity, synonymousExternalConcept, 3, 'UniversalVocabularyMt', vStrDef).
 2497exactlyAssertedEL_first(arity, substring, 2, 'UniversalVocabularyMt', vStrDef).
 2498exactlyAssertedEL_first(arity, subsetOf, 2, 'UniversalVocabularyMt', vStrDef).
 2499exactlyAssertedEL_first(arity, skolemizeForward, 1, 'UniversalVocabularyMt', vStrDef).
 2500exactlyAssertedEL_first(arity, skolem, 1, 'UniversalVocabularyMt', vStrDef).
 2501exactlyAssertedEL_first(arity, singleEntryFormatInArgs, 2, 'UniversalVocabularyMt', vStrDef).
 2502exactlyAssertedEL_first(arity, siblingDisjointExceptions, 2, 'UniversalVocabularyMt', vStrDef).
 2503exactlyAssertedEL_first(arity, sharedNotes, 2, 'UniversalVocabularyMt', vStrDef).
 2504exactlyAssertedEL_first(arity, sentenceTruth, 2, 'UniversalVocabularyMt', vStrDef).
 2505exactlyAssertedEL_first(arity, sentenceImplies, 2, 'UniversalVocabularyMt', vStrDef).
 2506exactlyAssertedEL_first(arity, sentenceEquiv, 2, 'UniversalVocabularyMt', vStrDef).
 2507exactlyAssertedEL_first(arity, sentenceDesignationArgnum, 2, 'UniversalVocabularyMt', vStrDef).
 2508exactlyAssertedEL_first(arity, scopingArg, 2, 'UniversalVocabularyMt', vStrDef).
 2509exactlyAssertedEL_first(arity, salientAssertions, 2, 'UniversalVocabularyMt', vStrDef).
 2510exactlyAssertedEL_first(arity, ruleTemplateDirection, 2, 'UniversalVocabularyMt', vStrDef).
 2511exactlyAssertedEL_first(arity, ruleAfterRemoving, 2, 'UniversalVocabularyMt', vStrDef).
 2512exactlyAssertedEL_first(arity, ruleAfterAdding, 2, 'UniversalVocabularyMt', vStrDef).
 2513exactlyAssertedEL_first(arity, rewriteOf, 2, 'UniversalVocabularyMt', vStrDef).
 2514exactlyAssertedEL_first(arity, resultQuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2515exactlyAssertedEL_first(arity, resultIsaArgIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2516exactlyAssertedEL_first(arity, resultIsaArg, 2, 'UniversalVocabularyMt', vStrDef).
 2517exactlyAssertedEL_first(arity, resultIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2518exactlyAssertedEL_first(arity, resultIsa, 2, 'LogicalTruthMt', vStrDef).
 2519exactlyAssertedEL_first(arity, resultGenlArg, 2, 'UniversalVocabularyMt', vStrDef).
 2520exactlyAssertedEL_first(arity, resultGenl, 2, 'UniversalVocabularyMt', vStrDef).
 2521exactlyAssertedEL_first(arity, requiredArg3Pred, 2, 'UniversalVocabularyMt', vStrDef).
 2522exactlyAssertedEL_first(arity, requiredArg2Pred, 2, 'UniversalVocabularyMt', vStrDef).
 2523exactlyAssertedEL_first(arity, requiredArg1Pred, 2, 'UniversalVocabularyMt', vStrDef).
 2524exactlyAssertedEL_first(arity, relationMemberInstance, 3, 'UniversalVocabularyMt', vStrDef).
 2525exactlyAssertedEL_first(arity, relationInstanceMember, 3, 'UniversalVocabularyMt', vStrDef).
 2526exactlyAssertedEL_first(arity, relationInstanceExists, 3, 'UniversalVocabularyMt', vStrDef).
 2527exactlyAssertedEL_first(arity, relationInstanceAll, 3, 'UniversalVocabularyMt', vStrDef).
 2528exactlyAssertedEL_first(arity, relationExpansion, 2, 'UniversalVocabularyMt', vStrDef).
 2529exactlyAssertedEL_first(arity, relationExistsMinAll, 4, 'UniversalVocabularyMt', vStrDef).
 2530exactlyAssertedEL_first(arity, relationExistsMaxAll, 4, 'UniversalVocabularyMt', vStrDef).
 2531exactlyAssertedEL_first(arity, relationExistsInstance, 3, 'UniversalVocabularyMt', vStrDef).
 2532exactlyAssertedEL_first(arity, relationExistsCountAll, 4, 'UniversalVocabularyMt', vStrDef).
 2533exactlyAssertedEL_first(arity, relationExistsAll, 3, 'UniversalVocabularyMt', vStrDef).
 2534exactlyAssertedEL_first(arity, relationAllInstance, 3, 'UniversalVocabularyMt', vStrDef).
 2535exactlyAssertedEL_first(arity, relationAllExistsMin, 4, 'UniversalVocabularyMt', vStrDef).
 2536exactlyAssertedEL_first(arity, relationAllExistsMax, 4, 'UniversalVocabularyMt', vStrDef).
 2537exactlyAssertedEL_first(arity, relationAllExistsCount, 4, 'UniversalVocabularyMt', vStrDef).
 2538exactlyAssertedEL_first(arity, relationAllExists, 3, 'UniversalVocabularyMt', vStrDef).
 2539exactlyAssertedEL_first(arity, relationAll, 2, 'UniversalVocabularyMt', vStrDef).
 2540exactlyAssertedEL_first(arity, reformulatorRuleProperties, 2, 'UniversalVocabularyMt', vStrDef).
 2541exactlyAssertedEL_first(arity, reformulatorRule, 2, 'UniversalVocabularyMt', vStrDef).
 2542exactlyAssertedEL_first(arity, reformulatorEquiv, 2, 'UniversalVocabularyMt', vStrDef).
 2543exactlyAssertedEL_first(arity, reformulatorEquals, 2, 'UniversalVocabularyMt', vStrDef).
 2544exactlyAssertedEL_first(arity, reformulationPrecondition, 3, 'UniversalVocabularyMt', vStrDef).
 2545exactlyAssertedEL_first(arity, reformulationDirectionInMode, 3, 'UniversalVocabularyMt', vStrDef).
 2546exactlyAssertedEL_first(arity, ratioOfTo, 3, 'UniversalVocabularyMt', vStrDef).
 2547exactlyAssertedEL_first(arity, quotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2548exactlyAssertedEL_first(arity, quotedDefnSufficient, 2, 'UniversalVocabularyMt', vStrDef).
 2549exactlyAssertedEL_first(arity, quotedDefnNecessary, 2, 'UniversalVocabularyMt', vStrDef).
 2550exactlyAssertedEL_first(arity, quotedDefnIff, 2, 'UniversalVocabularyMt', vStrDef).
 2551exactlyAssertedEL_first(arity, quotedArgument, 2, 'UniversalVocabularyMt', vStrDef).
 2552exactlyAssertedEL_first(arity, querySentence, 1, 'UniversalVocabularyMt', vStrDef).
 2553exactlyAssertedEL_first(arity, quantitySubsumes, 2, 'UniversalVocabularyMt', vStrDef).
 2554exactlyAssertedEL_first(arity, quantityIntersects, 2, 'UniversalVocabularyMt', vStrDef).
 2555exactlyAssertedEL_first(arity, prettyString, 2, 'UniversalVocabularyMt', vStrDef).
 2556exactlyAssertedEL_first(arity, preservesGenlsInArg, 2, 'UniversalVocabularyMt', vStrDef).
 2557exactlyAssertedEL_first(arity, predicateConventionMt, 2, 'UniversalVocabularyMt', vStrDef).
 2558exactlyAssertedEL_first(arity, pragmaticRequirement, 2, 'UniversalVocabularyMt', vStrDef).
 2559exactlyAssertedEL_first(arity, pragmaticallyNormal, 2, 'UniversalVocabularyMt', vStrDef).
 2560exactlyAssertedEL_first(arity, pointQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 2561exactlyAssertedEL_first(arity, performSubL, 1, 'UniversalVocabularyMt', vStrDef).
 2562exactlyAssertedEL_first(arity, overlappingExternalConcept, 3, 'UniversalVocabularyMt', vStrDef).
 2563exactlyAssertedEL_first(arity, operatorFormulas, 2, 'UniversalVocabularyMt', vStrDef).
 2564exactlyAssertedEL_first(arity, openEntryFormatInArgs, 2, 'UniversalVocabularyMt', vStrDef).
 2565exactlyAssertedEL_first(arity, opaqueArgument, 2, 'UniversalVocabularyMt', vStrDef).
 2566exactlyAssertedEL_first(arity, omitArgIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2567exactlyAssertedEL_first(arity, oldConstantName, 2, 'UniversalVocabularyMt', vStrDef).
 2568exactlyAssertedEL_first(arity, numericallyEquals, 2, 'UniversalVocabularyMt', vStrDef).
 2569exactlyAssertedEL_first(arity, nthSmallestElement, 4, 'UniversalVocabularyMt', vStrDef).
 2570exactlyAssertedEL_first(arity, nthLargestElement, 4, 'UniversalVocabularyMt', vStrDef).
 2571exactlyAssertedEL_first(arity, notAssertibleMt, 1, 'UniversalVocabularyMt', vStrDef).
 2572exactlyAssertedEL_first(arity, notAssertibleCollection, 1, 'UniversalVocabularyMt', vStrDef).
 2573exactlyAssertedEL_first(arity, notAssertible, 1, 'UniversalVocabularyMt', vStrDef).
 2574exactlyAssertedEL_first(arity, not, 1, 'UniversalVocabularyMt', vStrDef).
 2575exactlyAssertedEL_first(arity, not, 1, 'LogicalTruthMt', vStrDef).
 2576exactlyAssertedEL_first(arity, nonAbducibleWithValueInArg, 3, 'UniversalVocabularyMt', vStrDef).
 2577exactlyAssertedEL_first(arity, negationPreds, 2, 'UniversalVocabularyMt', vStrDef).
 2578exactlyAssertedEL_first(arity, negationMt, 2, 'UniversalVocabularyMt', vStrDef).
 2579exactlyAssertedEL_first(arity, negationInverse, 2, 'UniversalVocabularyMt', vStrDef).
 2580exactlyAssertedEL_first(arity, nearestIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2581exactlyAssertedEL_first(arity, nearestGenls, 2, 'UniversalVocabularyMt', vStrDef).
 2582exactlyAssertedEL_first(arity, nearestGenlPreds, 2, 'UniversalVocabularyMt', vStrDef).
 2583exactlyAssertedEL_first(arity, nearestGenlMt, 2, 'UniversalVocabularyMt', vStrDef).
 2584exactlyAssertedEL_first(arity, nearestDifferentIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2585exactlyAssertedEL_first(arity, nearestDifferentGenls, 3, 'UniversalVocabularyMt', vStrDef).
 2586exactlyAssertedEL_first(arity, nearestCommonSpecs, 3, 'UniversalVocabularyMt', vStrDef).
 2587exactlyAssertedEL_first(arity, nearestCommonIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2588exactlyAssertedEL_first(arity, nearestCommonGenls, 3, 'UniversalVocabularyMt', vStrDef).
 2589exactlyAssertedEL_first(arity, nearestCommonGenlMt, 3, 'UniversalVocabularyMt', vStrDef).
 2590exactlyAssertedEL_first(arity, natFunction, 2, 'UniversalVocabularyMt', vStrDef).
 2591exactlyAssertedEL_first(arity, natArgumentsEqual, 2, 'UniversalVocabularyMt', vStrDef).
 2592exactlyAssertedEL_first(arity, natArgument, 3, 'UniversalVocabularyMt', vStrDef).
 2593exactlyAssertedEL_first(arity, myCreator, 2, 'UniversalVocabularyMt', vStrDef).
 2594exactlyAssertedEL_first(arity, myCreationTime, 2, 'UniversalVocabularyMt', vStrDef).
 2595exactlyAssertedEL_first(arity, myCreationSecond, 2, 'UniversalVocabularyMt', vStrDef).
 2596exactlyAssertedEL_first(arity, myCreationPurpose, 2, 'UniversalVocabularyMt', vStrDef).
 2597exactlyAssertedEL_first(arity, multiplicationUnits, 3, 'UniversalVocabularyMt', vStrDef).
 2598exactlyAssertedEL_first(arity, mtVisible, 1, 'UniversalVocabularyMt', vStrDef).
 2599exactlyAssertedEL_first(arity, minQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 2600exactlyAssertedEL_first(arity, minimizeExtent, 1, 'UniversalVocabularyMt', vStrDef).
 2601exactlyAssertedEL_first(arity, minimize, 1, 'UniversalVocabularyMt', vStrDef).
 2602exactlyAssertedEL_first(arity, microtheoryDesignationArgnum, 2, 'UniversalVocabularyMt', vStrDef).
 2603exactlyAssertedEL_first(arity, meetsPragmaticRequirement, 2, 'UniversalVocabularyMt', vStrDef).
 2604exactlyAssertedEL_first(arity, means, 2, 'UniversalVocabularyMt', vStrDef).
 2605exactlyAssertedEL_first(arity, maxQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 2606exactlyAssertedEL_first(arity, knownSentence, 1, 'UniversalVocabularyMt', vStrDef).
 2607exactlyAssertedEL_first(arity, knownAntecedentRule, 1, 'UniversalVocabularyMt', vStrDef).
 2608exactlyAssertedEL_first(arity, ist, 2, 'UniversalVocabularyMt', vStrDef).
 2609exactlyAssertedEL_first(arity, ist, 2, 'LogicalTruthMt', vStrDef).
 2610exactlyAssertedEL_first(arity, isa, 2, 'UniversalVocabularyMt', vStrDef).
 2611exactlyAssertedEL_first(arity, isa, 2, 'LogicalTruthMt', vStrDef).
 2612exactlyAssertedEL_first(arity, irrelevantTerm, 1, 'UniversalVocabularyMt', vStrDef).
 2613exactlyAssertedEL_first(arity, irrelevantPredAssertion, 2, 'UniversalVocabularyMt', vStrDef).
 2614exactlyAssertedEL_first(arity, irrelevantMt, 1, 'UniversalVocabularyMt', vStrDef).
 2615exactlyAssertedEL_first(arity, irrelevantAssertion, 1, 'UniversalVocabularyMt', vStrDef).
 2616exactlyAssertedEL_first(arity, interArgResultIsaReln, 5, 'UniversalVocabularyMt', vStrDef).
 2617exactlyAssertedEL_first(arity, interArgResultIsa, 4, 'UniversalVocabularyMt', vStrDef).
 2618exactlyAssertedEL_first(arity, interArgResultGenlReln, 5, 'UniversalVocabularyMt', vStrDef).
 2619exactlyAssertedEL_first(arity, interArgResultGenl, 4, 'UniversalVocabularyMt', vStrDef).
 2620exactlyAssertedEL_first(arity, interArgIsa, 5, 'UniversalVocabularyMt', vStrDef).
 2621exactlyAssertedEL_first(arity, interArgDifferent, 3, 'UniversalVocabularyMt', vStrDef).
 2622exactlyAssertedEL_first(arity, integerBetween, 3, 'UniversalVocabularyMt', vStrDef).
 2623exactlyAssertedEL_first(arity, instanceElementType, 2, 'UniversalVocabularyMt', vStrDef).
 2624exactlyAssertedEL_first(arity, indexicalReferent, 2, 'UniversalVocabularyMt', vStrDef).
 2625exactlyAssertedEL_first(arity, independentArg, 2, 'UniversalVocabularyMt', vStrDef).
 2626exactlyAssertedEL_first(arity, implies, 2, 'UniversalVocabularyMt', vStrDef).
 2627exactlyAssertedEL_first(arity, implies, 2, 'LogicalTruthMt', vStrDef).
 2628exactlyAssertedEL_first(arity, hypotheticalTerm, 1, 'UniversalVocabularyMt', vStrDef).
 2629exactlyAssertedEL_first(arity, holdsIn, 2, 'UniversalVocabularyMt', vStrDef).
 2630exactlyAssertedEL_first(arity, hlPrototypicalInstance, 2, 'UniversalVocabularyMt', vStrDef).
 2631exactlyAssertedEL_first(arity, highlyRelevantTerm, 1, 'UniversalVocabularyMt', vStrDef).
 2632exactlyAssertedEL_first(arity, highlyRelevantPredAssertion, 2, 'UniversalVocabularyMt', vStrDef).
 2633exactlyAssertedEL_first(arity, highlyRelevantMt, 1, 'UniversalVocabularyMt', vStrDef).
 2634exactlyAssertedEL_first(arity, highlyRelevantAssertion, 1, 'UniversalVocabularyMt', vStrDef).
 2635exactlyAssertedEL_first(arity, greaterThanOrEqualTo, 2, 'UniversalVocabularyMt', vStrDef).
 2636exactlyAssertedEL_first(arity, greaterThan, 2, 'UniversalVocabularyMt', vStrDef).
 2637exactlyAssertedEL_first(arity, genMassNoun, 1, 'UniversalVocabularyMt', vStrDef).
 2638exactlyAssertedEL_first(arity, genls, 2, 'UniversalVocabularyMt', vStrDef).
 2639exactlyAssertedEL_first(arity, genls, 2, 'LogicalTruthMt', vStrDef).
 2640exactlyAssertedEL_first(arity, genlRules, 2, 'UniversalVocabularyMt', vStrDef).
 2641exactlyAssertedEL_first(arity, genlPreds, 2, 'UniversalVocabularyMt', vStrDef).
 2642exactlyAssertedEL_first(arity, genlMt, 2, 'UniversalVocabularyMt', vStrDef).
 2643exactlyAssertedEL_first(arity, genlMt, 2, 'LogicalTruthMt', vStrDef).
 2644exactlyAssertedEL_first(arity, genlInverse, 2, 'UniversalVocabularyMt', vStrDef).
 2645exactlyAssertedEL_first(arity, genlCanonicalizerDirectives, 2, 'UniversalVocabularyMt', vStrDef).
 2646exactlyAssertedEL_first(arity, genKeyword, 2, 'UniversalVocabularyMt', vStrDef).
 2647exactlyAssertedEL_first(arity, genFormat, 3, 'UniversalVocabularyMt', vStrDef).
 2648exactlyAssertedEL_first(arity, forwardNonTriggerLiteral, 1, 'UniversalVocabularyMt', vStrDef).
 2649exactlyAssertedEL_first(arity, formulaArity, 2, 'UniversalVocabularyMt', vStrDef).
 2650exactlyAssertedEL_first(arity, forAll, 2, 'UniversalVocabularyMt', vStrDef).
 2651exactlyAssertedEL_first(arity, forAll, 2, 'LogicalTruthMt', vStrDef).
 2652exactlyAssertedEL_first(arity, followingValue, 2, 'UniversalVocabularyMt', vStrDef).
 2653exactlyAssertedEL_first(arity, fanOutArg, 2, 'UniversalVocabularyMt', vStrDef).
 2654exactlyAssertedEL_first(arity, extentCardinality, 2, 'UniversalVocabularyMt', vStrDef).
 2655exactlyAssertedEL_first(arity, extConceptOverlapsColAndReln, 4, 'UniversalVocabularyMt', vStrDef).
 2656exactlyAssertedEL_first(arity, expresses, 2, 'UniversalVocabularyMt', vStrDef).
 2657exactlyAssertedEL_first(arity, expansionDefn, 2, 'UniversalVocabularyMt', vStrDef).
 2658exactlyAssertedEL_first(arity, expansion, 2, 'UniversalVocabularyMt', vStrDef).
 2659exactlyAssertedEL_first(arity, exceptWhen, 2, 'UniversalVocabularyMt', vStrDef).
 2660exactlyAssertedEL_first(arity, exceptMt, 1, 'UniversalVocabularyMt', vStrDef).
 2661exactlyAssertedEL_first(arity, exceptFor, 2, 'UniversalVocabularyMt', vStrDef).
 2662exactlyAssertedEL_first(arity, except, 1, 'UniversalVocabularyMt', vStrDef).
 2663exactlyAssertedEL_first(arity, exampleAssertions, 2, 'UniversalVocabularyMt', vStrDef).
 2664exactlyAssertedEL_first(arity, exactlyAssertedEL_next, 1, 'UniversalVocabularyMt', vStrDef).
 2665exactlyAssertedEL_first(arity, evaluationResultQuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2666exactlyAssertedEL_first(arity, evaluationDefn, 2, 'UniversalVocabularyMt', vStrDef).
 2667exactlyAssertedEL_first(arity, evaluateImmediately, 1, 'UniversalVocabularyMt', vStrDef).
 2668exactlyAssertedEL_first(arity, evaluateAtEL, 1, 'UniversalVocabularyMt', vStrDef).
 2669exactlyAssertedEL_first(arity, evaluate, 2, 'UniversalVocabularyMt', vStrDef).
 2670exactlyAssertedEL_first(arity, equiv, 2, 'UniversalVocabularyMt', vStrDef).
 2671exactlyAssertedEL_first(arity, equalSymbols, 2, 'UniversalVocabularyMt', vStrDef).
 2672exactlyAssertedEL_first(arity, equals, 2, 'UniversalVocabularyMt', vStrDef).
 2673exactlyAssertedEL_first(arity, equals, 2, 'LogicalTruthMt', vStrDef).
 2674exactlyAssertedEL_first(arity, ephemeralTerm, 1, 'UniversalVocabularyMt', vStrDef).
 2675exactlyAssertedEL_first(arity, elInverse, 2, 'UniversalVocabularyMt', vStrDef).
 2676exactlyAssertedEL_first(arity, elementOf, 2, 'UniversalVocabularyMt', vStrDef).
 2677exactlyAssertedEL_first(arity, distributesOutOfArg, 3, 'UniversalVocabularyMt', vStrDef).
 2678exactlyAssertedEL_first(arity, disjointWith, 2, 'UniversalVocabularyMt', vStrDef).
 2679exactlyAssertedEL_first(arity, disjointWith, 2, 'LogicalTruthMt', vStrDef).
 2680exactlyAssertedEL_first(arity, denotes, 2, 'UniversalVocabularyMt', vStrDef).
 2681exactlyAssertedEL_first(arity, denotes, 2, 'LogicalTruthMt', vStrDef).
 2682exactlyAssertedEL_first(arity, defnSufficient, 2, 'UniversalVocabularyMt', vStrDef).
 2683exactlyAssertedEL_first(arity, defnNecessary, 2, 'UniversalVocabularyMt', vStrDef).
 2684exactlyAssertedEL_first(arity, defnIff, 2, 'UniversalVocabularyMt', vStrDef).
 2685exactlyAssertedEL_first(arity, defnIff, 2, 'LogicalTruthImplementationMt', vStrDef).
 2686exactlyAssertedEL_first(arity, definingMt, 2, 'UniversalVocabularyMt', vStrDef).
 2687exactlyAssertedEL_first(arity, defaultReformulationDirectionInModeForPred, 3, 'UniversalVocabularyMt', vStrDef).
 2688exactlyAssertedEL_first(arity, decontextualizedPredicate, 1, 'UniversalVocabularyMt', vStrDef).
 2689exactlyAssertedEL_first(arity, decontextualizedCollection, 1, 'UniversalVocabularyMt', vStrDef).
 2690exactlyAssertedEL_first(arity, cycTransformationProofRule, 2, 'UniversalVocabularyMt', vStrDef).
 2691exactlyAssertedEL_first(arity, cycTransformationProofBindings, 2, 'UniversalVocabularyMt', vStrDef).
 2692exactlyAssertedEL_first(arity, cycTacticID, 3, 'UniversalVocabularyMt', vStrDef).
 2693exactlyAssertedEL_first(arity, cycProofID, 3, 'UniversalVocabularyMt', vStrDef).
 2694exactlyAssertedEL_first(arity, cycProblemStoreTerms, 2, 'UniversalVocabularyMt', vStrDef).
 2695exactlyAssertedEL_first(arity, cycProblemStoreProofs, 2, 'UniversalVocabularyMt', vStrDef).
 2696exactlyAssertedEL_first(arity, cycProblemStoreProofCount, 2, 'UniversalVocabularyMt', vStrDef).
 2697exactlyAssertedEL_first(arity, cycProblemStoreProblems, 2, 'UniversalVocabularyMt', vStrDef).
 2698exactlyAssertedEL_first(arity, cycProblemStoreProblemCount, 2, 'UniversalVocabularyMt', vStrDef).
 2699exactlyAssertedEL_first(arity, cycProblemStoreLinks, 2, 'UniversalVocabularyMt', vStrDef).
 2700exactlyAssertedEL_first(arity, cycProblemStoreLinkCount, 2, 'UniversalVocabularyMt', vStrDef).
 2701exactlyAssertedEL_first(arity, cycProblemStoreInferences, 2, 'UniversalVocabularyMt', vStrDef).
 2702exactlyAssertedEL_first(arity, cycProblemStoreInferenceCount, 2, 'UniversalVocabularyMt', vStrDef).
 2703exactlyAssertedEL_first(arity, cycProblemStoreID, 2, 'UniversalVocabularyMt', vStrDef).
 2704exactlyAssertedEL_first(arity, cycProblemQueryTerms, 2, 'UniversalVocabularyMt', vStrDef).
 2705exactlyAssertedEL_first(arity, cycProblemQuerySentence, 2, 'UniversalVocabularyMt', vStrDef).
 2706exactlyAssertedEL_first(arity, cycProblemProvabilityStatus, 2, 'UniversalVocabularyMt', vStrDef).
 2707exactlyAssertedEL_first(arity, cycProblemLinkID, 3, 'UniversalVocabularyMt', vStrDef).
 2708exactlyAssertedEL_first(arity, cycProblemID, 3, 'UniversalVocabularyMt', vStrDef).
 2709exactlyAssertedEL_first(arity, cycProblemDependentLinks, 2, 'UniversalVocabularyMt', vStrDef).
 2710exactlyAssertedEL_first(arity, cycProblemArgumentLinks, 2, 'UniversalVocabularyMt', vStrDef).
 2711exactlyAssertedEL_first(arity, cycInferenceRelevantProblems, 2, 'UniversalVocabularyMt', vStrDef).
 2712exactlyAssertedEL_first(arity, cycInferenceAnswerLink, 2, 'UniversalVocabularyMt', vStrDef).
 2713exactlyAssertedEL_first(arity, constraint, 1, 'UniversalVocabularyMt', vStrDef).
 2714exactlyAssertedEL_first(arity, constrainsArg, 2, 'UniversalVocabularyMt', vStrDef).
 2715exactlyAssertedEL_first(arity, constantName, 2, 'UniversalVocabularyMt', vStrDef).
 2716exactlyAssertedEL_first(arity, constantID, 2, 'UniversalVocabularyMt', vStrDef).
 2717exactlyAssertedEL_first(arity, constantGUID, 2, 'UniversalVocabularyMt', vStrDef).
 2718exactlyAssertedEL_first(arity, consistent, 1, 'UniversalVocabularyMt', vStrDef).
 2719exactlyAssertedEL_first(arity, conceptuallyRelated, 2, 'UniversalVocabularyMt', vStrDef).
 2720exactlyAssertedEL_first(arity, completelyEnumerableCollection, 1, 'UniversalVocabularyMt', vStrDef).
 2721exactlyAssertedEL_first(arity, completelyDecidableCollection, 1, 'UniversalVocabularyMt', vStrDef).
 2722exactlyAssertedEL_first(arity, completeExtentEnumerableViaBackchain, 1, 'UniversalVocabularyMt', vStrDef).
 2723exactlyAssertedEL_first(arity, completeExtentEnumerableForValueInArg, 3, 'UniversalVocabularyMt', vStrDef).
 2724exactlyAssertedEL_first(arity, completeExtentEnumerableForArg, 2, 'UniversalVocabularyMt', vStrDef).
 2725exactlyAssertedEL_first(arity, completeExtentEnumerable, 1, 'UniversalVocabularyMt', vStrDef).
 2726exactlyAssertedEL_first(arity, completeExtentDecidableForValueInArg, 3, 'UniversalVocabularyMt', vStrDef).
 2727exactlyAssertedEL_first(arity, completeExtentDecidable, 1, 'UniversalVocabularyMt', vStrDef).
 2728exactlyAssertedEL_first(arity, completeExtentAssertedForValueInArg, 3, 'UniversalVocabularyMt', vStrDef).
 2729exactlyAssertedEL_first(arity, completeExtentAsserted, 1, 'UniversalVocabularyMt', vStrDef).
 2730exactlyAssertedEL_first(arity, comment, 2, 'UniversalVocabularyMt', vStrDef).
 2731exactlyAssertedEL_first(arity, collectionIsaBackchainRequired, 1, 'UniversalVocabularyMt', vStrDef).
 2732exactlyAssertedEL_first(arity, collectionIsaBackchainEncouraged, 1, 'UniversalVocabularyMt', vStrDef).
 2733exactlyAssertedEL_first(arity, collectionGenlsBackchainRequired, 1, 'UniversalVocabularyMt', vStrDef).
 2734exactlyAssertedEL_first(arity, collectionGenlsBackchainEncouraged, 1, 'UniversalVocabularyMt', vStrDef).
 2735exactlyAssertedEL_first(arity, collectionExpansion, 2, 'UniversalVocabularyMt', vStrDef).
 2736exactlyAssertedEL_first(arity, collectionConventionMt, 2, 'UniversalVocabularyMt', vStrDef).
 2737exactlyAssertedEL_first(arity, collectionCompletelyEnumerableViaBackchain, 1, 'UniversalVocabularyMt', vStrDef).
 2738exactlyAssertedEL_first(arity, collectionBackchainRequired, 1, 'UniversalVocabularyMt', vStrDef).
 2739exactlyAssertedEL_first(arity, collectionBackchainEncouraged, 1, 'UniversalVocabularyMt', vStrDef).
 2740exactlyAssertedEL_first(arity, coExtensional, 2, 'UniversalVocabularyMt', vStrDef).
 2741exactlyAssertedEL_first(arity, canonicalizerDirectiveForArgAndRest, 3, 'UniversalVocabularyMt', vStrDef).
 2742exactlyAssertedEL_first(arity, canonicalizerDirectiveForArg, 3, 'UniversalVocabularyMt', vStrDef).
 2743exactlyAssertedEL_first(arity, canonicalizerDirectiveForAllArgs, 2, 'UniversalVocabularyMt', vStrDef).
 2744exactlyAssertedEL_first(arity, backchainRequired, 1, 'UniversalVocabularyMt', vStrDef).
 2745exactlyAssertedEL_first(arity, backchainForbiddenWhenUnboundInArg, 2, 'UniversalVocabularyMt', vStrDef).
 2746exactlyAssertedEL_first(arity, backchainForbidden, 1, 'UniversalVocabularyMt', vStrDef).
 2747exactlyAssertedEL_first(arity, assertionUtility, 2, 'UniversalVocabularyMt', vStrDef).
 2748exactlyAssertedEL_first(arity, assertionDirection, 2, 'UniversalVocabularyMt', vStrDef).
 2749exactlyAssertedEL_first(arity, assertedTermSentences, 2, 'UniversalVocabularyMt', vStrDef).
 2750exactlyAssertedEL_first(arity, knownSentence, 1, 'UniversalVocabularyMt', vStrDef).
 2751exactlyAssertedEL_first(arity, assertedPredicateArg, 3, 'UniversalVocabularyMt', vStrDef).
 2752exactlyAssertedEL_first(arity, arityMin, 2, 'UniversalVocabularyMt', vStrDef).
 2753exactlyAssertedEL_first(arity, arityMax, 2, 'UniversalVocabularyMt', vStrDef).
 2754exactlyAssertedEL_first(arity, arity, 2, 'UniversalVocabularyMt', vStrDef).
 2755exactlyAssertedEL_first(arity, arity, 2, 'LogicalTruthMt', vStrDef).
 2756exactlyAssertedEL_first(arity, argsQuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2757exactlyAssertedEL_first(arity, argSometimesIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2758exactlyAssertedEL_first(arity, argsIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2759exactlyAssertedEL_first(arity, argsGenl, 2, 'UniversalVocabularyMt', vStrDef).
 2760exactlyAssertedEL_first(arity, argQuotedIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2761exactlyAssertedEL_first(arity, argIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2762exactlyAssertedEL_first(arity, argIsa, 3, 'LogicalTruthMt', vStrDef).
 2763exactlyAssertedEL_first(arity, argAndRestQuotedIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2764exactlyAssertedEL_first(arity, argAndRestIsa, 3, 'UniversalVocabularyMt', vStrDef).
 2765exactlyAssertedEL_first(arity, argAndRestIsa, 3, 'LogicalTruthMt', vStrDef).
 2766exactlyAssertedEL_first(arity, argAndRestGenl, 3, 'UniversalVocabularyMt', vStrDef).
 2767exactlyAssertedEL_first(arity, arg6SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2768exactlyAssertedEL_first(arity, arg6QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2769exactlyAssertedEL_first(arity, arg6Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2770exactlyAssertedEL_first(arity, arg6Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2771exactlyAssertedEL_first(arity, arg6Format, 2, 'UniversalVocabularyMt', vStrDef).
 2772exactlyAssertedEL_first(arity, arg5SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2773exactlyAssertedEL_first(arity, arg5QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2774exactlyAssertedEL_first(arity, arg5Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2775exactlyAssertedEL_first(arity, arg5Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2776exactlyAssertedEL_first(arity, arg5Format, 2, 'UniversalVocabularyMt', vStrDef).
 2777exactlyAssertedEL_first(arity, arg4SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2778exactlyAssertedEL_first(arity, arg4QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2779exactlyAssertedEL_first(arity, arg4Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2780exactlyAssertedEL_first(arity, arg4Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2781exactlyAssertedEL_first(arity, arg4Format, 2, 'UniversalVocabularyMt', vStrDef).
 2782exactlyAssertedEL_first(arity, arg3SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2783exactlyAssertedEL_first(arity, arg3QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2784exactlyAssertedEL_first(arity, arg3Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2785exactlyAssertedEL_first(arity, arg3Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2786exactlyAssertedEL_first(arity, arg3Format, 2, 'UniversalVocabularyMt', vStrDef).
 2787exactlyAssertedEL_first(arity, arg2SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2788exactlyAssertedEL_first(arity, arg2QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2789exactlyAssertedEL_first(arity, arg2Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2790exactlyAssertedEL_first(arity, arg2Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2791exactlyAssertedEL_first(arity, arg2Format, 2, 'UniversalVocabularyMt', vStrDef).
 2792exactlyAssertedEL_first(arity, arg1SometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2793exactlyAssertedEL_first(arity, arg1QuotedIsa, 2, 'UniversalVocabularyMt', vStrDef).
 2794exactlyAssertedEL_first(arity, arg1Isa, 2, 'UniversalVocabularyMt', vStrDef).
 2795exactlyAssertedEL_first(arity, arg1Genl, 2, 'UniversalVocabularyMt', vStrDef).
 2796exactlyAssertedEL_first(arity, arg1Format, 2, 'UniversalVocabularyMt', vStrDef).
 2797exactlyAssertedEL_first(arity, afterRemoving, 2, 'UniversalVocabularyMt', vStrDef).
 2798exactlyAssertedEL_first(arity, afterRemoving, 2, 'LogicalTruthImplementationMt', vStrDef).
 2799exactlyAssertedEL_first(arity, afterAdding, 2, 'UniversalVocabularyMt', vStrDef).
 2800exactlyAssertedEL_first(arity, afterAdding, 2, 'LogicalTruthImplementationMt', vStrDef).
 2801exactlyAssertedEL_first(arity, admittedSentence, 1, 'UniversalVocabularyMt', vStrDef).
 2802exactlyAssertedEL_first(arity, admittedNAT, 1, 'UniversalVocabularyMt', vStrDef).
 2803exactlyAssertedEL_first(arity, admittedArgument, 3, 'UniversalVocabularyMt', vStrDef).
 2804exactlyAssertedEL_first(arity, admittedAllArgument, 3, 'UniversalVocabularyMt', vStrDef).
 2805exactlyAssertedEL_first(arity, abnormal, 2, 'UniversalVocabularyMt', vStrDef).
 2806exactlyAssertedEL_first(arity, 'UnitProductFn', 2, 'UniversalVocabularyMt', vStrDef).
 2807exactlyAssertedEL_first(arity, 'UncanonicalizerAssertionFn', 1, 'UniversalVocabularyMt', vStrDef).
 2808exactlyAssertedEL_first(arity, 'TLVariableFn', 2, 'UniversalVocabularyMt', vStrDef).
 2809exactlyAssertedEL_first(arity, 'TLReifiedNatFn', 1, 'UniversalVocabularyMt', vStrDef).
 2810exactlyAssertedEL_first(arity, 'TLAssertionFn', 2, 'UniversalVocabularyMt', vStrDef).
 2811exactlyAssertedEL_first(arity, 'TheSetOf', 2, 'UniversalVocabularyMt', vStrDef).
 2812exactlyAssertedEL_first(arity, 'ThePrototypicalTransitiveBinaryPredicate', 2, 'UniversalVocabularyMt', vStrDef).
 2813exactlyAssertedEL_first(arity, 'ThePrototypicalBinaryPredicate', 2, 'UniversalVocabularyMt', vStrDef).
 2814exactlyAssertedEL_first(arity, 'TheCollectionOf', 2, 'UniversalVocabularyMt', vStrDef).
 2815exactlyAssertedEL_first(arity, 'substring-CaseInsensitive', 2, 'UniversalVocabularyMt', vStrDef).
 2816exactlyAssertedEL_first(arity, 'SubLQuoteFn', 1, 'UniversalVocabularyMt', vStrDef).
 2817exactlyAssertedEL_first(arity, 'SkolemFunctionFn', 3, 'UniversalVocabularyMt', vStrDef).
 2818exactlyAssertedEL_first(arity, 'SkolemFuncNFn', 4, 'UniversalVocabularyMt', vStrDef).
 2819exactlyAssertedEL_first(arity, 'RoundUpFn', 1, 'UniversalVocabularyMt', vStrDef).
 2820exactlyAssertedEL_first(arity, 'RoundDownFn', 1, 'UniversalVocabularyMt', vStrDef).
 2821exactlyAssertedEL_first(arity, 'RoundClosestFn', 1, 'UniversalVocabularyMt', vStrDef).
 2822exactlyAssertedEL_first(arity, 'RelationInstanceExistsFn', 3, 'UniversalVocabularyMt', vStrDef).
 2823exactlyAssertedEL_first(arity, 'RelationExistsInstanceFn', 3, 'UniversalVocabularyMt', vStrDef).
 2824exactlyAssertedEL_first(arity, 'RelationExistsAllFn', 4, 'UniversalVocabularyMt', vStrDef).
 2825exactlyAssertedEL_first(arity, 'RelationAllExistsFn', 4, 'UniversalVocabularyMt', vStrDef).
 2826exactlyAssertedEL_first(arity, 'QuotientFn', 2, 'UniversalVocabularyMt', vStrDef).
 2827exactlyAssertedEL_first(arity, 'Quote', 1, 'UniversalVocabularyMt', vStrDef).
 2828exactlyAssertedEL_first(arity, 'QuasiQuote', 1, 'UniversalVocabularyMt', vStrDef).
 2829exactlyAssertedEL_first(arity, 'QuantityConversionFn', 2, 'UniversalVocabularyMt', vStrDef).
 2830exactlyAssertedEL_first(arity, 'prettyString-Canonical', 2, 'UniversalVocabularyMt', vStrDef).
 2831exactlyAssertedEL_first(arity, 'PlusAll', 2, 'UniversalVocabularyMt', vStrDef).
 2832exactlyAssertedEL_first(arity, 'PerFn', 2, 'UniversalVocabularyMt', vStrDef).
 2833exactlyAssertedEL_first(arity, 'MtTimeWithGranularityDimFn', 2, 'UniversalVocabularyMt', vStrDef).
 2834exactlyAssertedEL_first(arity, 'MtTimeDimFn', 1, 'UniversalVocabularyMt', vStrDef).
 2835exactlyAssertedEL_first(arity, 'ModuloFn', 2, 'UniversalVocabularyMt', vStrDef).
 2836exactlyAssertedEL_first(arity, 'Minimum', 2, 'UniversalVocabularyMt', vStrDef).
 2837exactlyAssertedEL_first(arity, 'MeaningInSystemFn', 2, 'UniversalVocabularyMt', vStrDef).
 2838exactlyAssertedEL_first(arity, 'Maximum', 2, 'UniversalVocabularyMt', vStrDef).
 2839exactlyAssertedEL_first(arity, 'LogFn', 1, 'UniversalVocabularyMt', vStrDef).
 2840exactlyAssertedEL_first(arity, 'larkc-pluginByDataConnectsTo', 2, 'UniversalVocabularyMt', vStrDef).
 2841exactlyAssertedEL_first(arity, 'larkc-hasUri', 2, 'UniversalVocabularyMt', vStrDef).
 2842exactlyAssertedEL_first(arity, 'larkc-hasScalability', 2, 'UniversalVocabularyMt', vStrDef).
 2843exactlyAssertedEL_first(arity, 'larkc-hasOutputType', 2, 'UniversalVocabularyMt', vStrDef).
 2844exactlyAssertedEL_first(arity, 'larkc-hasInputType', 2, 'UniversalVocabularyMt', vStrDef).
 2845exactlyAssertedEL_first(arity, 'larkc-hasEndpoint', 2, 'UniversalVocabularyMt', vStrDef).
 2846exactlyAssertedEL_first(arity, 'larkc-hasCostPerInvocation', 2, 'UniversalVocabularyMt', vStrDef).
 2847exactlyAssertedEL_first(arity, 'Kappa', 2, 'UniversalVocabularyMt', vStrDef).
 2848exactlyAssertedEL_first(arity, 'ist-Asserted', 2, 'UniversalVocabularyMt', vStrDef).
 2849exactlyAssertedEL_first(arity, 'IntervalMinFn', 1, 'UniversalVocabularyMt', vStrDef).
 2850exactlyAssertedEL_first(arity, 'IntervalMaxFn', 1, 'UniversalVocabularyMt', vStrDef).
 2851exactlyAssertedEL_first(arity, 'interArgIsa5-4', 3, 'UniversalVocabularyMt', vStrDef).
 2852exactlyAssertedEL_first(arity, 'interArgIsa5-3', 3, 'UniversalVocabularyMt', vStrDef).
 2853exactlyAssertedEL_first(arity, 'interArgIsa5-2', 3, 'UniversalVocabularyMt', vStrDef).
 2854exactlyAssertedEL_first(arity, 'interArgIsa5-1', 3, 'UniversalVocabularyMt', vStrDef).
 2855exactlyAssertedEL_first(arity, 'interArgIsa4-5', 3, 'UniversalVocabularyMt', vStrDef).
 2856exactlyAssertedEL_first(arity, 'interArgIsa4-3', 3, 'UniversalVocabularyMt', vStrDef).
 2857exactlyAssertedEL_first(arity, 'interArgIsa4-2', 3, 'UniversalVocabularyMt', vStrDef).
 2858exactlyAssertedEL_first(arity, 'interArgIsa4-1', 3, 'UniversalVocabularyMt', vStrDef).
 2859exactlyAssertedEL_first(arity, 'interArgIsa3-5', 3, 'UniversalVocabularyMt', vStrDef).
 2860exactlyAssertedEL_first(arity, 'interArgIsa3-4', 3, 'UniversalVocabularyMt', vStrDef).
 2861exactlyAssertedEL_first(arity, 'interArgIsa3-2', 3, 'UniversalVocabularyMt', vStrDef).
 2862exactlyAssertedEL_first(arity, 'interArgIsa3-1', 3, 'UniversalVocabularyMt', vStrDef).
 2863exactlyAssertedEL_first(arity, 'interArgIsa2-5', 3, 'UniversalVocabularyMt', vStrDef).
 2864exactlyAssertedEL_first(arity, 'interArgIsa2-4', 3, 'UniversalVocabularyMt', vStrDef).
 2865exactlyAssertedEL_first(arity, 'interArgIsa2-3', 3, 'UniversalVocabularyMt', vStrDef).
 2866exactlyAssertedEL_first(arity, 'interArgIsa2-1', 3, 'UniversalVocabularyMt', vStrDef).
 2867exactlyAssertedEL_first(arity, 'interArgIsa1-5', 3, 'UniversalVocabularyMt', vStrDef).
 2868exactlyAssertedEL_first(arity, 'interArgIsa1-4', 3, 'UniversalVocabularyMt', vStrDef).
 2869exactlyAssertedEL_first(arity, 'interArgIsa1-3', 3, 'UniversalVocabularyMt', vStrDef).
 2870exactlyAssertedEL_first(arity, 'interArgIsa1-2', 3, 'UniversalVocabularyMt', vStrDef).
 2871exactlyAssertedEL_first(arity, 'interArgGenl1-2', 3, 'UniversalVocabularyMt', vStrDef).
 2872exactlyAssertedEL_first(arity, 'interArgFormat1-2', 3, 'UniversalVocabularyMt', vStrDef).
 2873exactlyAssertedEL_first(arity, 'genls-SpecDenotesGenlInstances', 2, 'UniversalVocabularyMt', vStrDef).
 2874exactlyAssertedEL_first(arity, 'genls-GenlDenotesSpecInstances', 2, 'UniversalVocabularyMt', vStrDef).
 2875exactlyAssertedEL_first(arity, 'FunctionToArg', 2, 'UniversalVocabularyMt', vStrDef).
 2876exactlyAssertedEL_first(arity, 'FormulaArityFn', 1, 'UniversalVocabularyMt', vStrDef).
 2877exactlyAssertedEL_first(arity, 'FormulaArgSetFn', 1, 'UniversalVocabularyMt', vStrDef).
 2878exactlyAssertedEL_first(arity, 'FormulaArgListFn', 1, 'UniversalVocabularyMt', vStrDef).
 2879exactlyAssertedEL_first(arity, 'FormulaArgFn', 2, 'UniversalVocabularyMt', vStrDef).
 2880exactlyAssertedEL_first(arity, 'FOL-TermFn', 1, 'UniversalVocabularyMt', vStrDef).
 2881exactlyAssertedEL_first(arity, 'FOL-PredicateFn', 2, 'UniversalVocabularyMt', vStrDef).
 2882exactlyAssertedEL_first(arity, 'FOL-FunctionFn', 2, 'UniversalVocabularyMt', vStrDef).
 2883exactlyAssertedEL_first(arity, 'ExpFn', 1, 'UniversalVocabularyMt', vStrDef).
 2884exactlyAssertedEL_first(arity, 'ExpandSubLFn', 2, 'UniversalVocabularyMt', vStrDef).
 2885exactlyAssertedEL_first(arity, 'EvaluateSubLFn', 1, 'UniversalVocabularyMt', vStrDef).
 2886exactlyAssertedEL_first(arity, 'EscapeQuote', 1, 'UniversalVocabularyMt', vStrDef).
 2887exactlyAssertedEL_first(arity, 'equalStrings-CaseInsensitive', 2, 'UniversalVocabularyMt', vStrDef).
 2888exactlyAssertedEL_first(arity, 'DifferenceFn', 2, 'UniversalVocabularyMt', vStrDef).
 2889exactlyAssertedEL_first(arity, 'DateEncodeStringFn', 2, 'UniversalVocabularyMt', vStrDef).
 2890exactlyAssertedEL_first(arity, 'DateDecodeStringFn', 2, 'UniversalVocabularyMt', vStrDef).
 2891exactlyAssertedEL_first(arity, 'CycTacticFn', 2, 'UniversalVocabularyMt', vStrDef).
 2892exactlyAssertedEL_first(arity, 'CycProofFn', 2, 'UniversalVocabularyMt', vStrDef).
 2893exactlyAssertedEL_first(arity, 'CycProblemStoreFn', 1, 'UniversalVocabularyMt', vStrDef).
 2894exactlyAssertedEL_first(arity, 'CycProblemLinkFn', 2, 'UniversalVocabularyMt', vStrDef).
 2895exactlyAssertedEL_first(arity, 'CycProblemFn', 2, 'UniversalVocabularyMt', vStrDef).
 2896exactlyAssertedEL_first(arity, 'CycInferenceFn', 2, 'UniversalVocabularyMt', vStrDef).
 2897exactlyAssertedEL_first(arity, 'CollectionRuleTemplateFn', 1, 'UniversalVocabularyMt', vStrDef).
 2898exactlyAssertedEL_first(arity, 'Average', 2, 'UniversalVocabularyMt', vStrDef).
 2899exactlyAssertedEL_first(arity, 'assertionUtility-1', 2, 'UniversalVocabularyMt', vStrDef).
 2900exactlyAssertedEL_first(arity, 'AbsoluteValueFn', 1, 'UniversalVocabularyMt', vStrDef).
 2901
 2902exactlyAssertedEL_next(resultQuotedIsa, 'RelationInstanceExistsFn', 'IndeterminateTerm', 'BaseKB', vStrDef).
 2903exactlyAssertedEL_next(resultQuotedIsa, 'RelationExistsInstanceFn', 'IndeterminateTerm', 'BaseKB', vStrDef).
 2904exactlyAssertedEL_next(resultQuotedIsa, 'RelationExistsAllFn', 'IndeterminateTerm', 'BaseKB', vStrDef).
 2905exactlyAssertedEL_next(resultQuotedIsa, 'RelationAllExistsFn', 'IndeterminateTerm', 'BaseKB', vStrDef).
 2906exactlyAssertedEL_next(resultIsaArgIsa, 'IntervalMinFn', 1, 'UniversalVocabularyMt', vStrDef).
 2907exactlyAssertedEL_next(resultIsaArgIsa, 'IntervalMaxFn', 1, 'UniversalVocabularyMt', vStrDef).
 2908exactlyAssertedEL_next(resultIsaArg, 'RelationInstanceExistsFn', 3, 'UniversalVocabularyMt', vStrMon).
 2909exactlyAssertedEL_next(resultIsaArg, 'RelationExistsInstanceFn', 2, 'UniversalVocabularyMt', vStrMon).
 2910exactlyAssertedEL_next(resultIsaArg, 'RelationExistsAllFn', 3, 'UniversalVocabularyMt', vStrMon).
 2911exactlyAssertedEL_next(resultIsaArg, 'RelationAllExistsFn', 4, 'UniversalVocabularyMt', vStrMon).
 2912exactlyAssertedEL_next(resultIsa, 'Unity', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2913exactlyAssertedEL_next(resultIsa, 'UnitProductFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 2914exactlyAssertedEL_next(resultIsa, 'UncanonicalizerAssertionFn', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2915exactlyAssertedEL_next(resultIsa, 'TLVariableFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2916exactlyAssertedEL_next(resultIsa, 'TLVariableFn', 'SubLAtom', 'UniversalVocabularyMt', vStrDef).
 2917exactlyAssertedEL_next(resultIsa, 'TLReifiedNatFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2918exactlyAssertedEL_next(resultIsa, 'TLReifiedNatFn', 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 2919exactlyAssertedEL_next(resultIsa, 'TLAssertionFn', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 2920exactlyAssertedEL_next(resultIsa, 'TimesFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2921exactlyAssertedEL_next(resultIsa, 'TheSetOf', 'Set-Mathematical', 'UniversalVocabularyMt', vStrDef).
 2922exactlyAssertedEL_next(resultIsa, 'TheSet', 'Set-Mathematical', 'UniversalVocabularyMt', vStrDef).
 2923exactlyAssertedEL_next(resultIsa, 'TheList', 'List', 'UniversalVocabularyMt', vStrDef).
 2924exactlyAssertedEL_next(resultIsa, 'TheCollectionOf', tCol, 'UniversalVocabularyMt', vStrDef).
 2925exactlyAssertedEL_next(resultIsa, 'SkolemFunctionFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2926exactlyAssertedEL_next(resultIsa, 'SkolemFuncNFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2927exactlyAssertedEL_next(resultIsa, 'RoundUpFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2928exactlyAssertedEL_next(resultIsa, 'RoundDownFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2929exactlyAssertedEL_next(resultIsa, 'RoundClosestFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2930exactlyAssertedEL_next(resultIsa, 'RelationInstanceExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2931exactlyAssertedEL_next(resultIsa, 'RelationExistsInstanceFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2932exactlyAssertedEL_next(resultIsa, 'RelationExistsAllFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2933exactlyAssertedEL_next(resultIsa, 'RelationAllExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2934exactlyAssertedEL_next(resultIsa, 'QuotientFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2935exactlyAssertedEL_next(resultIsa, 'Quote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2936exactlyAssertedEL_next(resultIsa, 'Quote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2937exactlyAssertedEL_next(resultIsa, 'Quote', 'CycLTerm', 'LogicalTruthImplementationMt', vStrDef).
 2938exactlyAssertedEL_next(resultIsa, 'QuasiQuote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2939exactlyAssertedEL_next(resultIsa, 'QuasiQuote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2940exactlyAssertedEL_next(resultIsa, 'QuasiQuote', 'CycLTerm', 'LogicalTruthImplementationMt', vStrDef).
 2941exactlyAssertedEL_next(resultIsa, 'QuantityConversionFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2942exactlyAssertedEL_next(resultIsa, 'PlusFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2943exactlyAssertedEL_next(resultIsa, 'PlusAll', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2944exactlyAssertedEL_next(resultIsa, 'PerFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 2945exactlyAssertedEL_next(resultIsa, 'Percent', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2946exactlyAssertedEL_next(resultIsa, 'MtUnionFn', 'ProblemSolvingCntxt', 'UniversalVocabularyMt', vStrDef).
 2947exactlyAssertedEL_next(resultIsa, 'MtTimeWithGranularityDimFn', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2948exactlyAssertedEL_next(resultIsa, 'MtTimeDimFn', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2949exactlyAssertedEL_next(resultIsa, 'MtSpace', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 2950exactlyAssertedEL_next(resultIsa, 'ModuloFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2951exactlyAssertedEL_next(resultIsa, 'MinRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2952exactlyAssertedEL_next(resultIsa, 'Minimum', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2953exactlyAssertedEL_next(resultIsa, 'MeaningInSystemFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2954exactlyAssertedEL_next(resultIsa, 'MaxRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2955exactlyAssertedEL_next(resultIsa, 'Maximum', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2956exactlyAssertedEL_next(resultIsa, 'LogFn', 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 2957exactlyAssertedEL_next(resultIsa, 'Kappa', tPred, 'UniversalVocabularyMt', vStrDef).
 2958exactlyAssertedEL_next(resultIsa, 'IntervalMinFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2959exactlyAssertedEL_next(resultIsa, 'IntervalMaxFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2960exactlyAssertedEL_next(resultIsa, 'FunctionToArg', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 2961exactlyAssertedEL_next(resultIsa, 'FormulaArityFn', 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 2962exactlyAssertedEL_next(resultIsa, 'FormulaArgSetFn', 'Set-Mathematical', 'UniversalVocabularyMt', vStrDef).
 2963exactlyAssertedEL_next(resultIsa, 'FormulaArgListFn', 'List', 'UniversalVocabularyMt', vStrDef).
 2964exactlyAssertedEL_next(resultIsa, 'FormulaArgFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2965exactlyAssertedEL_next(resultIsa, 'FOL-TermFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2966exactlyAssertedEL_next(resultIsa, 'FOL-PredicateFn', tPred, 'UniversalVocabularyMt', vStrDef).
 2967exactlyAssertedEL_next(resultIsa, 'FOL-FunctionFn', tFunction, 'UniversalVocabularyMt', vStrDef).
 2968exactlyAssertedEL_next(resultIsa, 'ExpFn', 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 2969exactlyAssertedEL_next(resultIsa, 'EvaluateSubLFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2970exactlyAssertedEL_next(resultIsa, 'EscapeQuote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2971exactlyAssertedEL_next(resultIsa, 'EscapeQuote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 2972exactlyAssertedEL_next(resultIsa, 'EscapeQuote', 'CycLTerm', 'LogicalTruthImplementationMt', vStrDef).
 2973exactlyAssertedEL_next(resultIsa, 'DifferenceFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2974exactlyAssertedEL_next(resultIsa, 'DateEncodeStringFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 2975exactlyAssertedEL_next(resultIsa, 'DateDecodeStringFn', 'Individual', 'UniversalVocabularyMt', vStrDef).
 2976exactlyAssertedEL_next(resultIsa, 'CycTacticFn', 'CycTactic', 'UniversalVocabularyMt', vStrDef).
 2977exactlyAssertedEL_next(resultIsa, 'CycProofFn', 'CycProof', 'UniversalVocabularyMt', vStrDef).
 2978exactlyAssertedEL_next(resultIsa, 'CycProblemStoreFn', 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 2979exactlyAssertedEL_next(resultIsa, 'CycProblemLinkFn', 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 2980exactlyAssertedEL_next(resultIsa, 'CycProblemFn', 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 2981exactlyAssertedEL_next(resultIsa, 'CycInferenceFn', 'CycInference', 'UniversalVocabularyMt', vStrDef).
 2982exactlyAssertedEL_next(resultIsa, 'CollectionRuleTemplateFn', 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 2983exactlyAssertedEL_next(resultIsa, 'Average', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2984exactlyAssertedEL_next(resultIsa, 'AbsoluteValueFn', 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2985
 2986exactlyAssertedEL_first(argsQuotedIsa, or, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 2987exactlyAssertedEL_first(argsQuotedIsa, or, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 2988exactlyAssertedEL_first(argsQuotedIsa, differentSymbols, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 2989exactlyAssertedEL_first(argsQuotedIsa, and, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 2990exactlyAssertedEL_first(argsQuotedIsa, and, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 2991exactlyAssertedEL_first(argsIsa, different, 'Thing', 'UniversalVocabularyMt', vStrDef).
 2992exactlyAssertedEL_first(argsIsa, defaultReformulatorModePrecedence, 'Individual', 'UniversalVocabularyMt', vStrDef).
 2993exactlyAssertedEL_first(argsIsa, 'Unity', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2994exactlyAssertedEL_first(argsIsa, 'TimesFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2995exactlyAssertedEL_first(argsIsa, 'TheSet', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2996exactlyAssertedEL_first(argsIsa, 'TheList', 'Thing', 'UniversalVocabularyMt', vStrDef).
 2997exactlyAssertedEL_first(argsIsa, 'PlusFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2998exactlyAssertedEL_first(argsIsa, 'Percent', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 2999exactlyAssertedEL_first(argsIsa, 'MtUnionFn', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3000exactlyAssertedEL_first(argsIsa, 'MtSpace', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3001exactlyAssertedEL_first(argsIsa, 'MinRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3002exactlyAssertedEL_first(argsIsa, 'MaxRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3003
 3004exactlyAssertedEL_next(quotedIsa, unknownSentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3005exactlyAssertedEL_next(quotedIsa, trueSentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3006exactlyAssertedEL_next(quotedIsa, transitiveViaArgInverse, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3007exactlyAssertedEL_next(quotedIsa, transitiveViaArg, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3008exactlyAssertedEL_next(quotedIsa, transitiveViaArg, tPred, 'UniversalVocabularyMt', vStrDef).
 3009exactlyAssertedEL_next(quotedIsa, termOfUnit, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3010exactlyAssertedEL_next(quotedIsa, termExternalIDString, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3011exactlyAssertedEL_next(quotedIsa, termChosen, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3012exactlyAssertedEL_next(quotedIsa, subsetOf, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3013exactlyAssertedEL_next(quotedIsa, skolemizeForward, 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3014exactlyAssertedEL_next(quotedIsa, siblingDisjointExceptions, tPred, 'UniversalVocabularyMt', vStrDef).
 3015exactlyAssertedEL_next(quotedIsa, sentenceImplies, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3016exactlyAssertedEL_next(quotedIsa, sentenceEquiv, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3017exactlyAssertedEL_next(quotedIsa, ruleAfterRemoving, tPred, 'UniversalVocabularyMt', vStrDef).
 3018exactlyAssertedEL_next(quotedIsa, ruleAfterAdding, tPred, 'UniversalVocabularyMt', vStrDef).
 3019exactlyAssertedEL_next(quotedIsa, relationInstanceExists, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3020exactlyAssertedEL_next(quotedIsa, relationInstanceAll, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3021exactlyAssertedEL_next(quotedIsa, relationExistsInstance, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3022exactlyAssertedEL_next(quotedIsa, relationExistsAll, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3023exactlyAssertedEL_next(quotedIsa, relationAllInstance, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3024exactlyAssertedEL_next(quotedIsa, relationAllExists, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3025exactlyAssertedEL_next(quotedIsa, relationAll, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3026exactlyAssertedEL_next(quotedIsa, quotedIsa, 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3027exactlyAssertedEL_next(quotedIsa, quotedArgument, tPred, 'UniversalVocabularyMt', vStrDef).
 3028exactlyAssertedEL_next(quotedIsa, pragmaticRequirement, 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3029exactlyAssertedEL_next(quotedIsa, performSubL, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3030exactlyAssertedEL_next(quotedIsa, operatorFormulas, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3031exactlyAssertedEL_next(quotedIsa, nthSmallestElement, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3032exactlyAssertedEL_next(quotedIsa, nthLargestElement, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3033exactlyAssertedEL_next(quotedIsa, negationPreds, 'TransformationModuleSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3034exactlyAssertedEL_next(quotedIsa, negationPreds, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3035exactlyAssertedEL_next(quotedIsa, negationPreds, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3036exactlyAssertedEL_next(quotedIsa, negationInverse, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3037exactlyAssertedEL_next(quotedIsa, nearestIsa, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3038exactlyAssertedEL_next(quotedIsa, nearestGenls, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3039exactlyAssertedEL_next(quotedIsa, nearestGenlPreds, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3040exactlyAssertedEL_next(quotedIsa, nearestGenlMt, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3041exactlyAssertedEL_next(quotedIsa, nearestDifferentIsa, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3042exactlyAssertedEL_next(quotedIsa, nearestDifferentGenls, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3043exactlyAssertedEL_next(quotedIsa, nearestCommonSpecs, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3044exactlyAssertedEL_next(quotedIsa, nearestCommonIsa, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3045exactlyAssertedEL_next(quotedIsa, nearestCommonGenls, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3046exactlyAssertedEL_next(quotedIsa, nearestCommonGenlMt, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3047exactlyAssertedEL_next(quotedIsa, natFunction, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3048exactlyAssertedEL_next(quotedIsa, natArgumentsEqual, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3049exactlyAssertedEL_next(quotedIsa, natArgument, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3050exactlyAssertedEL_next(quotedIsa, myCreator, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3051exactlyAssertedEL_next(quotedIsa, myCreator, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3052exactlyAssertedEL_next(quotedIsa, myCreationTime, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3053exactlyAssertedEL_next(quotedIsa, myCreationTime, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3054exactlyAssertedEL_next(quotedIsa, myCreationSecond, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3055exactlyAssertedEL_next(quotedIsa, myCreationSecond, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3056exactlyAssertedEL_next(quotedIsa, myCreationPurpose, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3057exactlyAssertedEL_next(quotedIsa, myCreationPurpose, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3058exactlyAssertedEL_next(quotedIsa, minQuantValue, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3059exactlyAssertedEL_next(quotedIsa, minimizeExtent, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3060exactlyAssertedEL_next(quotedIsa, maxQuantValue, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3061exactlyAssertedEL_next(quotedIsa, knownSentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3062exactlyAssertedEL_next(quotedIsa, ist, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3063exactlyAssertedEL_next(quotedIsa, isa, 'TransformationModuleSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3064exactlyAssertedEL_next(quotedIsa, isa, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3065exactlyAssertedEL_next(quotedIsa, isa, tPred, 'UniversalVocabularyMt', vStrDef).
 3066exactlyAssertedEL_next(quotedIsa, interArgDifferent, tPred, 'UniversalVocabularyMt', vStrDef).
 3067exactlyAssertedEL_next(quotedIsa, integerBetween, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3068exactlyAssertedEL_next(quotedIsa, indexicalReferent, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3069exactlyAssertedEL_next(quotedIsa, hlPrototypicalInstance, 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3070exactlyAssertedEL_next(quotedIsa, genls, 'TransformationModuleSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3071exactlyAssertedEL_next(quotedIsa, genls, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3072exactlyAssertedEL_next(quotedIsa, genls, tPred, 'UniversalVocabularyMt', vStrDef).
 3073exactlyAssertedEL_next(quotedIsa, genlPreds, 'TransformationModuleSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3074exactlyAssertedEL_next(quotedIsa, genlPreds, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3075exactlyAssertedEL_next(quotedIsa, genlPreds, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3076exactlyAssertedEL_next(quotedIsa, genlPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 3077exactlyAssertedEL_next(quotedIsa, genlMt, 'TransformationModuleSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3078exactlyAssertedEL_next(quotedIsa, genlMt, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3079exactlyAssertedEL_next(quotedIsa, genlInverse, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3080exactlyAssertedEL_next(quotedIsa, genlInverse, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3081exactlyAssertedEL_next(quotedIsa, genlInverse, tPred, 'UniversalVocabularyMt', vStrDef).
 3082exactlyAssertedEL_next(quotedIsa, forwardNonTriggerLiteral, 'InferenceSupportedPredicate', 'UniversalVocabularyMt', vStrDef).
 3083exactlyAssertedEL_next(quotedIsa, formulaArity, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3084exactlyAssertedEL_next(quotedIsa, extentCardinality, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3085exactlyAssertedEL_next(quotedIsa, exactlyAssertedEL_next, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3086exactlyAssertedEL_next(quotedIsa, evaluationDefn, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3087exactlyAssertedEL_next(quotedIsa, evaluate, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3088exactlyAssertedEL_next(quotedIsa, equalSymbols, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3089exactlyAssertedEL_next(quotedIsa, equals, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3090exactlyAssertedEL_next(quotedIsa, elInverse, tPred, 'UniversalVocabularyMt', vStrDef).
 3091exactlyAssertedEL_next(quotedIsa, elementOf, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3092exactlyAssertedEL_next(quotedIsa, disjointWith, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3093exactlyAssertedEL_next(quotedIsa, disjointWith, tPred, 'UniversalVocabularyMt', vStrDef).
 3094exactlyAssertedEL_next(quotedIsa, differentSymbols, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3095exactlyAssertedEL_next(quotedIsa, (different), 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3096exactlyAssertedEL_next(quotedIsa, cycTransformationProofRule, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3097exactlyAssertedEL_next(quotedIsa, cycTransformationProofBindings, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3098exactlyAssertedEL_next(quotedIsa, cycProblemStoreTerms, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3099exactlyAssertedEL_next(quotedIsa, cycProblemStoreProofCount, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3100exactlyAssertedEL_next(quotedIsa, cycProblemStoreProblems, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3101exactlyAssertedEL_next(quotedIsa, cycProblemStoreProblemCount, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3102exactlyAssertedEL_next(quotedIsa, cycProblemStoreLinkCount, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3103exactlyAssertedEL_next(quotedIsa, cycProblemStoreInferenceCount, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3104exactlyAssertedEL_next(quotedIsa, cycProblemQueryTerms, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3105exactlyAssertedEL_next(quotedIsa, cycProblemQuerySentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3106exactlyAssertedEL_next(quotedIsa, cycProblemProvabilityStatus, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3107exactlyAssertedEL_next(quotedIsa, constantName, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3108exactlyAssertedEL_next(quotedIsa, constantID, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3109exactlyAssertedEL_next(quotedIsa, constantGUID, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3110exactlyAssertedEL_next(quotedIsa, consistent, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3111exactlyAssertedEL_next(quotedIsa, conceptuallyRelated, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3112exactlyAssertedEL_next(quotedIsa, completeExtentEnumerableForValueInArg, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3113exactlyAssertedEL_next(quotedIsa, completeExtentEnumerableForArg, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3114exactlyAssertedEL_next(quotedIsa, completeExtentEnumerable, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3115exactlyAssertedEL_next(quotedIsa, completeExtentDecidableForValueInArg, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3116exactlyAssertedEL_next(quotedIsa, completeExtentDecidable, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3117exactlyAssertedEL_next(quotedIsa, completeExtentAssertedForValueInArg, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3118exactlyAssertedEL_next(quotedIsa, completeExtentAsserted, 'RemovalModuleSupportedPredicate-Generic', 'UniversalVocabularyMt', vStrDef).
 3119exactlyAssertedEL_next(quotedIsa, comment, tPred, 'UniversalVocabularyMt', vStrDef).
 3120exactlyAssertedEL_next(quotedIsa, assertionDirection, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3121exactlyAssertedEL_next(quotedIsa, assertedTermSentences, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3122exactlyAssertedEL_next(quotedIsa, knownSentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3123exactlyAssertedEL_next(quotedIsa, assertedPredicateArg, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3124exactlyAssertedEL_next(quotedIsa, arityMax, tPred, 'UniversalVocabularyMt', vStrDef).
 3125exactlyAssertedEL_next(quotedIsa, arity, tPred, 'UniversalVocabularyMt', vStrDef).
 3126exactlyAssertedEL_next(quotedIsa, argAndRestIsa, tPred, 'UniversalVocabularyMt', vStrDef).
 3127exactlyAssertedEL_next(quotedIsa, afterAdding, tPred, 'UniversalVocabularyMt', vStrDef).
 3128exactlyAssertedEL_next(quotedIsa, admittedSentence, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3129exactlyAssertedEL_next(quotedIsa, admittedArgument, 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3130exactlyAssertedEL_next(quotedIsa, 'True', 'CycLTruthValueSentence', 'UniversalVocabularyMt', vStrDef).
 3131exactlyAssertedEL_next(quotedIsa, 'True', 'CycLTruthValueSentence', 'CoreCycLMt', vStrDef).
 3132exactlyAssertedEL_next(quotedIsa, 'True', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3133exactlyAssertedEL_next(quotedIsa, 'TransitiveBinaryPredicate', 'RemovalModuleSupportedCollection-Generic', 'UniversalVocabularyMt', vStrDef).
 3134exactlyAssertedEL_next(quotedIsa, 'TheUser', 'TheTerm', 'UniversalVocabularyMt', vStrDef).
 3135exactlyAssertedEL_next(quotedIsa, 'ThePrototypicalTransitiveBinaryPredicate', 'HLPrototypicalTerm', 'UniversalVocabularyMt', vStrDef).
 3136exactlyAssertedEL_next(quotedIsa, 'ThePrototypicalCollection', 'HLPrototypicalTerm', 'UniversalVocabularyMt', vStrDef).
 3137exactlyAssertedEL_next(quotedIsa, 'ThePrototypicalBinaryPredicate', 'HLPrototypicalTerm', 'UniversalVocabularyMt', vStrDef).
 3138exactlyAssertedEL_next(quotedIsa, 'TheCollectionOf', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 3139exactlyAssertedEL_next(quotedIsa, 'SymmetricBinaryPredicate', 'TransformationModuleSupportedCollection', 'UniversalVocabularyMt', vStrDef).
 3140exactlyAssertedEL_next(quotedIsa, 'SymmetricBinaryPredicate', 'RemovalModuleSupportedCollection-Generic', 'UniversalVocabularyMt', vStrDef).
 3141exactlyAssertedEL_next(quotedIsa, 'SubLPositiveInteger', 'InferenceSupportedCollection', 'UniversalVocabularyMt', vStrDef).
 3142exactlyAssertedEL_next(quotedIsa, 'ReflexiveBinaryPredicate', 'RemovalModuleSupportedCollection-Generic', 'UniversalVocabularyMt', vStrDef).
 3143exactlyAssertedEL_next(quotedIsa, 'Quote', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 3144exactlyAssertedEL_next(quotedIsa, 'Quote', 'CycLExpression', 'LogicalTruthMt', vStrDef).
 3145exactlyAssertedEL_next(quotedIsa, 'QueryMt', 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 3146exactlyAssertedEL_next(quotedIsa, 'QuasiQuote', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 3147exactlyAssertedEL_next(quotedIsa, 'Kappa', 'InferenceSupportedFunction', 'UniversalVocabularyMt', vStrDef).
 3148exactlyAssertedEL_next(quotedIsa, 'ist-Asserted', 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3149exactlyAssertedEL_next(quotedIsa, 'IrreflexiveBinaryPredicate', 'RemovalModuleSupportedCollection-Generic', 'UniversalVocabularyMt', vStrDef).
 3150exactlyAssertedEL_next(quotedIsa, 'Guest', 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 3151exactlyAssertedEL_next(quotedIsa, 'genls-SpecDenotesGenlInstances', tPred, 'UniversalVocabularyMt', vStrDef).
 3152exactlyAssertedEL_next(quotedIsa, 'genls-GenlDenotesSpecInstances', tPred, 'UniversalVocabularyMt', vStrDef).
 3153exactlyAssertedEL_next(quotedIsa, 'False', 'CycLTruthValueSentence', 'UniversalVocabularyMt', vStrDef).
 3154exactlyAssertedEL_next(quotedIsa, 'False', 'CycLTruthValueSentence', 'CoreCycLMt', vStrDef).
 3155exactlyAssertedEL_next(quotedIsa, 'EscapeQuote', 'InferenceSupportedTerm', 'UniversalVocabularyMt', vStrDef).
 3156exactlyAssertedEL_next(quotedIsa, 'EscapeQuote', 'CycLExpression', 'LogicalTruthMt', vStrDef).
 3157exactlyAssertedEL_next(quotedIsa, 'equalStrings-CaseInsensitive', 'RemovalModuleSupportedPredicate-Specific', 'UniversalVocabularyMt', vStrDef).
 3158exactlyAssertedEL_next(quotedIsa, 'DocumentationPredicate', 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3159exactlyAssertedEL_next(quotedIsa, 'CycAdministrator', 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 3160exactlyAssertedEL_next(quotedIsa, 'AsymmetricBinaryPredicate', 'TransformationModuleSupportedCollection', 'UniversalVocabularyMt', vStrDef).
 3161exactlyAssertedEL_next(quotedIsa, 'AsymmetricBinaryPredicate', 'RemovalModuleSupportedCollection-Generic', 'UniversalVocabularyMt', vStrDef).
 3162
 3163exactlyAssertedEL_next(quotedDefnIff, 'SubLSymbol', 'SubLQuoteFn'('SYMBOLP'), 'UniversalVocabularyMt', vStrDef).
 3164exactlyAssertedEL_next(quotedDefnIff, 'SubLSymbol', 'SubLQuoteFn'('SYMBOLP'), 'LogicalTruthImplementationMt', vStrDef).
 3165exactlyAssertedEL_next(quotedDefnIff, 'SubLString', 'SubLQuoteFn'('CYC-SYSTEM-STRING-P'), 'UniversalVocabularyMt', vStrDef).
 3166exactlyAssertedEL_next(quotedDefnIff, 'SubLSExpression', 'SubLQuoteFn'('CYC-SUBL-EXPRESSION'), 'UniversalVocabularyMt', vStrDef).
 3167exactlyAssertedEL_next(quotedDefnIff, 'SubLRealNumber', 'SubLQuoteFn'('CYC-SYSTEM-REAL-NUMBER-P'), 'UniversalVocabularyMt', vStrDef).
 3168exactlyAssertedEL_next(quotedDefnIff, 'SubLPositiveInteger', 'SubLQuoteFn'('CYC-POSITIVE-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 3169exactlyAssertedEL_next(quotedDefnIff, 'SubLPositiveInteger', 'SubLQuoteFn'('CYC-POSITIVE-INTEGER'), 'LogicalTruthImplementationMt', vStrDef).
 3170exactlyAssertedEL_next(quotedDefnIff, 'SubLNonVariableSymbol', 'SubLQuoteFn'('CYC-SYSTEM-NON-VARIABLE-SYMBOL-P'), 'UniversalVocabularyMt', vStrDef).
 3171exactlyAssertedEL_next(quotedDefnIff, 'SubLNonVariableNonKeywordSymbol', 'SubLQuoteFn'('SUBL-NON-VARIABLE-NON-KEYWORD-SYMBOL-P'), 'UniversalVocabularyMt', vStrDef).
 3172exactlyAssertedEL_next(quotedDefnIff, 'SubLNonNegativeInteger', 'SubLQuoteFn'('CYC-NON-NEGATIVE-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 3173exactlyAssertedEL_next(quotedDefnIff, 'SubLNonNegativeInteger', 'SubLQuoteFn'('CYC-NON-NEGATIVE-INTEGER'), 'LogicalTruthImplementationMt', vStrDef).
 3174exactlyAssertedEL_next(quotedDefnIff, 'SubLList', 'SubLQuoteFn'('LISTP'), 'UniversalVocabularyMt', vStrDef).
 3175exactlyAssertedEL_next(quotedDefnIff, 'SubLKeyword', 'SubLQuoteFn'('KEYWORDP'), 'UniversalVocabularyMt', vStrDef).
 3176exactlyAssertedEL_next(quotedDefnIff, 'SubLInteger', 'SubLQuoteFn'('CYC-SYSTEM-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 3177exactlyAssertedEL_next(quotedDefnIff, 'SubLCharacter', 'SubLQuoteFn'('CYC-SYSTEM-CHARACTER-P'), 'UniversalVocabularyMt', vStrDef).
 3178exactlyAssertedEL_next(quotedDefnIff, 'SubLAtomicTerm', 'SubLQuoteFn'('CYC-SYSTEM-TERM-P'), 'UniversalVocabularyMt', vStrDef).
 3179exactlyAssertedEL_next(quotedDefnIff, 'SubLAtom', 'SubLQuoteFn'('CYC-SYSTEM-ATOM'), 'UniversalVocabularyMt', vStrDef).
 3180exactlyAssertedEL_next(quotedDefnIff, ftVar, 'SubLQuoteFn'('CYCL-VARIABLE-P'), 'UniversalVocabularyMt', vStrDef).
 3181exactlyAssertedEL_next(quotedDefnIff, 'CycLTerm', 'SubLQuoteFn'('CYCL-EXPRESSION?'), 'UniversalVocabularyMt', vStrDef).
 3182exactlyAssertedEL_next(quotedDefnIff, 'CycLSentence-Assertible', 'SubLQuoteFn'('CYCL-SENTENCE-ASSERTIBLE?'), 'UniversalVocabularyMt', vStrDef).
 3183exactlyAssertedEL_next(quotedDefnIff, 'CycLSentence-Askable', 'SubLQuoteFn'('CYCL-SENTENCE-ASKABLE?'), 'UniversalVocabularyMt', vStrDef).
 3184exactlyAssertedEL_next(quotedDefnIff, 'CycLSentence', 'SubLQuoteFn'('CYCL-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3185exactlyAssertedEL_next(quotedDefnIff, 'CycLRuleAssertion', 'SubLQuoteFn'('CYCL-RULE-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3186exactlyAssertedEL_next(quotedDefnIff, 'CycLRepresentedTerm', 'SubLQuoteFn'('CYCL-REPRESENTED-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3187exactlyAssertedEL_next(quotedDefnIff, 'CycLRepresentedAtomicTerm', 'SubLQuoteFn'('CYCL-REPRESENTED-ATOMIC-TERM-P'), 'UniversalVocabularyMt', vStrDef).
 3188exactlyAssertedEL_next(quotedDefnIff, 'CycLReifiedDenotationalTerm', 'SubLQuoteFn'('CYCL-REIFIED-DENOTATIONAL-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3189exactlyAssertedEL_next(quotedDefnIff, 'CycLReifiableNonAtomicTerm', 'SubLQuoteFn'('CYCL-REIFIABLE-NON-ATOMIC-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3190exactlyAssertedEL_next(quotedDefnIff, 'CycLReifiableNonAtomicTerm', 'SubLQuoteFn'('CYCL-REIFIABLE-NON-ATOMIC-TERM?'), 'LogicalTruthImplementationMt', vStrDef).
 3191exactlyAssertedEL_next(quotedDefnIff, 'CycLReifiableDenotationalTerm', 'SubLQuoteFn'('CYCL-REIFIABLE-DENOTATIONAL-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3192exactlyAssertedEL_next(quotedDefnIff, 'CycLPropositionalSentence', 'SubLQuoteFn'('CYCL-PROPOSITIONAL-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3193exactlyAssertedEL_next(quotedDefnIff, 'CycLOpenSentence', 'SubLQuoteFn'('CYCL-OPEN-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3194exactlyAssertedEL_next(quotedDefnIff, 'CycLOpenNonAtomicTerm', 'SubLQuoteFn'('CYCL-OPEN-NON-ATOMIC-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3195exactlyAssertedEL_next(quotedDefnIff, 'CycLOpenFormula', 'SubLQuoteFn'('CYCL-OPEN-FORMULA?'), 'UniversalVocabularyMt', vStrDef).
 3196exactlyAssertedEL_next(quotedDefnIff, 'CycLOpenExpression', 'SubLQuoteFn'('CYCL-OPEN-EXPRESSION?'), 'UniversalVocabularyMt', vStrDef).
 3197exactlyAssertedEL_next(quotedDefnIff, 'CycLOpenDenotationalTerm', 'SubLQuoteFn'('CYCL-OPEN-DENOTATIONAL-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3198exactlyAssertedEL_next(quotedDefnIff, 'CycLNonAtomicTerm-Assertible', 'SubLQuoteFn'('CYCL-NON-ATOMIC-TERM-ASSERTIBLE?'), 'UniversalVocabularyMt', vStrDef).
 3199exactlyAssertedEL_next(quotedDefnIff, 'CycLNonAtomicTerm-Askable', 'SubLQuoteFn'('CYCL-NON-ATOMIC-TERM-ASKABLE?'), 'UniversalVocabularyMt', vStrDef).
 3200exactlyAssertedEL_next(quotedDefnIff, 'CycLNonAtomicTerm', 'SubLQuoteFn'('CYCL-NON-ATOMIC-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3201exactlyAssertedEL_next(quotedDefnIff, 'CycLNonAtomicReifiedTerm', 'SubLQuoteFn'('CYCL-NON-ATOMIC-REIFIED-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3202exactlyAssertedEL_next(quotedDefnIff, 'CycLIndexedTerm', 'SubLQuoteFn'('CYCL-INDEXED-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3203exactlyAssertedEL_next(quotedDefnIff, 'CycLGenericRelationFormula', 'SubLQuoteFn'('CYCL-UNBOUND-RELATION-FORMULA-P'), 'UniversalVocabularyMt', vStrDef).
 3204exactlyAssertedEL_next(quotedDefnIff, 'CycLGAFAssertion', 'SubLQuoteFn'('CYCL-GAF-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3205exactlyAssertedEL_next(quotedDefnIff, 'CycLFormula', 'SubLQuoteFn'('CYCL-FORMULA?'), 'UniversalVocabularyMt', vStrDef).
 3206exactlyAssertedEL_next(quotedDefnIff, 'CycLExpression-Assertible', 'SubLQuoteFn'('CYCL-EXPRESSION-ASSERTIBLE?'), 'UniversalVocabularyMt', vStrDef).
 3207exactlyAssertedEL_next(quotedDefnIff, 'CycLExpression-Askable', 'SubLQuoteFn'('CYCL-EXPRESSION-ASKABLE?'), 'UniversalVocabularyMt', vStrDef).
 3208exactlyAssertedEL_next(quotedDefnIff, 'CycLExpression', 'SubLQuoteFn'('CYCL-EXPRESSION?'), 'UniversalVocabularyMt', vStrDef).
 3209exactlyAssertedEL_next(quotedDefnIff, 'CycLExpression', 'SubLQuoteFn'('CYCL-EXPRESSION?'), 'LogicalTruthImplementationMt', vStrDef).
 3210exactlyAssertedEL_next(quotedDefnIff, 'CycLDenotationalTerm', 'SubLQuoteFn'('CYCL-DENOTATIONAL-TERM-P'), 'UniversalVocabularyMt', vStrDef).
 3211exactlyAssertedEL_next(quotedDefnIff, 'CycLDeducedAssertion', 'SubLQuoteFn'('CYCL-DEDUCED-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3212exactlyAssertedEL_next(quotedDefnIff, 'CycLConstant', 'SubLQuoteFn'('CYCL-CONSTANT-P'), 'UniversalVocabularyMt', vStrDef).
 3213exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedSentence', 'SubLQuoteFn'('CYCL-CLOSED-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3214exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedNonAtomicTerm', 'SubLQuoteFn'('CYCL-CLOSED-NON-ATOMIC-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3215exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedFormula', 'SubLQuoteFn'('CYCL-CLOSED-FORMULA?'), 'UniversalVocabularyMt', vStrDef).
 3216exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedExpression', 'SubLQuoteFn'('CYCL-CLOSED-EXPRESSION?'), 'UniversalVocabularyMt', vStrDef).
 3217exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedDenotationalTerm', 'SubLQuoteFn'('CYCL-CLOSED-DENOTATIONAL-TERM?'), 'UniversalVocabularyMt', vStrDef).
 3218exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedAtomicTerm', 'SubLQuoteFn'('CYCL-CLOSED-ATOMIC-TERM-P'), 'UniversalVocabularyMt', vStrDef).
 3219exactlyAssertedEL_next(quotedDefnIff, 'CycLClosedAtomicSentence', 'SubLQuoteFn'('CYCL-CLOSED-ATOMIC-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3220exactlyAssertedEL_next(quotedDefnIff, 'CycLAtomicTerm', 'SubLQuoteFn'('CYCL-ATOMIC-TERM-P'), 'UniversalVocabularyMt', vStrDef).
 3221exactlyAssertedEL_next(quotedDefnIff, 'CycLAtomicSentence', 'SubLQuoteFn'('CYCL-ATOMIC-SENTENCE?'), 'UniversalVocabularyMt', vStrDef).
 3222exactlyAssertedEL_next(quotedDefnIff, 'CycLAtomicAssertion', 'SubLQuoteFn'('CYCL-ATOMIC-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3223exactlyAssertedEL_next(quotedDefnIff, 'CycLAssertion', 'SubLQuoteFn'('CYCL-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3224exactlyAssertedEL_next(quotedDefnIff, 'CycLAssertedAssertion', 'SubLQuoteFn'('CYCL-ASSERTED-ASSERTION?'), 'UniversalVocabularyMt', vStrDef).
 3225exactlyAssertedEL_next(quotedArgument, xor, 2, 'UniversalVocabularyMt', vStrDef).
 3226exactlyAssertedEL_next(quotedArgument, xor, 1, 'UniversalVocabularyMt', vStrDef).
 3227exactlyAssertedEL_next(quotedArgument, unknownSentence, 1, 'UniversalVocabularyMt', vStrDef).
 3228exactlyAssertedEL_next(quotedArgument, trueSubL, 1, 'UniversalVocabularyMt', vStrDef).
 3229exactlyAssertedEL_next(quotedArgument, trueSentence, 1, 'UniversalVocabularyMt', vStrDef).
 3230exactlyAssertedEL_next(quotedArgument, trueRule, 2, 'UniversalVocabularyMt', vStrDef).
 3231exactlyAssertedEL_next(quotedArgument, thereExists, 2, 'UniversalVocabularyMt', vStrDef).
 3232exactlyAssertedEL_next(quotedArgument, thereExists, 1, 'UniversalVocabularyMt', vStrMon).
 3233exactlyAssertedEL_next(quotedArgument, thereExistExactly, 3, 'UniversalVocabularyMt', vStrDef).
 3234exactlyAssertedEL_next(quotedArgument, thereExistExactly, 2, 'UniversalVocabularyMt', vStrDef).
 3235exactlyAssertedEL_next(quotedArgument, thereExistAtMost, 3, 'UniversalVocabularyMt', vStrDef).
 3236exactlyAssertedEL_next(quotedArgument, thereExistAtMost, 2, 'UniversalVocabularyMt', vStrDef).
 3237exactlyAssertedEL_next(quotedArgument, thereExistAtLeast, 3, 'UniversalVocabularyMt', vStrDef).
 3238exactlyAssertedEL_next(quotedArgument, thereExistAtLeast, 2, 'UniversalVocabularyMt', vStrDef).
 3239exactlyAssertedEL_next(quotedArgument, termOfUnit, 2, 'UniversalVocabularyMt', vStrDef).
 3240exactlyAssertedEL_next(quotedArgument, termOfUnit, 1, 'UniversalVocabularyMt', vStrDef).
 3241exactlyAssertedEL_next(quotedArgument, termExternalIDString, 1, 'UniversalVocabularyMt', vStrDef).
 3242exactlyAssertedEL_next(quotedArgument, termDependsOn, 2, 'UniversalVocabularyMt', vStrMon).
 3243exactlyAssertedEL_next(quotedArgument, termDependsOn, 1, 'UniversalVocabularyMt', vStrMon).
 3244exactlyAssertedEL_next(quotedArgument, skolemizeForward, 1, 'UniversalVocabularyMt', vStrDef).
 3245exactlyAssertedEL_next(quotedArgument, skolem, 1, 'UniversalVocabularyMt', vStrDef).
 3246exactlyAssertedEL_next(quotedArgument, sharedNotes, 2, 'UniversalVocabularyMt', vStrDef).
 3247exactlyAssertedEL_next(quotedArgument, sharedNotes, 1, 'UniversalVocabularyMt', vStrDef).
 3248exactlyAssertedEL_next(quotedArgument, sentenceImplies, 2, 'UniversalVocabularyMt', vStrDef).
 3249exactlyAssertedEL_next(quotedArgument, sentenceImplies, 1, 'UniversalVocabularyMt', vStrDef).
 3250exactlyAssertedEL_next(quotedArgument, sentenceEquiv, 2, 'UniversalVocabularyMt', vStrDef).
 3251exactlyAssertedEL_next(quotedArgument, sentenceEquiv, 1, 'UniversalVocabularyMt', vStrDef).
 3252exactlyAssertedEL_next(quotedArgument, salientAssertions, 2, 'UniversalVocabularyMt', vStrDef).
 3253exactlyAssertedEL_next(quotedArgument, salientAssertions, 1, 'UniversalVocabularyMt', vStrDef).
 3254exactlyAssertedEL_next(quotedArgument, ruleAfterRemoving, 2, 'UniversalVocabularyMt', vStrDef).
 3255exactlyAssertedEL_next(quotedArgument, ruleAfterAdding, 2, 'UniversalVocabularyMt', vStrDef).
 3256exactlyAssertedEL_next(quotedArgument, rewriteOf, 2, 'UniversalVocabularyMt', vStrMon).
 3257exactlyAssertedEL_next(quotedArgument, rewriteOf, 1, 'UniversalVocabularyMt', vStrMon).
 3258exactlyAssertedEL_next(quotedArgument, relationExpansion, 2, 'UniversalVocabularyMt', vStrDef).
 3259exactlyAssertedEL_next(quotedArgument, reformulatorRuleProperties, 2, 'UniversalVocabularyMt', vStrDef).
 3260exactlyAssertedEL_next(quotedArgument, reformulatorRule, 2, 'UniversalVocabularyMt', vStrDef).
 3261exactlyAssertedEL_next(quotedArgument, reformulatorRule, 1, 'UniversalVocabularyMt', vStrDef).
 3262exactlyAssertedEL_next(quotedArgument, reformulatorEquiv, 2, 'UniversalVocabularyMt', vStrDef).
 3263exactlyAssertedEL_next(quotedArgument, reformulatorEquiv, 1, 'UniversalVocabularyMt', vStrDef).
 3264exactlyAssertedEL_next(quotedArgument, reformulatorEquals, 2, 'UniversalVocabularyMt', vStrDef).
 3265exactlyAssertedEL_next(quotedArgument, reformulatorEquals, 1, 'UniversalVocabularyMt', vStrDef).
 3266exactlyAssertedEL_next(quotedArgument, reformulationPrecondition, 3, 'UniversalVocabularyMt', vStrDef).
 3267exactlyAssertedEL_next(quotedArgument, reformulationDirectionInMode, 3, 'UniversalVocabularyMt', vStrDef).
 3268exactlyAssertedEL_next(quotedArgument, quotedIsa, 1, 'UniversalVocabularyMt', vStrDef).
 3269exactlyAssertedEL_next(quotedArgument, quotedDefnSufficient, 2, 'UniversalVocabularyMt', vStrDef).
 3270exactlyAssertedEL_next(quotedArgument, quotedDefnNecessary, 2, 'UniversalVocabularyMt', vStrDef).
 3271exactlyAssertedEL_next(quotedArgument, quotedDefnIff, 2, 'UniversalVocabularyMt', vStrDef).
 3272exactlyAssertedEL_next(quotedArgument, quotedArgument, 1, 'UniversalVocabularyMt', vStrMon).
 3273exactlyAssertedEL_next(quotedArgument, querySentence, 1, 'UniversalVocabularyMt', vStrDef).
 3274exactlyAssertedEL_next(quotedArgument, prettyString, 2, 'UniversalVocabularyMt', vStrDef).
 3275exactlyAssertedEL_next(quotedArgument, pragmaticRequirement, 2, 'UniversalVocabularyMt', vStrDef).
 3276exactlyAssertedEL_next(quotedArgument, pragmaticRequirement, 1, 'UniversalVocabularyMt', vStrDef).
 3277exactlyAssertedEL_next(quotedArgument, pragmaticallyNormal, 2, 'UniversalVocabularyMt', vStrDef).
 3278exactlyAssertedEL_next(quotedArgument, pointQuantValue, 1, 'UniversalVocabularyMt', vStrDef).
 3279exactlyAssertedEL_next(quotedArgument, performSubL, 1, 'UniversalVocabularyMt', vStrDef).
 3280exactlyAssertedEL_next(quotedArgument, overlappingExternalConcept, 1, 'UniversalVocabularyMt', vStrDef).
 3281exactlyAssertedEL_next(quotedArgument, or, 1, 'UniversalVocabularyMt', vStrDef).
 3282exactlyAssertedEL_next(quotedArgument, operatorFormulas, 2, 'UniversalVocabularyMt', vStrDef).
 3283exactlyAssertedEL_next(quotedArgument, operatorFormulas, 1, 'UniversalVocabularyMt', vStrDef).
 3284exactlyAssertedEL_next(quotedArgument, opaqueArgument, 1, 'UniversalVocabularyMt', vStrMon).
 3285exactlyAssertedEL_next(quotedArgument, oldConstantName, 2, 'UniversalVocabularyMt', vStrDef).
 3286exactlyAssertedEL_next(quotedArgument, oldConstantName, 1, 'UniversalVocabularyMt', vStrDef).
 3287exactlyAssertedEL_next(quotedArgument, not, 1, 'UniversalVocabularyMt', vStrDef).
 3288exactlyAssertedEL_next(quotedArgument, natFunction, 1, 'UniversalVocabularyMt', vStrDef).
 3289exactlyAssertedEL_next(quotedArgument, natArgumentsEqual, 2, 'UniversalVocabularyMt', vStrDef).
 3290exactlyAssertedEL_next(quotedArgument, natArgumentsEqual, 1, 'UniversalVocabularyMt', vStrDef).
 3291exactlyAssertedEL_next(quotedArgument, natArgument, 1, 'UniversalVocabularyMt', vStrDef).
 3292exactlyAssertedEL_next(quotedArgument, myCreator, 1, 'UniversalVocabularyMt', vStrDef).
 3293exactlyAssertedEL_next(quotedArgument, myCreationTime, 1, 'UniversalVocabularyMt', vStrMon).
 3294exactlyAssertedEL_next(quotedArgument, myCreationSecond, 1, 'UniversalVocabularyMt', vStrMon).
 3295exactlyAssertedEL_next(quotedArgument, myCreationPurpose, 1, 'UniversalVocabularyMt', vStrDef).
 3296exactlyAssertedEL_next(quotedArgument, minimize, 1, 'UniversalVocabularyMt', vStrDef).
 3297exactlyAssertedEL_next(quotedArgument, meetsPragmaticRequirement, 2, 'UniversalVocabularyMt', vStrDef).
 3298exactlyAssertedEL_next(quotedArgument, knownSentence, 1, 'UniversalVocabularyMt', vStrDef).
 3299exactlyAssertedEL_next(quotedArgument, knownAntecedentRule, 1, 'UniversalVocabularyMt', vStrDef).
 3300exactlyAssertedEL_next(quotedArgument, ist, 2, 'UniversalVocabularyMt', vStrDef).
 3301exactlyAssertedEL_next(quotedArgument, irrelevantTerm, 1, 'UniversalVocabularyMt', vStrDef).
 3302exactlyAssertedEL_next(quotedArgument, irrelevantPredAssertion, 2, 'UniversalVocabularyMt', vStrDef).
 3303exactlyAssertedEL_next(quotedArgument, irrelevantAssertion, 1, 'UniversalVocabularyMt', vStrDef).
 3304exactlyAssertedEL_next(quotedArgument, indexicalReferent, 1, 'UniversalVocabularyMt', vStrDef).
 3305exactlyAssertedEL_next(quotedArgument, implies, 2, 'UniversalVocabularyMt', vStrDef).
 3306exactlyAssertedEL_next(quotedArgument, implies, 1, 'UniversalVocabularyMt', vStrDef).
 3307exactlyAssertedEL_next(quotedArgument, hypotheticalTerm, 1, 'UniversalVocabularyMt', vStrDef).
 3308exactlyAssertedEL_next(quotedArgument, holdsIn, 2, 'UniversalVocabularyMt', vStrDef).
 3309exactlyAssertedEL_next(quotedArgument, hlPrototypicalInstance, 1, 'UniversalVocabularyMt', vStrDef).
 3310exactlyAssertedEL_next(quotedArgument, highlyRelevantTerm, 1, 'UniversalVocabularyMt', vStrDef).
 3311exactlyAssertedEL_next(quotedArgument, highlyRelevantPredAssertion, 2, 'UniversalVocabularyMt', vStrDef).
 3312exactlyAssertedEL_next(quotedArgument, highlyRelevantAssertion, 1, 'UniversalVocabularyMt', vStrDef).
 3313exactlyAssertedEL_next(quotedArgument, genMassNoun, 1, 'UniversalVocabularyMt', vStrDef).
 3314exactlyAssertedEL_next(quotedArgument, genlRules, 2, 'UniversalVocabularyMt', vStrDef).
 3315exactlyAssertedEL_next(quotedArgument, genlRules, 1, 'UniversalVocabularyMt', vStrDef).
 3316exactlyAssertedEL_next(quotedArgument, genKeyword, 2, 'UniversalVocabularyMt', vStrDef).
 3317exactlyAssertedEL_next(quotedArgument, genKeyword, 1, 'UniversalVocabularyMt', vStrDef).
 3318exactlyAssertedEL_next(quotedArgument, genFormat, 2, 'UniversalVocabularyMt', vStrDef).
 3319exactlyAssertedEL_next(quotedArgument, genFormat, 1, 'UniversalVocabularyMt', vStrDef).
 3320exactlyAssertedEL_next(quotedArgument, forwardNonTriggerLiteral, 1, 'UniversalVocabularyMt', vStrMon).
 3321exactlyAssertedEL_next(quotedArgument, formulaArity, 1, 'UniversalVocabularyMt', vStrDef).
 3322exactlyAssertedEL_next(quotedArgument, forAll, 2, 'UniversalVocabularyMt', vStrDef).
 3323exactlyAssertedEL_next(quotedArgument, forAll, 1, 'UniversalVocabularyMt', vStrDef).
 3324exactlyAssertedEL_next(quotedArgument, expansionDefn, 2, 'UniversalVocabularyMt', vStrDef).
 3325exactlyAssertedEL_next(quotedArgument, expansion, 2, 'UniversalVocabularyMt', vStrDef).
 3326exactlyAssertedEL_next(quotedArgument, exceptWhen, 2, 'UniversalVocabularyMt', vStrDef).
 3327exactlyAssertedEL_next(quotedArgument, exceptWhen, 1, 'UniversalVocabularyMt', vStrDef).
 3328exactlyAssertedEL_next(quotedArgument, exceptFor, 2, 'UniversalVocabularyMt', vStrDef).
 3329exactlyAssertedEL_next(quotedArgument, exceptFor, 1, 'UniversalVocabularyMt', vStrDef).
 3330exactlyAssertedEL_next(quotedArgument, except, 1, 'UniversalVocabularyMt', vStrDef).
 3331exactlyAssertedEL_next(quotedArgument, exampleAssertions, 2, 'UniversalVocabularyMt', vStrDef).
 3332exactlyAssertedEL_next(quotedArgument, exampleAssertions, 1, 'UniversalVocabularyMt', vStrDef).
 3333exactlyAssertedEL_next(quotedArgument, exactlyAssertedEL_next, 1, 'UniversalVocabularyMt', vStrDef).
 3334exactlyAssertedEL_next(quotedArgument, evaluationDefn, 2, 'UniversalVocabularyMt', vStrDef).
 3335exactlyAssertedEL_next(quotedArgument, evaluate, 2, 'UniversalVocabularyMt', vStrMon).
 3336exactlyAssertedEL_next(quotedArgument, equiv, 2, 'UniversalVocabularyMt', vStrDef).
 3337exactlyAssertedEL_next(quotedArgument, equiv, 1, 'UniversalVocabularyMt', vStrDef).
 3338exactlyAssertedEL_next(quotedArgument, equalSymbols, 2, 'UniversalVocabularyMt', vStrMon).
 3339exactlyAssertedEL_next(quotedArgument, equalSymbols, 1, 'UniversalVocabularyMt', vStrMon).
 3340exactlyAssertedEL_next(quotedArgument, ephemeralTerm, 1, 'UniversalVocabularyMt', vStrDef).
 3341exactlyAssertedEL_next(quotedArgument, differentSymbols, 5, 'UniversalVocabularyMt', vStrMon).
 3342exactlyAssertedEL_next(quotedArgument, differentSymbols, 4, 'UniversalVocabularyMt', vStrMon).
 3343exactlyAssertedEL_next(quotedArgument, differentSymbols, 3, 'UniversalVocabularyMt', vStrMon).
 3344exactlyAssertedEL_next(quotedArgument, differentSymbols, 2, 'UniversalVocabularyMt', vStrMon).
 3345exactlyAssertedEL_next(quotedArgument, differentSymbols, 1, 'UniversalVocabularyMt', vStrMon).
 3346exactlyAssertedEL_next(quotedArgument, differentSymbols, '$VAR'('ALL'), 'UniversalVocabularyMt', vStrMon).
 3347exactlyAssertedEL_next(quotedArgument, defnSufficient, 2, 'UniversalVocabularyMt', vStrDef).
 3348exactlyAssertedEL_next(quotedArgument, defnNecessary, 2, 'UniversalVocabularyMt', vStrDef).
 3349exactlyAssertedEL_next(quotedArgument, defnIff, 2, 'UniversalVocabularyMt', vStrDef).
 3350exactlyAssertedEL_next(quotedArgument, definingMt, 1, 'UniversalVocabularyMt', vStrMon).
 3351exactlyAssertedEL_next(quotedArgument, cycTransformationProofRule, 2, 'UniversalVocabularyMt', vStrDef).
 3352exactlyAssertedEL_next(quotedArgument, cycProblemStoreTerms, 2, 'UniversalVocabularyMt', vStrDef).
 3353exactlyAssertedEL_next(quotedArgument, cycProblemQueryTerms, 2, 'UniversalVocabularyMt', vStrDef).
 3354exactlyAssertedEL_next(quotedArgument, cycProblemQuerySentence, 2, 'UniversalVocabularyMt', vStrDef).
 3355exactlyAssertedEL_next(quotedArgument, constraint, 1, 'UniversalVocabularyMt', vStrDef).
 3356exactlyAssertedEL_next(quotedArgument, constantName, 2, 'UniversalVocabularyMt', vStrDef).
 3357exactlyAssertedEL_next(quotedArgument, constantName, 1, 'UniversalVocabularyMt', vStrDef).
 3358exactlyAssertedEL_next(quotedArgument, constantID, 1, 'UniversalVocabularyMt', vStrMon).
 3359exactlyAssertedEL_next(quotedArgument, constantGUID, 1, 'UniversalVocabularyMt', vStrDef).
 3360exactlyAssertedEL_next(quotedArgument, consistent, 1, 'UniversalVocabularyMt', vStrDef).
 3361exactlyAssertedEL_next(quotedArgument, comment, 2, 'UniversalVocabularyMt', vStrMon).
 3362exactlyAssertedEL_next(quotedArgument, comment, 1, 'UniversalVocabularyMt', vStrMon).
 3363exactlyAssertedEL_next(quotedArgument, collectionExpansion, 2, 'UniversalVocabularyMt', vStrDef).
 3364exactlyAssertedEL_next(quotedArgument, assertionUtility, 1, 'UniversalVocabularyMt', vStrDef).
 3365exactlyAssertedEL_next(quotedArgument, assertionDirection, 1, 'UniversalVocabularyMt', vStrDef).
 3366exactlyAssertedEL_next(quotedArgument, assertedTermSentences, 2, 'UniversalVocabularyMt', vStrMon).
 3367exactlyAssertedEL_next(quotedArgument, assertedTermSentences, 1, 'UniversalVocabularyMt', vStrMon).
 3368exactlyAssertedEL_next(quotedArgument, knownSentence, 1, 'UniversalVocabularyMt', vStrMon).
 3369exactlyAssertedEL_next(quotedArgument, arity, 2, 'UniversalVocabularyMt', vStrDef).
 3370exactlyAssertedEL_next(quotedArgument, argSometimesIsa, 2, 'UniversalVocabularyMt', vStrDef).
 3371exactlyAssertedEL_next(quotedArgument, argIsa, 2, 'UniversalVocabularyMt', vStrDef).
 3372exactlyAssertedEL_next(quotedArgument, argAndRestIsa, 2, 'UniversalVocabularyMt', vStrDef).
 3373exactlyAssertedEL_next(quotedArgument, and, 1, 'UniversalVocabularyMt', vStrDef).
 3374exactlyAssertedEL_next(quotedArgument, afterRemoving, 2, 'UniversalVocabularyMt', vStrDef).
 3375exactlyAssertedEL_next(quotedArgument, afterAdding, 2, 'UniversalVocabularyMt', vStrDef).
 3376exactlyAssertedEL_next(quotedArgument, admittedSentence, 1, 'UniversalVocabularyMt', vStrDef).
 3377exactlyAssertedEL_next(quotedArgument, admittedNAT, 1, 'UniversalVocabularyMt', vStrDef).
 3378exactlyAssertedEL_next(quotedArgument, abnormal, 2, 'UniversalVocabularyMt', vStrDef).
 3379exactlyAssertedEL_next(quotedArgument, 'UncanonicalizerAssertionFn', 1, 'UniversalVocabularyMt', vStrDef).
 3380exactlyAssertedEL_next(quotedArgument, 'TLVariableFn', 2, 'UniversalVocabularyMt', vStrDef).
 3381exactlyAssertedEL_next(quotedArgument, 'TLAssertionFn', 2, 'UniversalVocabularyMt', vStrDef).
 3382exactlyAssertedEL_next(quotedArgument, 'TheSetOf', 2, 'UniversalVocabularyMt', vStrDef).
 3383exactlyAssertedEL_next(quotedArgument, 'TheSetOf', 1, 'UniversalVocabularyMt', vStrDef).
 3384exactlyAssertedEL_next(quotedArgument, 'TheCollectionOf', 2, 'UniversalVocabularyMt', vStrDef).
 3385exactlyAssertedEL_next(quotedArgument, 'TheCollectionOf', 1, 'UniversalVocabularyMt', vStrDef).
 3386exactlyAssertedEL_next(quotedArgument, 'SubLQuoteFn', 1, 'UniversalVocabularyMt', vStrDef).
 3387exactlyAssertedEL_next(quotedArgument, 'SkolemFunctionFn', 3, 'UniversalVocabularyMt', vStrDef).
 3388exactlyAssertedEL_next(quotedArgument, 'SkolemFunctionFn', 2, 'UniversalVocabularyMt', vStrDef).
 3389exactlyAssertedEL_next(quotedArgument, 'SkolemFunctionFn', 1, 'UniversalVocabularyMt', vStrDef).
 3390exactlyAssertedEL_next(quotedArgument, 'SkolemFuncNFn', 3, 'UniversalVocabularyMt', vStrDef).
 3391exactlyAssertedEL_next(quotedArgument, 'SkolemFuncNFn', 2, 'UniversalVocabularyMt', vStrDef).
 3392exactlyAssertedEL_next(quotedArgument, 'SkolemFuncNFn', 1, 'UniversalVocabularyMt', vStrDef).
 3393exactlyAssertedEL_next(quotedArgument, 'Quote', 1, 'UniversalVocabularyMt', vStrDef).
 3394exactlyAssertedEL_next(quotedArgument, 'QuasiQuote', 1, 'UniversalVocabularyMt', vStrDef).
 3395exactlyAssertedEL_next(quotedArgument, 'prettyString-Canonical', 2, 'UniversalVocabularyMt', vStrDef).
 3396exactlyAssertedEL_next(quotedArgument, 'Kappa', 2, 'UniversalVocabularyMt', vStrDef).
 3397exactlyAssertedEL_next(quotedArgument, 'Kappa', 1, 'UniversalVocabularyMt', vStrDef).
 3398exactlyAssertedEL_next(quotedArgument, 'ist-Asserted', 2, 'UniversalVocabularyMt', vStrMon).
 3399exactlyAssertedEL_next(quotedArgument, 'FormulaArityFn', 1, 'UniversalVocabularyMt', vStrDef).
 3400exactlyAssertedEL_next(quotedArgument, 'FormulaArgSetFn', 1, 'UniversalVocabularyMt', vStrDef).
 3401exactlyAssertedEL_next(quotedArgument, 'FormulaArgListFn', 1, 'UniversalVocabularyMt', vStrDef).
 3402exactlyAssertedEL_next(quotedArgument, 'FormulaArgFn', 2, 'UniversalVocabularyMt', vStrDef).
 3403exactlyAssertedEL_next(quotedArgument, 'ExpandSubLFn', 2, 'UniversalVocabularyMt', vStrDef).
 3404exactlyAssertedEL_next(quotedArgument, 'ExpandSubLFn', 1, 'UniversalVocabularyMt', vStrDef).
 3405exactlyAssertedEL_next(quotedArgument, 'EvaluateSubLFn', 1, 'UniversalVocabularyMt', vStrDef).
 3406exactlyAssertedEL_next(quotedArgument, 'EscapeQuote', 1, 'UniversalVocabularyMt', vStrDef).
 3407exactlyAssertedEL_next(quotedArgument, 'assertionUtility-1', 1, 'UniversalVocabularyMt', vStrDef).
 3408exactlyAssertedEL_first(argQuotedIsa, xor, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3409exactlyAssertedEL_first(argQuotedIsa, xor, 2, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3410exactlyAssertedEL_first(argQuotedIsa, xor, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3411exactlyAssertedEL_first(argQuotedIsa, xor, 1, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3412exactlyAssertedEL_first(argQuotedIsa, unknownSentence, 1, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 3413exactlyAssertedEL_first(argQuotedIsa, trueSubL, 1, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3414exactlyAssertedEL_first(argQuotedIsa, trueSentence, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3415exactlyAssertedEL_first(argQuotedIsa, trueRule, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3416exactlyAssertedEL_first(argQuotedIsa, thereExists, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3417exactlyAssertedEL_first(argQuotedIsa, thereExists, 2, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3418exactlyAssertedEL_first(argQuotedIsa, thereExists, 1, ftVar, 'UniversalVocabularyMt', vStrDef).
 3419exactlyAssertedEL_first(argQuotedIsa, thereExists, 1, ftVar, 'LogicalTruthMt', vStrDef).
 3420exactlyAssertedEL_first(argQuotedIsa, thereExistExactly, 3, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3421exactlyAssertedEL_first(argQuotedIsa, thereExistExactly, 2, ftVar, 'UniversalVocabularyMt', vStrDef).
 3422exactlyAssertedEL_first(argQuotedIsa, thereExistAtMost, 3, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3423exactlyAssertedEL_first(argQuotedIsa, thereExistAtMost, 2, ftVar, 'UniversalVocabularyMt', vStrDef).
 3424exactlyAssertedEL_first(argQuotedIsa, thereExistAtLeast, 3, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3425exactlyAssertedEL_first(argQuotedIsa, thereExistAtLeast, 2, ftVar, 'UniversalVocabularyMt', vStrDef).
 3426exactlyAssertedEL_first(argQuotedIsa, termOfUnit, 2, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3427exactlyAssertedEL_first(argQuotedIsa, termOfUnit, 1, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3428exactlyAssertedEL_first(argQuotedIsa, termOfUnit, 1, 'CycLReifiableNonAtomicTerm', 'LogicalTruthImplementationMt', vStrDef).
 3429exactlyAssertedEL_first(argQuotedIsa, termExternalIDString, 1, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 3430exactlyAssertedEL_first(argQuotedIsa, termDependsOn, 2, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3431exactlyAssertedEL_first(argQuotedIsa, termDependsOn, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3432exactlyAssertedEL_first(argQuotedIsa, sharedNotes, 2, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 3433exactlyAssertedEL_first(argQuotedIsa, sharedNotes, 1, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 3434exactlyAssertedEL_first(argQuotedIsa, sentenceImplies, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3435exactlyAssertedEL_first(argQuotedIsa, sentenceImplies, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3436exactlyAssertedEL_first(argQuotedIsa, sentenceEquiv, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3437exactlyAssertedEL_first(argQuotedIsa, sentenceEquiv, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3438exactlyAssertedEL_first(argQuotedIsa, salientAssertions, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3439exactlyAssertedEL_first(argQuotedIsa, salientAssertions, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3440exactlyAssertedEL_first(argQuotedIsa, ruleAfterRemoving, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3441exactlyAssertedEL_first(argQuotedIsa, ruleAfterAdding, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3442exactlyAssertedEL_first(argQuotedIsa, rewriteOf, 2, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3443exactlyAssertedEL_first(argQuotedIsa, rewriteOf, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3444exactlyAssertedEL_first(argQuotedIsa, relationExpansion, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3445exactlyAssertedEL_first(argQuotedIsa, reformulatorRuleProperties, 2, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 3446exactlyAssertedEL_first(argQuotedIsa, reformulatorRule, 2, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 3447exactlyAssertedEL_first(argQuotedIsa, reformulatorRule, 1, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 3448exactlyAssertedEL_first(argQuotedIsa, reformulatorEquiv, 2, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 3449exactlyAssertedEL_first(argQuotedIsa, reformulatorEquiv, 1, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 3450exactlyAssertedEL_first(argQuotedIsa, reformulatorEquals, 2, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3451exactlyAssertedEL_first(argQuotedIsa, reformulatorEquals, 1, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3452exactlyAssertedEL_first(argQuotedIsa, reformulationPrecondition, 3, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 3453exactlyAssertedEL_first(argQuotedIsa, reformulationDirectionInMode, 3, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 3454exactlyAssertedEL_first(argQuotedIsa, quotedDefnSufficient, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3455exactlyAssertedEL_first(argQuotedIsa, quotedDefnNecessary, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3456exactlyAssertedEL_first(argQuotedIsa, quotedDefnIff, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3457exactlyAssertedEL_first(argQuotedIsa, querySentence, 1, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 3458exactlyAssertedEL_first(argQuotedIsa, prettyString, 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3459exactlyAssertedEL_first(argQuotedIsa, pragmaticRequirement, 2, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 3460exactlyAssertedEL_first(argQuotedIsa, pragmaticRequirement, 1, 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 3461exactlyAssertedEL_first(argQuotedIsa, pragmaticallyNormal, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrMon).
 3462exactlyAssertedEL_first(argQuotedIsa, pointQuantValue, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3463exactlyAssertedEL_first(argQuotedIsa, performSubL, 1, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3464exactlyAssertedEL_first(argQuotedIsa, or, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3465exactlyAssertedEL_first(argQuotedIsa, operatorFormulas, 2, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3466exactlyAssertedEL_first(argQuotedIsa, operatorFormulas, 1, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3467exactlyAssertedEL_first(argQuotedIsa, oldConstantName, 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3468exactlyAssertedEL_first(argQuotedIsa, oldConstantName, 2, 'SubLString', 'BookkeepingMt', vStrDef).
 3469exactlyAssertedEL_first(argQuotedIsa, oldConstantName, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 3470exactlyAssertedEL_first(argQuotedIsa, oldConstantName, 1, 'CycLConstant', 'BookkeepingMt', vStrDef).
 3471exactlyAssertedEL_first(argQuotedIsa, not, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3472exactlyAssertedEL_first(argQuotedIsa, not, 1, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3473exactlyAssertedEL_first(argQuotedIsa, not, 1, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3474exactlyAssertedEL_first(argQuotedIsa, natFunction, 1, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3475exactlyAssertedEL_first(argQuotedIsa, natArgumentsEqual, 2, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3476exactlyAssertedEL_first(argQuotedIsa, natArgumentsEqual, 1, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3477exactlyAssertedEL_first(argQuotedIsa, natArgument, 1, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3478exactlyAssertedEL_first(argQuotedIsa, myCreator, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3479exactlyAssertedEL_first(argQuotedIsa, myCreator, 1, 'CycLReifiableDenotationalTerm', 'BookkeepingMt', vStrDef).
 3480exactlyAssertedEL_first(argQuotedIsa, myCreationTime, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrMon).
 3481exactlyAssertedEL_first(argQuotedIsa, myCreationTime, 1, 'CycLConstant', 'BookkeepingMt', vStrDef).
 3482exactlyAssertedEL_first(argQuotedIsa, myCreationSecond, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 3483exactlyAssertedEL_first(argQuotedIsa, myCreationSecond, 1, 'CycLConstant', 'BookkeepingMt', vStrDef).
 3484exactlyAssertedEL_first(argQuotedIsa, myCreationPurpose, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3485exactlyAssertedEL_first(argQuotedIsa, myCreationPurpose, 1, 'CycLReifiableDenotationalTerm', 'BookkeepingMt', vStrDef).
 3486exactlyAssertedEL_first(argQuotedIsa, minimize, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3487exactlyAssertedEL_first(argQuotedIsa, meetsPragmaticRequirement, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrMon).
 3488exactlyAssertedEL_first(argQuotedIsa, knownSentence, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3489exactlyAssertedEL_first(argQuotedIsa, knownAntecedentRule, 1, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 3490exactlyAssertedEL_first(argQuotedIsa, ist, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3491exactlyAssertedEL_first(argQuotedIsa, ist, 2, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3492exactlyAssertedEL_first(argQuotedIsa, irrelevantTerm, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3493exactlyAssertedEL_first(argQuotedIsa, irrelevantPredAssertion, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3494exactlyAssertedEL_first(argQuotedIsa, irrelevantAssertion, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3495exactlyAssertedEL_first(argQuotedIsa, indexicalReferent, 1, 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 3496exactlyAssertedEL_first(argQuotedIsa, implies, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3497exactlyAssertedEL_first(argQuotedIsa, implies, 2, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3498exactlyAssertedEL_first(argQuotedIsa, implies, 2, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3499exactlyAssertedEL_first(argQuotedIsa, implies, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3500exactlyAssertedEL_first(argQuotedIsa, implies, 1, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3501exactlyAssertedEL_first(argQuotedIsa, implies, 1, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3502exactlyAssertedEL_first(argQuotedIsa, hypotheticalTerm, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3503exactlyAssertedEL_first(argQuotedIsa, holdsIn, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3504exactlyAssertedEL_first(argQuotedIsa, hlPrototypicalInstance, 1, 'HLPrototypicalTerm', 'UniversalVocabularyMt', vStrDef).
 3505exactlyAssertedEL_first(argQuotedIsa, hlPrototypicalInstance, 1, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 3506exactlyAssertedEL_first(argQuotedIsa, highlyRelevantTerm, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3507exactlyAssertedEL_first(argQuotedIsa, highlyRelevantPredAssertion, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3508exactlyAssertedEL_first(argQuotedIsa, highlyRelevantAssertion, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3509exactlyAssertedEL_first(argQuotedIsa, genMassNoun, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3510exactlyAssertedEL_first(argQuotedIsa, genlRules, 2, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 3511exactlyAssertedEL_first(argQuotedIsa, genlRules, 1, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 3512exactlyAssertedEL_first(argQuotedIsa, genKeyword, 2, 'SubLKeyword', 'UniversalVocabularyMt', vStrDef).
 3513exactlyAssertedEL_first(argQuotedIsa, genKeyword, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3514exactlyAssertedEL_first(argQuotedIsa, genFormat, 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3515exactlyAssertedEL_first(argQuotedIsa, forwardNonTriggerLiteral, 1, 'CycLOpenSentence', 'UniversalVocabularyMt', vStrDef).
 3516exactlyAssertedEL_first(argQuotedIsa, formulaArity, 1, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3517exactlyAssertedEL_first(argQuotedIsa, forAll, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3518exactlyAssertedEL_first(argQuotedIsa, forAll, 2, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrDef).
 3519exactlyAssertedEL_first(argQuotedIsa, forAll, 1, ftVar, 'UniversalVocabularyMt', vStrDef).
 3520exactlyAssertedEL_first(argQuotedIsa, forAll, 1, ftVar, 'LogicalTruthMt', vStrDef).
 3521exactlyAssertedEL_first(argQuotedIsa, expansionDefn, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3522exactlyAssertedEL_first(argQuotedIsa, expansion, 2, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 3523exactlyAssertedEL_first(argQuotedIsa, expansion, 2, 'CycLExpression', 'UniversalVocabularyImplementationMt', vStrDef).
 3524exactlyAssertedEL_first(argQuotedIsa, exceptWhen, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3525exactlyAssertedEL_first(argQuotedIsa, exceptWhen, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3526exactlyAssertedEL_first(argQuotedIsa, exceptFor, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3527exactlyAssertedEL_first(argQuotedIsa, exceptFor, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3528exactlyAssertedEL_first(argQuotedIsa, except, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3529exactlyAssertedEL_first(argQuotedIsa, exampleAssertions, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3530exactlyAssertedEL_first(argQuotedIsa, exampleAssertions, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3531exactlyAssertedEL_first(argQuotedIsa, exactlyAssertedEL_next, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3532exactlyAssertedEL_first(argQuotedIsa, evaluationDefn, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3533exactlyAssertedEL_first(argQuotedIsa, equiv, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3534exactlyAssertedEL_first(argQuotedIsa, equiv, 2, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3535exactlyAssertedEL_first(argQuotedIsa, equiv, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3536exactlyAssertedEL_first(argQuotedIsa, equiv, 1, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 3537exactlyAssertedEL_first(argQuotedIsa, ephemeralTerm, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3538exactlyAssertedEL_first(argQuotedIsa, defnSufficient, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3539exactlyAssertedEL_first(argQuotedIsa, defnNecessary, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3540exactlyAssertedEL_first(argQuotedIsa, defnIff, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3541exactlyAssertedEL_first(argQuotedIsa, definingMt, 1, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3542exactlyAssertedEL_first(argQuotedIsa, cycTransformationProofRule, 2, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 3543exactlyAssertedEL_first(argQuotedIsa, cycProblemStoreTerms, 2, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3544exactlyAssertedEL_first(argQuotedIsa, cycProblemQueryTerms, 2, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 3545exactlyAssertedEL_first(argQuotedIsa, cycProblemQuerySentence, 2, 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 3546exactlyAssertedEL_first(argQuotedIsa, constraint, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3547exactlyAssertedEL_first(argQuotedIsa, constantName, 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3548exactlyAssertedEL_first(argQuotedIsa, constantName, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 3549exactlyAssertedEL_first(argQuotedIsa, constantID, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 3550exactlyAssertedEL_first(argQuotedIsa, constantGUID, 1, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 3551exactlyAssertedEL_first(argQuotedIsa, consistent, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3552exactlyAssertedEL_first(argQuotedIsa, comment, 2, 'SubLString', 'UniversalVocabularyMt', vStrMon).
 3553exactlyAssertedEL_first(argQuotedIsa, comment, 1, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrMon).
 3554exactlyAssertedEL_first(argQuotedIsa, collectionExpansion, 2, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 3555exactlyAssertedEL_first(argQuotedIsa, collectionExpansion, 2, 'CycLExpression', 'UniversalVocabularyImplementationMt', vStrDef).
 3556exactlyAssertedEL_first(argQuotedIsa, assertionUtility, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3557exactlyAssertedEL_first(argQuotedIsa, assertionDirection, 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3558exactlyAssertedEL_first(argQuotedIsa, assertedTermSentences, 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3559exactlyAssertedEL_first(argQuotedIsa, assertedTermSentences, 1, 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 3560exactlyAssertedEL_first(argQuotedIsa, knownSentence, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3561exactlyAssertedEL_first(argQuotedIsa, arity, 2, 'SubLNonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3562exactlyAssertedEL_first(argQuotedIsa, arity, 2, 'SubLNonNegativeInteger', 'LogicalTruthImplementationMt', vStrDef).
 3563exactlyAssertedEL_first(argQuotedIsa, argSometimesIsa, 2, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3564exactlyAssertedEL_first(argQuotedIsa, argIsa, 2, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3565exactlyAssertedEL_first(argQuotedIsa, argIsa, 2, 'SubLPositiveInteger', 'LogicalTruthImplementationMt', vStrDef).
 3566exactlyAssertedEL_first(argQuotedIsa, argAndRestIsa, 2, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3567exactlyAssertedEL_first(argQuotedIsa, argAndRestIsa, 2, 'SubLPositiveInteger', 'LogicalTruthImplementationMt', vStrDef).
 3568exactlyAssertedEL_first(argQuotedIsa, and, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3569exactlyAssertedEL_first(argQuotedIsa, afterRemoving, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3570exactlyAssertedEL_first(argQuotedIsa, afterAdding, 2, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3571exactlyAssertedEL_first(argQuotedIsa, admittedSentence, 1, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3572exactlyAssertedEL_first(argQuotedIsa, admittedNAT, 1, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3573exactlyAssertedEL_first(argQuotedIsa, abnormal, 2, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3574exactlyAssertedEL_first(argQuotedIsa, 'UncanonicalizerAssertionFn', 1, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3575exactlyAssertedEL_first(argQuotedIsa, 'TLVariableFn', 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3576exactlyAssertedEL_first(argQuotedIsa, 'TLAssertionFn', 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3577exactlyAssertedEL_first(argQuotedIsa, 'TheSetOf', 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3578exactlyAssertedEL_first(argQuotedIsa, 'TheSetOf', 1, ftVar, 'UniversalVocabularyMt', vStrDef).
 3579exactlyAssertedEL_first(argQuotedIsa, 'TheCollectionOf', 2, 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 3580exactlyAssertedEL_first(argQuotedIsa, 'TheCollectionOf', 1, ftVar, 'UniversalVocabularyMt', vStrDef).
 3581exactlyAssertedEL_first(argQuotedIsa, 'SubLQuoteFn', 1, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 3582exactlyAssertedEL_first(argQuotedIsa, 'SkolemFunctionFn', 3, 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 3583exactlyAssertedEL_first(argQuotedIsa, 'SkolemFunctionFn', 2, ftVar, 'UniversalVocabularyMt', vStrDef).
 3584exactlyAssertedEL_first(argQuotedIsa, 'SkolemFunctionFn', 1, 'SubLList', 'UniversalVocabularyMt', vStrDef).
 3585exactlyAssertedEL_first(argQuotedIsa, 'SkolemFuncNFn', 3, 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 3586exactlyAssertedEL_first(argQuotedIsa, 'SkolemFuncNFn', 2, ftVar, 'UniversalVocabularyMt', vStrDef).
 3587exactlyAssertedEL_first(argQuotedIsa, 'SkolemFuncNFn', 1, 'SubLList', 'UniversalVocabularyMt', vStrDef).
 3588exactlyAssertedEL_first(argQuotedIsa, 'Quote', 1, 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 3589exactlyAssertedEL_first(argQuotedIsa, 'Quote', 1, 'CycLTerm', 'LogicalTruthImplementationMt', vStrDef).
 3590exactlyAssertedEL_first(argQuotedIsa, 'QuasiQuote', 1, 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 3591exactlyAssertedEL_first(argQuotedIsa, 'QuasiQuote', 1, 'CycLTerm', 'LogicalTruthImplementationMt', vStrMon).
 3592exactlyAssertedEL_first(argQuotedIsa, 'prettyString-Canonical', 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 3593exactlyAssertedEL_first(argQuotedIsa, 'Kappa', 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3594exactlyAssertedEL_first(argQuotedIsa, 'Kappa', 1, 'SubLList', 'UniversalVocabularyMt', vStrDef).
 3595exactlyAssertedEL_first(argQuotedIsa, 'ist-Asserted', 2, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 3596exactlyAssertedEL_first(argQuotedIsa, 'FormulaArityFn', 1, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3597exactlyAssertedEL_first(argQuotedIsa, 'FormulaArgSetFn', 1, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3598exactlyAssertedEL_first(argQuotedIsa, 'FormulaArgListFn', 1, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3599exactlyAssertedEL_first(argQuotedIsa, 'FormulaArgFn', 2, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 3600exactlyAssertedEL_first(argQuotedIsa, 'ExpandSubLFn', 2, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 3601exactlyAssertedEL_first(argQuotedIsa, 'ExpandSubLFn', 1, 'SubLList', 'UniversalVocabularyMt', vStrDef).
 3602exactlyAssertedEL_first(argQuotedIsa, 'EvaluateSubLFn', 1, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 3603exactlyAssertedEL_first(argQuotedIsa, 'EscapeQuote', 1, 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 3604exactlyAssertedEL_first(argQuotedIsa, 'EscapeQuote', 1, 'CycLTerm', 'LogicalTruthImplementationMt', vStrDef).
 3605exactlyAssertedEL_first(argQuotedIsa, 'assertionUtility-1', 1, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 3606exactlyAssertedEL_first(argIsa, unitMultiplicationFactor, 3, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 3607exactlyAssertedEL_first(argIsa, unitMultiplicationFactor, 3, 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3608exactlyAssertedEL_first(argIsa, unitMultiplicationFactor, 2, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 3609exactlyAssertedEL_first(argIsa, unitMultiplicationFactor, 1, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 3610exactlyAssertedEL_first(argIsa, trueSubL, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3611exactlyAssertedEL_first(argIsa, trueRule, 1, 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 3612exactlyAssertedEL_first(argIsa, transitiveViaArgInverse, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3613exactlyAssertedEL_first(argIsa, transitiveViaArgInverse, 2, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3614exactlyAssertedEL_first(argIsa, transitiveViaArgInverse, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3615exactlyAssertedEL_first(argIsa, transitiveViaArg, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3616exactlyAssertedEL_first(argIsa, transitiveViaArg, 2, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3617exactlyAssertedEL_first(argIsa, transitiveViaArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3618exactlyAssertedEL_first(argIsa, thereExistExactly, 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3619exactlyAssertedEL_first(argIsa, thereExistAtMost, 1, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3620exactlyAssertedEL_first(argIsa, thereExistAtLeast, 1, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3621exactlyAssertedEL_first(argIsa, termOfUnit, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3622exactlyAssertedEL_first(argIsa, termOfUnit, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3623exactlyAssertedEL_first(argIsa, termExternalIDString, 2, 'HLExternalIDString', 'UniversalVocabularyMt', vStrDef).
 3624exactlyAssertedEL_first(argIsa, termExternalIDString, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3625exactlyAssertedEL_first(argIsa, termDependsOn, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3626exactlyAssertedEL_first(argIsa, termDependsOn, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3627exactlyAssertedEL_first(argIsa, termChosen, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3628exactlyAssertedEL_first(argIsa, synonymousExternalConcept, 3, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3629exactlyAssertedEL_first(argIsa, synonymousExternalConcept, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3630exactlyAssertedEL_first(argIsa, synonymousExternalConcept, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3631exactlyAssertedEL_first(argIsa, substring, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3632exactlyAssertedEL_first(argIsa, substring, 1, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3633exactlyAssertedEL_first(argIsa, subsetOf, 2, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3634exactlyAssertedEL_first(argIsa, subsetOf, 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3635exactlyAssertedEL_first(argIsa, skolemizeForward, 1, 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 3636exactlyAssertedEL_first(argIsa, skolem, 1, 'SkolemFunction', 'UniversalVocabularyMt', vStrDef).
 3637exactlyAssertedEL_first(argIsa, singleEntryFormatInArgs, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3638exactlyAssertedEL_first(argIsa, singleEntryFormatInArgs, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3639exactlyAssertedEL_first(argIsa, siblingDisjointExceptions, 2, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3640exactlyAssertedEL_first(argIsa, siblingDisjointExceptions, 2, 'SetOrCollection', 'BaseKB', vStrDef).
 3641exactlyAssertedEL_first(argIsa, siblingDisjointExceptions, 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3642exactlyAssertedEL_first(argIsa, siblingDisjointExceptions, 1, 'SetOrCollection', 'BaseKB', vStrDef).
 3643exactlyAssertedEL_first(argIsa, sharedNotes, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3644exactlyAssertedEL_first(argIsa, sharedNotes, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3645exactlyAssertedEL_first(argIsa, sentenceTruth, 2, 'TruthValue', 'UniversalVocabularyMt', vStrDef).
 3646exactlyAssertedEL_first(argIsa, sentenceEquiv, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3647exactlyAssertedEL_first(argIsa, sentenceEquiv, 2, 'Thing', 'BaseKB', vStrDef).
 3648exactlyAssertedEL_first(argIsa, sentenceEquiv, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3649exactlyAssertedEL_first(argIsa, sentenceEquiv, 2, 'Individual', 'BaseKB', vStrDef).
 3650exactlyAssertedEL_first(argIsa, sentenceEquiv, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3651exactlyAssertedEL_first(argIsa, sentenceEquiv, 1, 'Thing', 'BaseKB', vStrDef).
 3652exactlyAssertedEL_first(argIsa, sentenceEquiv, 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3653exactlyAssertedEL_first(argIsa, sentenceEquiv, 1, 'Individual', 'BaseKB', vStrDef).
 3654exactlyAssertedEL_first(argIsa, sentenceDesignationArgnum, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3655exactlyAssertedEL_first(argIsa, sentenceDesignationArgnum, 1, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 3656exactlyAssertedEL_first(argIsa, scopingArg, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3657exactlyAssertedEL_first(argIsa, scopingArg, 1, 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 3658exactlyAssertedEL_first(argIsa, salientAssertions, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3659exactlyAssertedEL_first(argIsa, ruleTemplateDirection, 2, 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 3660exactlyAssertedEL_first(argIsa, ruleTemplateDirection, 1, 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 3661exactlyAssertedEL_first(argIsa, ruleAfterRemoving, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3662exactlyAssertedEL_first(argIsa, ruleAfterRemoving, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3663exactlyAssertedEL_first(argIsa, ruleAfterAdding, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3664exactlyAssertedEL_first(argIsa, ruleAfterAdding, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3665exactlyAssertedEL_first(argIsa, rewriteOf, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3666exactlyAssertedEL_first(argIsa, rewriteOf, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3667exactlyAssertedEL_first(argIsa, resultQuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3668exactlyAssertedEL_first(argIsa, resultQuotedIsa, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3669exactlyAssertedEL_first(argIsa, resultIsaArgIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3670exactlyAssertedEL_first(argIsa, resultIsaArgIsa, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3671exactlyAssertedEL_first(argIsa, resultIsaArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3672exactlyAssertedEL_first(argIsa, resultIsaArg, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3673exactlyAssertedEL_first(argIsa, resultIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3674exactlyAssertedEL_first(argIsa, resultIsa, 2, tCol, 'LogicalTruthMt', vStrDef).
 3675exactlyAssertedEL_first(argIsa, resultIsa, 2, tCol, 'BaseKB', vStrDef).
 3676exactlyAssertedEL_first(argIsa, resultIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3677exactlyAssertedEL_first(argIsa, resultIsa, 1, tRelation, 'BaseKB', vStrMon).
 3678exactlyAssertedEL_first(argIsa, resultIsa, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3679exactlyAssertedEL_first(argIsa, resultGenlArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3680exactlyAssertedEL_first(argIsa, resultGenlArg, 1, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 3681exactlyAssertedEL_first(argIsa, resultGenl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3682exactlyAssertedEL_first(argIsa, resultGenl, 2, tCol, 'BaseKB', vStrDef).
 3683exactlyAssertedEL_first(argIsa, resultGenl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3684exactlyAssertedEL_first(argIsa, resultGenl, 1, tRelation, 'BaseKB', vStrMon).
 3685exactlyAssertedEL_first(argIsa, resultGenl, 1, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 3686exactlyAssertedEL_first(argIsa, requiredArg3Pred, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3687exactlyAssertedEL_first(argIsa, requiredArg3Pred, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3688exactlyAssertedEL_first(argIsa, requiredArg2Pred, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3689exactlyAssertedEL_first(argIsa, requiredArg2Pred, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3690exactlyAssertedEL_first(argIsa, requiredArg1Pred, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3691exactlyAssertedEL_first(argIsa, requiredArg1Pred, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3692exactlyAssertedEL_first(argIsa, relationMemberInstance, 3, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3693exactlyAssertedEL_first(argIsa, relationMemberInstance, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3694exactlyAssertedEL_first(argIsa, relationMemberInstance, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3695exactlyAssertedEL_first(argIsa, relationInstanceMember, 3, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3696exactlyAssertedEL_first(argIsa, relationInstanceMember, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3697exactlyAssertedEL_first(argIsa, relationInstanceMember, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3698exactlyAssertedEL_first(argIsa, relationInstanceExists, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3699exactlyAssertedEL_first(argIsa, relationInstanceExists, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3700exactlyAssertedEL_first(argIsa, relationInstanceExists, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3701exactlyAssertedEL_first(argIsa, relationInstanceAll, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3702exactlyAssertedEL_first(argIsa, relationInstanceAll, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3703exactlyAssertedEL_first(argIsa, relationInstanceAll, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3704exactlyAssertedEL_first(argIsa, relationExpansion, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3705exactlyAssertedEL_first(argIsa, relationExistsMinAll, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3706exactlyAssertedEL_first(argIsa, relationExistsMinAll, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3707exactlyAssertedEL_first(argIsa, relationExistsMinAll, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3708exactlyAssertedEL_first(argIsa, relationExistsMinAll, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3709exactlyAssertedEL_first(argIsa, relationExistsMaxAll, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3710exactlyAssertedEL_first(argIsa, relationExistsMaxAll, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3711exactlyAssertedEL_first(argIsa, relationExistsMaxAll, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3712exactlyAssertedEL_first(argIsa, relationExistsMaxAll, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3713exactlyAssertedEL_first(argIsa, relationExistsInstance, 3, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3714exactlyAssertedEL_first(argIsa, relationExistsInstance, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3715exactlyAssertedEL_first(argIsa, relationExistsInstance, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3716exactlyAssertedEL_first(argIsa, relationExistsCountAll, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3717exactlyAssertedEL_first(argIsa, relationExistsCountAll, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3718exactlyAssertedEL_first(argIsa, relationExistsCountAll, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3719exactlyAssertedEL_first(argIsa, relationExistsCountAll, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3720exactlyAssertedEL_first(argIsa, relationExistsAll, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3721exactlyAssertedEL_first(argIsa, relationExistsAll, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3722exactlyAssertedEL_first(argIsa, relationExistsAll, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3723exactlyAssertedEL_first(argIsa, relationAllInstance, 3, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3724exactlyAssertedEL_first(argIsa, relationAllInstance, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3725exactlyAssertedEL_first(argIsa, relationAllInstance, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3726exactlyAssertedEL_first(argIsa, relationAllExistsMin, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3727exactlyAssertedEL_first(argIsa, relationAllExistsMin, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3728exactlyAssertedEL_first(argIsa, relationAllExistsMin, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3729exactlyAssertedEL_first(argIsa, relationAllExistsMin, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3730exactlyAssertedEL_first(argIsa, relationAllExistsMax, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3731exactlyAssertedEL_first(argIsa, relationAllExistsMax, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3732exactlyAssertedEL_first(argIsa, relationAllExistsMax, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3733exactlyAssertedEL_first(argIsa, relationAllExistsMax, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3734exactlyAssertedEL_first(argIsa, relationAllExistsCount, 4, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3735exactlyAssertedEL_first(argIsa, relationAllExistsCount, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3736exactlyAssertedEL_first(argIsa, relationAllExistsCount, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3737exactlyAssertedEL_first(argIsa, relationAllExistsCount, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3738exactlyAssertedEL_first(argIsa, relationAllExists, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3739exactlyAssertedEL_first(argIsa, relationAllExists, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3740exactlyAssertedEL_first(argIsa, relationAllExists, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3741exactlyAssertedEL_first(argIsa, relationAll, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3742exactlyAssertedEL_first(argIsa, relationAll, 1, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3743exactlyAssertedEL_first(argIsa, reformulatorRuleProperties, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3744exactlyAssertedEL_first(argIsa, reformulatorRule, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3745exactlyAssertedEL_first(argIsa, reformulatorRule, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3746exactlyAssertedEL_first(argIsa, reformulatorEquals, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3747exactlyAssertedEL_first(argIsa, reformulatorEquals, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3748exactlyAssertedEL_first(argIsa, reformulationPrecondition, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3749exactlyAssertedEL_first(argIsa, reformulationPrecondition, 2, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 3750exactlyAssertedEL_first(argIsa, reformulationPrecondition, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3751exactlyAssertedEL_first(argIsa, reformulationDirectionInMode, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3752exactlyAssertedEL_first(argIsa, reformulationDirectionInMode, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3753exactlyAssertedEL_first(argIsa, ratioOfTo, 3, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3754exactlyAssertedEL_first(argIsa, ratioOfTo, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3755exactlyAssertedEL_first(argIsa, ratioOfTo, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3756exactlyAssertedEL_first(argIsa, quotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3757exactlyAssertedEL_first(argIsa, quotedIsa, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3758exactlyAssertedEL_first(argIsa, quotedDefnSufficient, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3759exactlyAssertedEL_first(argIsa, quotedDefnSufficient, 1, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3760exactlyAssertedEL_first(argIsa, quotedDefnNecessary, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3761exactlyAssertedEL_first(argIsa, quotedDefnNecessary, 1, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3762exactlyAssertedEL_first(argIsa, quotedDefnIff, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3763exactlyAssertedEL_first(argIsa, quotedDefnIff, 1, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3764exactlyAssertedEL_first(argIsa, quotedArgument, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3765exactlyAssertedEL_first(argIsa, quotedArgument, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3766exactlyAssertedEL_first(argIsa, quantitySubsumes, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3767exactlyAssertedEL_first(argIsa, quantitySubsumes, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3768exactlyAssertedEL_first(argIsa, quantityIntersects, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3769exactlyAssertedEL_first(argIsa, quantityIntersects, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3770exactlyAssertedEL_first(argIsa, prettyString, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3771exactlyAssertedEL_first(argIsa, prettyString, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3772exactlyAssertedEL_first(argIsa, preservesGenlsInArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3773exactlyAssertedEL_first(argIsa, preservesGenlsInArg, 1, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 3774exactlyAssertedEL_first(argIsa, predicateConventionMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3775exactlyAssertedEL_first(argIsa, predicateConventionMt, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3776exactlyAssertedEL_first(argIsa, pragmaticallyNormal, 1, 'List', 'UniversalVocabularyMt', vStrMon).
 3777exactlyAssertedEL_first(argIsa, pointQuantValue, 2, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 3778exactlyAssertedEL_first(argIsa, pointQuantValue, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3779exactlyAssertedEL_first(argIsa, pointQuantValue, 1, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 3780exactlyAssertedEL_first(argIsa, performSubL, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3781exactlyAssertedEL_first(argIsa, overlappingExternalConcept, 3, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3782exactlyAssertedEL_first(argIsa, overlappingExternalConcept, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3783exactlyAssertedEL_first(argIsa, operatorFormulas, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3784exactlyAssertedEL_first(argIsa, operatorFormulas, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3785exactlyAssertedEL_first(argIsa, operatorFormulas, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3786exactlyAssertedEL_first(argIsa, openEntryFormatInArgs, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3787exactlyAssertedEL_first(argIsa, openEntryFormatInArgs, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3788exactlyAssertedEL_first(argIsa, opaqueArgument, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3789exactlyAssertedEL_first(argIsa, opaqueArgument, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3790exactlyAssertedEL_first(argIsa, omitArgIsa, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3791exactlyAssertedEL_first(argIsa, omitArgIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3792exactlyAssertedEL_first(argIsa, oldConstantName, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3793exactlyAssertedEL_first(argIsa, oldConstantName, 2, 'CharacterString', 'BookkeepingMt', vStrDef).
 3794exactlyAssertedEL_first(argIsa, oldConstantName, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3795exactlyAssertedEL_first(argIsa, oldConstantName, 1, 'Thing', 'BookkeepingMt', vStrDef).
 3796exactlyAssertedEL_first(argIsa, numericallyEquals, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3797exactlyAssertedEL_first(argIsa, numericallyEquals, 2, 'ScalarInterval', 'BaseKB', vStrDef).
 3798exactlyAssertedEL_first(argIsa, numericallyEquals, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3799exactlyAssertedEL_first(argIsa, numericallyEquals, 1, 'ScalarInterval', 'BaseKB', vStrDef).
 3800exactlyAssertedEL_first(argIsa, nthSmallestElement, 4, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 3801exactlyAssertedEL_first(argIsa, nthSmallestElement, 3, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3802exactlyAssertedEL_first(argIsa, nthSmallestElement, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3803exactlyAssertedEL_first(argIsa, nthSmallestElement, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3804exactlyAssertedEL_first(argIsa, nthLargestElement, 4, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 3805exactlyAssertedEL_first(argIsa, nthLargestElement, 3, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3806exactlyAssertedEL_first(argIsa, nthLargestElement, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3807exactlyAssertedEL_first(argIsa, nthLargestElement, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3808exactlyAssertedEL_first(argIsa, notAssertibleMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3809exactlyAssertedEL_first(argIsa, notAssertibleCollection, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3810exactlyAssertedEL_first(argIsa, notAssertible, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3811exactlyAssertedEL_first(argIsa, nonAbducibleWithValueInArg, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3812exactlyAssertedEL_first(argIsa, nonAbducibleWithValueInArg, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3813exactlyAssertedEL_first(argIsa, nonAbducibleWithValueInArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3814exactlyAssertedEL_first(argIsa, negationPreds, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3815exactlyAssertedEL_first(argIsa, negationPreds, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3816exactlyAssertedEL_first(argIsa, negationMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3817exactlyAssertedEL_first(argIsa, negationMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3818exactlyAssertedEL_first(argIsa, negationInverse, 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3819exactlyAssertedEL_first(argIsa, negationInverse, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3820exactlyAssertedEL_first(argIsa, nearestIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3821exactlyAssertedEL_first(argIsa, nearestIsa, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3822exactlyAssertedEL_first(argIsa, nearestGenls, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3823exactlyAssertedEL_first(argIsa, nearestGenls, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3824exactlyAssertedEL_first(argIsa, nearestGenlPreds, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3825exactlyAssertedEL_first(argIsa, nearestGenlPreds, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3826exactlyAssertedEL_first(argIsa, nearestGenlMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3827exactlyAssertedEL_first(argIsa, nearestGenlMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3828exactlyAssertedEL_first(argIsa, nearestDifferentIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3829exactlyAssertedEL_first(argIsa, nearestDifferentIsa, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3830exactlyAssertedEL_first(argIsa, nearestDifferentIsa, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3831exactlyAssertedEL_first(argIsa, nearestDifferentGenls, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3832exactlyAssertedEL_first(argIsa, nearestDifferentGenls, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3833exactlyAssertedEL_first(argIsa, nearestDifferentGenls, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3834exactlyAssertedEL_first(argIsa, nearestCommonSpecs, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3835exactlyAssertedEL_first(argIsa, nearestCommonSpecs, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3836exactlyAssertedEL_first(argIsa, nearestCommonSpecs, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3837exactlyAssertedEL_first(argIsa, nearestCommonIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3838exactlyAssertedEL_first(argIsa, nearestCommonIsa, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3839exactlyAssertedEL_first(argIsa, nearestCommonIsa, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3840exactlyAssertedEL_first(argIsa, nearestCommonGenls, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3841exactlyAssertedEL_first(argIsa, nearestCommonGenls, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3842exactlyAssertedEL_first(argIsa, nearestCommonGenls, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3843exactlyAssertedEL_first(argIsa, nearestCommonGenlMt, 3, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3844exactlyAssertedEL_first(argIsa, nearestCommonGenlMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3845exactlyAssertedEL_first(argIsa, nearestCommonGenlMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3846exactlyAssertedEL_first(argIsa, natFunction, 2, 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 3847exactlyAssertedEL_first(argIsa, natFunction, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3848exactlyAssertedEL_first(argIsa, natArgumentsEqual, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3849exactlyAssertedEL_first(argIsa, natArgumentsEqual, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3850exactlyAssertedEL_first(argIsa, natArgument, 3, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3851exactlyAssertedEL_first(argIsa, natArgument, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3852exactlyAssertedEL_first(argIsa, natArgument, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3853exactlyAssertedEL_first(argIsa, myCreator, 2, 'Cyclist', 'UniversalVocabularyMt', vStrDef).
 3854exactlyAssertedEL_first(argIsa, myCreator, 2, 'Cyclist', 'BookkeepingMt', vStrDef).
 3855exactlyAssertedEL_first(argIsa, myCreator, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3856exactlyAssertedEL_first(argIsa, myCreator, 1, 'Thing', 'BookkeepingMt', vStrDef).
 3857exactlyAssertedEL_first(argIsa, myCreationTime, 2, 'Integer', 'UniversalVocabularyMt', vStrDef).
 3858exactlyAssertedEL_first(argIsa, myCreationTime, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3859exactlyAssertedEL_first(argIsa, myCreationTime, 1, 'Thing', 'BookkeepingMt', vStrDef).
 3860exactlyAssertedEL_first(argIsa, myCreationSecond, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3861exactlyAssertedEL_first(argIsa, myCreationSecond, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3862exactlyAssertedEL_first(argIsa, myCreationSecond, 1, 'Thing', 'BookkeepingMt', vStrDef).
 3863exactlyAssertedEL_first(argIsa, myCreationPurpose, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3864exactlyAssertedEL_first(argIsa, myCreationPurpose, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3865exactlyAssertedEL_first(argIsa, myCreationPurpose, 1, 'Thing', 'BookkeepingMt', vStrDef).
 3866exactlyAssertedEL_first(argIsa, multiplicationUnits, 3, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 3867exactlyAssertedEL_first(argIsa, multiplicationUnits, 2, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 3868exactlyAssertedEL_first(argIsa, multiplicationUnits, 1, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 3869exactlyAssertedEL_first(argIsa, mtVisible, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3870exactlyAssertedEL_first(argIsa, minQuantValue, 2, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 3871exactlyAssertedEL_first(argIsa, minQuantValue, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3872exactlyAssertedEL_first(argIsa, minimizeExtent, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3873exactlyAssertedEL_first(argIsa, microtheoryDesignationArgnum, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3874exactlyAssertedEL_first(argIsa, microtheoryDesignationArgnum, 1, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 3875exactlyAssertedEL_first(argIsa, meetsPragmaticRequirement, 1, 'List', 'UniversalVocabularyMt', vStrMon).
 3876exactlyAssertedEL_first(argIsa, means, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3877exactlyAssertedEL_first(argIsa, means, 1, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 3878exactlyAssertedEL_first(argIsa, maxQuantValue, 2, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 3879exactlyAssertedEL_first(argIsa, maxQuantValue, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3880exactlyAssertedEL_first(argIsa, ist, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3881exactlyAssertedEL_first(argIsa, ist, 1, 'Microtheory', 'LogicalTruthMt', vStrDef).
 3882exactlyAssertedEL_first(argIsa, isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3883exactlyAssertedEL_first(argIsa, isa, 2, tCol, 'LogicalTruthMt', vStrDef).
 3884exactlyAssertedEL_first(argIsa, isa, 2, tCol, 'BaseKB', vStrDef).
 3885exactlyAssertedEL_first(argIsa, isa, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3886exactlyAssertedEL_first(argIsa, isa, 1, 'Thing', 'LogicalTruthMt', vStrDef).
 3887exactlyAssertedEL_first(argIsa, isa, 1, 'Thing', 'BaseKB', vStrDef).
 3888exactlyAssertedEL_first(argIsa, irrelevantTerm, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3889exactlyAssertedEL_first(argIsa, irrelevantPredAssertion, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3890exactlyAssertedEL_first(argIsa, irrelevantMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3891exactlyAssertedEL_first(argIsa, interArgResultIsaReln, 5, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3892exactlyAssertedEL_first(argIsa, interArgResultIsaReln, 4, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3893exactlyAssertedEL_first(argIsa, interArgResultIsaReln, 3, tPred, 'UniversalVocabularyMt', vStrDef).
 3894exactlyAssertedEL_first(argIsa, interArgResultIsaReln, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3895exactlyAssertedEL_first(argIsa, interArgResultIsaReln, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3896exactlyAssertedEL_first(argIsa, interArgResultIsa, 4, tCol, 'UniversalVocabularyMt', vStrDef).
 3897exactlyAssertedEL_first(argIsa, interArgResultIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3898exactlyAssertedEL_first(argIsa, interArgResultIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3899exactlyAssertedEL_first(argIsa, interArgResultIsa, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3900exactlyAssertedEL_first(argIsa, interArgResultGenlReln, 5, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3901exactlyAssertedEL_first(argIsa, interArgResultGenlReln, 4, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3902exactlyAssertedEL_first(argIsa, interArgResultGenlReln, 3, tPred, 'UniversalVocabularyMt', vStrDef).
 3903exactlyAssertedEL_first(argIsa, interArgResultGenlReln, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3904exactlyAssertedEL_first(argIsa, interArgResultGenlReln, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3905exactlyAssertedEL_first(argIsa, interArgResultGenl, 4, tCol, 'UniversalVocabularyMt', vStrDef).
 3906exactlyAssertedEL_first(argIsa, interArgResultGenl, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3907exactlyAssertedEL_first(argIsa, interArgResultGenl, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3908exactlyAssertedEL_first(argIsa, interArgResultGenl, 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 3909exactlyAssertedEL_first(argIsa, interArgIsa, 5, tCol, 'UniversalVocabularyMt', vStrDef).
 3910exactlyAssertedEL_first(argIsa, interArgIsa, 4, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3911exactlyAssertedEL_first(argIsa, interArgIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 3912exactlyAssertedEL_first(argIsa, interArgIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3913exactlyAssertedEL_first(argIsa, interArgIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3914exactlyAssertedEL_first(argIsa, interArgDifferent, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3915exactlyAssertedEL_first(argIsa, interArgDifferent, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3916exactlyAssertedEL_first(argIsa, interArgDifferent, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3917exactlyAssertedEL_first(argIsa, integerBetween, 3, 'Integer', 'UniversalVocabularyMt', vStrDef).
 3918exactlyAssertedEL_first(argIsa, integerBetween, 2, 'Integer', 'UniversalVocabularyMt', vStrDef).
 3919exactlyAssertedEL_first(argIsa, integerBetween, 1, 'Integer', 'UniversalVocabularyMt', vStrDef).
 3920exactlyAssertedEL_first(argIsa, instanceElementType, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3921exactlyAssertedEL_first(argIsa, instanceElementType, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3922exactlyAssertedEL_first(argIsa, indexicalReferent, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3923exactlyAssertedEL_first(argIsa, indexicalReferent, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3924exactlyAssertedEL_first(argIsa, independentArg, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3925exactlyAssertedEL_first(argIsa, independentArg, 1, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3926exactlyAssertedEL_first(argIsa, independentArg, 1, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 3927exactlyAssertedEL_first(argIsa, hypotheticalTerm, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3928exactlyAssertedEL_first(argIsa, holdsIn, 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3929exactlyAssertedEL_first(argIsa, hlPrototypicalInstance, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3930exactlyAssertedEL_first(argIsa, hlPrototypicalInstance, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3931exactlyAssertedEL_first(argIsa, highlyRelevantTerm, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3932exactlyAssertedEL_first(argIsa, highlyRelevantPredAssertion, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3933exactlyAssertedEL_first(argIsa, highlyRelevantMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3934exactlyAssertedEL_first(argIsa, greaterThanOrEqualTo, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3935exactlyAssertedEL_first(argIsa, greaterThanOrEqualTo, 2, 'ScalarInterval', 'BaseKB', vStrDef).
 3936exactlyAssertedEL_first(argIsa, greaterThanOrEqualTo, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3937exactlyAssertedEL_first(argIsa, greaterThanOrEqualTo, 1, 'ScalarInterval', 'BaseKB', vStrDef).
 3938exactlyAssertedEL_first(argIsa, greaterThan, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3939exactlyAssertedEL_first(argIsa, greaterThan, 2, 'ScalarInterval', 'BaseKB', vStrDef).
 3940exactlyAssertedEL_first(argIsa, greaterThan, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3941exactlyAssertedEL_first(argIsa, greaterThan, 1, 'ScalarInterval', 'BaseKB', vStrDef).
 3942exactlyAssertedEL_first(argIsa, genMassNoun, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3943exactlyAssertedEL_first(argIsa, genls, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 3944exactlyAssertedEL_first(argIsa, genls, 2, tCol, 'LogicalTruthMt', vStrDef).
 3945exactlyAssertedEL_first(argIsa, genls, 2, tCol, 'BaseKB', vStrDef).
 3946exactlyAssertedEL_first(argIsa, genls, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3947exactlyAssertedEL_first(argIsa, genls, 1, tCol, 'LogicalTruthMt', vStrDef).
 3948exactlyAssertedEL_first(argIsa, genls, 1, tCol, 'BaseKB', vStrDef).
 3949exactlyAssertedEL_first(argIsa, genlPreds, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 3950exactlyAssertedEL_first(argIsa, genlPreds, 2, tPred, 'BaseKB', vStrDef).
 3951exactlyAssertedEL_first(argIsa, genlPreds, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 3952exactlyAssertedEL_first(argIsa, genlPreds, 1, tPred, 'BaseKB', vStrDef).
 3953exactlyAssertedEL_first(argIsa, genlMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3954exactlyAssertedEL_first(argIsa, genlMt, 2, 'Microtheory', 'LogicalTruthMt', vStrDef).
 3955exactlyAssertedEL_first(argIsa, genlMt, 2, 'Microtheory', 'BaseKB', vStrDef).
 3956exactlyAssertedEL_first(argIsa, genlMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3957exactlyAssertedEL_first(argIsa, genlMt, 1, 'Microtheory', 'LogicalTruthMt', vStrDef).
 3958exactlyAssertedEL_first(argIsa, genlMt, 1, 'Microtheory', 'BaseKB', vStrDef).
 3959exactlyAssertedEL_first(argIsa, genlInverse, 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3960exactlyAssertedEL_first(argIsa, genlInverse, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3961exactlyAssertedEL_first(argIsa, genlCanonicalizerDirectives, 2, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 3962exactlyAssertedEL_first(argIsa, genlCanonicalizerDirectives, 1, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 3963exactlyAssertedEL_first(argIsa, genKeyword, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3964exactlyAssertedEL_first(argIsa, genFormat, 3, 'List', 'UniversalVocabularyMt', vStrDef).
 3965exactlyAssertedEL_first(argIsa, genFormat, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3966exactlyAssertedEL_first(argIsa, genFormat, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3967exactlyAssertedEL_first(argIsa, formulaArity, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3968exactlyAssertedEL_first(argIsa, formulaArity, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3969exactlyAssertedEL_first(argIsa, followingValue, 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3970exactlyAssertedEL_first(argIsa, followingValue, 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 3971exactlyAssertedEL_first(argIsa, fanOutArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 3972exactlyAssertedEL_first(argIsa, fanOutArg, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3973exactlyAssertedEL_first(argIsa, extentCardinality, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 3974exactlyAssertedEL_first(argIsa, extentCardinality, 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 3975exactlyAssertedEL_first(argIsa, extConceptOverlapsColAndReln, 4, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 3976exactlyAssertedEL_first(argIsa, extConceptOverlapsColAndReln, 3, 'Individual', 'UniversalVocabularyMt', vStrDef).
 3977exactlyAssertedEL_first(argIsa, extConceptOverlapsColAndReln, 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 3978exactlyAssertedEL_first(argIsa, extConceptOverlapsColAndReln, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 3979exactlyAssertedEL_first(argIsa, expresses, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3980exactlyAssertedEL_first(argIsa, expresses, 1, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 3981exactlyAssertedEL_first(argIsa, expansionDefn, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3982exactlyAssertedEL_first(argIsa, expansionDefn, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3983exactlyAssertedEL_first(argIsa, expansion, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3984exactlyAssertedEL_first(argIsa, expansion, 2, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 3985exactlyAssertedEL_first(argIsa, expansion, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 3986exactlyAssertedEL_first(argIsa, exceptMt, 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 3987exactlyAssertedEL_first(argIsa, exceptFor, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3988exactlyAssertedEL_first(argIsa, exampleAssertions, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3989exactlyAssertedEL_first(argIsa, evaluationResultQuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 3990exactlyAssertedEL_first(argIsa, evaluationResultQuotedIsa, 1, 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 3991exactlyAssertedEL_first(argIsa, evaluationDefn, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3992exactlyAssertedEL_first(argIsa, evaluationDefn, 1, 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 3993exactlyAssertedEL_first(argIsa, evaluateImmediately, 1, 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 3994exactlyAssertedEL_first(argIsa, evaluateAtEL, 1, 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 3995exactlyAssertedEL_first(argIsa, evaluate, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3996exactlyAssertedEL_first(argIsa, evaluate, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3997exactlyAssertedEL_first(argIsa, equalSymbols, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3998exactlyAssertedEL_first(argIsa, equalSymbols, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 3999exactlyAssertedEL_first(argIsa, equals, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4000exactlyAssertedEL_first(argIsa, equals, 2, 'Thing', 'LogicalTruthMt', vStrDef).
 4001exactlyAssertedEL_first(argIsa, equals, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4002exactlyAssertedEL_first(argIsa, equals, 1, 'Thing', 'LogicalTruthMt', vStrDef).
 4003exactlyAssertedEL_first(argIsa, ephemeralTerm, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4004exactlyAssertedEL_first(argIsa, elInverse, 2, 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 4005exactlyAssertedEL_first(argIsa, elInverse, 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4006exactlyAssertedEL_first(argIsa, elInverse, 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4007exactlyAssertedEL_first(argIsa, elementOf, 2, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4008exactlyAssertedEL_first(argIsa, elementOf, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4009exactlyAssertedEL_first(argIsa, distributesOutOfArg, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4010exactlyAssertedEL_first(argIsa, distributesOutOfArg, 2, tPred, 'UniversalVocabularyMt', vStrDef).
 4011exactlyAssertedEL_first(argIsa, distributesOutOfArg, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4012exactlyAssertedEL_first(argIsa, disjointWith, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4013exactlyAssertedEL_first(argIsa, disjointWith, 2, tCol, 'LogicalTruthMt', vStrDef).
 4014exactlyAssertedEL_first(argIsa, disjointWith, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4015exactlyAssertedEL_first(argIsa, disjointWith, 1, tCol, 'LogicalTruthMt', vStrDef).
 4016exactlyAssertedEL_first(argIsa, different, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4017exactlyAssertedEL_first(argIsa, denotes, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4018exactlyAssertedEL_first(argIsa, denotes, 1, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4019exactlyAssertedEL_first(argIsa, defnSufficient, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4020exactlyAssertedEL_first(argIsa, defnSufficient, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4021exactlyAssertedEL_first(argIsa, defnNecessary, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4022exactlyAssertedEL_first(argIsa, defnNecessary, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4023exactlyAssertedEL_first(argIsa, defnIff, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4024exactlyAssertedEL_first(argIsa, defnIff, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4025exactlyAssertedEL_first(argIsa, defnIff, 1, tCol, 'LogicalTruthImplementationMt', vStrDef).
 4026exactlyAssertedEL_first(argIsa, definingMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4027exactlyAssertedEL_first(argIsa, definingMt, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4028exactlyAssertedEL_first(argIsa, defaultReformulatorModePrecedence, 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4029exactlyAssertedEL_first(argIsa, defaultReformulationDirectionInModeForPred, 3, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
 4030exactlyAssertedEL_first(argIsa, defaultReformulationDirectionInModeForPred, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4031exactlyAssertedEL_first(argIsa, defaultReformulationDirectionInModeForPred, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4032exactlyAssertedEL_first(argIsa, decontextualizedPredicate, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4033exactlyAssertedEL_first(argIsa, decontextualizedCollection, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4034exactlyAssertedEL_first(argIsa, cycTransformationProofRule, 1, 'CycTransformationProof', 'UniversalVocabularyMt', vStrDef).
 4035exactlyAssertedEL_first(argIsa, cycTransformationProofBindings, 2, 'List', 'UniversalVocabularyMt', vStrDef).
 4036exactlyAssertedEL_first(argIsa, cycTransformationProofBindings, 1, 'CycTransformationProof', 'UniversalVocabularyMt', vStrDef).
 4037exactlyAssertedEL_first(argIsa, cycTacticID, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4038exactlyAssertedEL_first(argIsa, cycTacticID, 2, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4039exactlyAssertedEL_first(argIsa, cycTacticID, 1, 'CycTactic', 'UniversalVocabularyMt', vStrDef).
 4040exactlyAssertedEL_first(argIsa, cycProofID, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4041exactlyAssertedEL_first(argIsa, cycProofID, 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4042exactlyAssertedEL_first(argIsa, cycProofID, 1, 'CycProof', 'UniversalVocabularyMt', vStrDef).
 4043exactlyAssertedEL_first(argIsa, cycProblemStoreTerms, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4044exactlyAssertedEL_first(argIsa, cycProblemStoreTerms, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4045exactlyAssertedEL_first(argIsa, cycProblemStoreProofs, 2, 'CycProof', 'UniversalVocabularyMt', vStrDef).
 4046exactlyAssertedEL_first(argIsa, cycProblemStoreProofs, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4047exactlyAssertedEL_first(argIsa, cycProblemStoreProofCount, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4048exactlyAssertedEL_first(argIsa, cycProblemStoreProofCount, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4049exactlyAssertedEL_first(argIsa, cycProblemStoreProblems, 2, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4050exactlyAssertedEL_first(argIsa, cycProblemStoreProblems, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4051exactlyAssertedEL_first(argIsa, cycProblemStoreProblemCount, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4052exactlyAssertedEL_first(argIsa, cycProblemStoreProblemCount, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4053exactlyAssertedEL_first(argIsa, cycProblemStoreLinks, 2, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4054exactlyAssertedEL_first(argIsa, cycProblemStoreLinks, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4055exactlyAssertedEL_first(argIsa, cycProblemStoreLinkCount, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4056exactlyAssertedEL_first(argIsa, cycProblemStoreLinkCount, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4057exactlyAssertedEL_first(argIsa, cycProblemStoreInferences, 2, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 4058exactlyAssertedEL_first(argIsa, cycProblemStoreInferences, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4059exactlyAssertedEL_first(argIsa, cycProblemStoreInferenceCount, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4060exactlyAssertedEL_first(argIsa, cycProblemStoreInferenceCount, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4061exactlyAssertedEL_first(argIsa, cycProblemStoreID, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4062exactlyAssertedEL_first(argIsa, cycProblemStoreID, 1, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4063exactlyAssertedEL_first(argIsa, cycProblemQueryTerms, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4064exactlyAssertedEL_first(argIsa, cycProblemQueryTerms, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4065exactlyAssertedEL_first(argIsa, cycProblemQuerySentence, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4066exactlyAssertedEL_first(argIsa, cycProblemProvabilityStatus, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4067exactlyAssertedEL_first(argIsa, cycProblemProvabilityStatus, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4068exactlyAssertedEL_first(argIsa, cycProblemLinkID, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4069exactlyAssertedEL_first(argIsa, cycProblemLinkID, 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4070exactlyAssertedEL_first(argIsa, cycProblemLinkID, 1, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4071exactlyAssertedEL_first(argIsa, cycProblemID, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4072exactlyAssertedEL_first(argIsa, cycProblemID, 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4073exactlyAssertedEL_first(argIsa, cycProblemID, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4074exactlyAssertedEL_first(argIsa, cycProblemDependentLinks, 2, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4075exactlyAssertedEL_first(argIsa, cycProblemDependentLinks, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4076exactlyAssertedEL_first(argIsa, cycProblemArgumentLinks, 2, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4077exactlyAssertedEL_first(argIsa, cycProblemArgumentLinks, 1, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4078exactlyAssertedEL_first(argIsa, cycInferenceRelevantProblems, 2, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4079exactlyAssertedEL_first(argIsa, cycInferenceRelevantProblems, 1, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 4080exactlyAssertedEL_first(argIsa, cycInferenceAnswerLink, 2, 'CycProblemLink-AnswerLink', 'UniversalVocabularyMt', vStrDef).
 4081exactlyAssertedEL_first(argIsa, cycInferenceAnswerLink, 1, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 4082exactlyAssertedEL_first(argIsa, constrainsArg, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4083exactlyAssertedEL_first(argIsa, constrainsArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4084exactlyAssertedEL_first(argIsa, constantName, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4085exactlyAssertedEL_first(argIsa, constantName, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4086exactlyAssertedEL_first(argIsa, constantID, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4087exactlyAssertedEL_first(argIsa, constantID, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4088exactlyAssertedEL_first(argIsa, constantGUID, 2, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4089exactlyAssertedEL_first(argIsa, constantGUID, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4090exactlyAssertedEL_first(argIsa, conceptuallyRelated, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4091exactlyAssertedEL_first(argIsa, conceptuallyRelated, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4092exactlyAssertedEL_first(argIsa, completelyEnumerableCollection, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4093exactlyAssertedEL_first(argIsa, completelyDecidableCollection, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4094exactlyAssertedEL_first(argIsa, completeExtentEnumerableViaBackchain, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4095exactlyAssertedEL_first(argIsa, completeExtentEnumerableForValueInArg, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4096exactlyAssertedEL_first(argIsa, completeExtentEnumerableForValueInArg, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4097exactlyAssertedEL_first(argIsa, completeExtentEnumerableForValueInArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4098exactlyAssertedEL_first(argIsa, completeExtentEnumerableForArg, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4099exactlyAssertedEL_first(argIsa, completeExtentEnumerableForArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4100exactlyAssertedEL_first(argIsa, completeExtentEnumerable, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4101exactlyAssertedEL_first(argIsa, completeExtentDecidableForValueInArg, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4102exactlyAssertedEL_first(argIsa, completeExtentDecidableForValueInArg, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4103exactlyAssertedEL_first(argIsa, completeExtentDecidableForValueInArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4104exactlyAssertedEL_first(argIsa, completeExtentDecidable, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4105exactlyAssertedEL_first(argIsa, completeExtentAssertedForValueInArg, 3, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4106exactlyAssertedEL_first(argIsa, completeExtentAssertedForValueInArg, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4107exactlyAssertedEL_first(argIsa, completeExtentAssertedForValueInArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4108exactlyAssertedEL_first(argIsa, completeExtentAsserted, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4109exactlyAssertedEL_first(argIsa, commutativeInArgsAndRest, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4110exactlyAssertedEL_first(argIsa, commutativeInArgsAndRest, 1, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 4111exactlyAssertedEL_first(argIsa, commutativeInArgs, 3, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4112exactlyAssertedEL_first(argIsa, commutativeInArgs, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4113exactlyAssertedEL_first(argIsa, commutativeInArgs, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4114exactlyAssertedEL_first(argIsa, comment, 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4115exactlyAssertedEL_first(argIsa, comment, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4116exactlyAssertedEL_first(argIsa, collectionIsaBackchainRequired, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4117exactlyAssertedEL_first(argIsa, collectionIsaBackchainEncouraged, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4118exactlyAssertedEL_first(argIsa, collectionGenlsBackchainRequired, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4119exactlyAssertedEL_first(argIsa, collectionGenlsBackchainEncouraged, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4120exactlyAssertedEL_first(argIsa, collectionExpansion, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4121exactlyAssertedEL_first(argIsa, collectionExpansion, 2, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 4122exactlyAssertedEL_first(argIsa, collectionExpansion, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4123exactlyAssertedEL_first(argIsa, collectionConventionMt, 2, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4124exactlyAssertedEL_first(argIsa, collectionConventionMt, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4125exactlyAssertedEL_first(argIsa, collectionCompletelyEnumerableViaBackchain, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4126exactlyAssertedEL_first(argIsa, collectionBackchainRequired, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4127exactlyAssertedEL_first(argIsa, collectionBackchainEncouraged, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4128exactlyAssertedEL_first(argIsa, coExtensional, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4129exactlyAssertedEL_first(argIsa, coExtensional, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4130exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArgAndRest, 3, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4131exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArgAndRest, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4132exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArgAndRest, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4133exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArg, 3, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4134exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4135exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForArg, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4136exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForAllArgs, 2, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4137exactlyAssertedEL_first(argIsa, canonicalizerDirectiveForAllArgs, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4138exactlyAssertedEL_first(argIsa, backchainRequired, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4139exactlyAssertedEL_first(argIsa, backchainForbiddenWhenUnboundInArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4140exactlyAssertedEL_first(argIsa, backchainForbiddenWhenUnboundInArg, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4141exactlyAssertedEL_first(argIsa, backchainForbidden, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4142exactlyAssertedEL_first(argIsa, assertionUtility, 2, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 4143exactlyAssertedEL_first(argIsa, assertionDirection, 2, 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 4144exactlyAssertedEL_first(argIsa, assertedTermSentences, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4145exactlyAssertedEL_first(argIsa, assertedPredicateArg, 3, tPred, 'UniversalVocabularyMt', vStrDef).
 4146exactlyAssertedEL_first(argIsa, assertedPredicateArg, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4147exactlyAssertedEL_first(argIsa, assertedPredicateArg, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4148exactlyAssertedEL_first(argIsa, arityMin, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4149exactlyAssertedEL_first(argIsa, arityMin, 1, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 4150exactlyAssertedEL_first(argIsa, arityMax, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4151exactlyAssertedEL_first(argIsa, arityMax, 1, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 4152exactlyAssertedEL_first(argIsa, arity, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4153exactlyAssertedEL_first(argIsa, arity, 2, 'NonNegativeInteger', 'LogicalTruthMt', vStrDef).
 4154exactlyAssertedEL_first(argIsa, arity, 2, 'Integer', 'UniversalVocabularyMt', vStrDef).
 4155exactlyAssertedEL_first(argIsa, arity, 1, 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 4156exactlyAssertedEL_first(argIsa, arity, 1, 'FixedArityRelation', 'LogicalTruthMt', vStrDef).
 4157exactlyAssertedEL_first(argIsa, argsQuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4158exactlyAssertedEL_first(argIsa, argsQuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4159exactlyAssertedEL_first(argIsa, argSometimesIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4160exactlyAssertedEL_first(argIsa, argSometimesIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4161exactlyAssertedEL_first(argIsa, argSometimesIsa, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4162exactlyAssertedEL_first(argIsa, argSometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4163exactlyAssertedEL_first(argIsa, argsIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4164exactlyAssertedEL_first(argIsa, argsIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4165exactlyAssertedEL_first(argIsa, argsGenl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4166exactlyAssertedEL_first(argIsa, argsGenl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4167exactlyAssertedEL_first(argIsa, argQuotedIsa, 3, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4168exactlyAssertedEL_first(argIsa, argQuotedIsa, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4169exactlyAssertedEL_first(argIsa, argQuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4170exactlyAssertedEL_first(argIsa, argIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4171exactlyAssertedEL_first(argIsa, argIsa, 3, tCol, 'LogicalTruthMt', vStrDef).
 4172exactlyAssertedEL_first(argIsa, argIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4173exactlyAssertedEL_first(argIsa, argIsa, 2, 'PositiveInteger', 'LogicalTruthMt', vStrDef).
 4174exactlyAssertedEL_first(argIsa, argIsa, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4175exactlyAssertedEL_first(argIsa, argIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4176exactlyAssertedEL_first(argIsa, argIsa, 1, tRelation, 'LogicalTruthMt', vStrDef).
 4177exactlyAssertedEL_first(argIsa, argAndRestQuotedIsa, 3, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4178exactlyAssertedEL_first(argIsa, argAndRestQuotedIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4179exactlyAssertedEL_first(argIsa, argAndRestQuotedIsa, 1, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 4180exactlyAssertedEL_first(argIsa, argAndRestIsa, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4181exactlyAssertedEL_first(argIsa, argAndRestIsa, 3, tCol, 'LogicalTruthMt', vStrDef).
 4182exactlyAssertedEL_first(argIsa, argAndRestIsa, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4183exactlyAssertedEL_first(argIsa, argAndRestIsa, 2, 'PositiveInteger', 'LogicalTruthMt', vStrDef).
 4184exactlyAssertedEL_first(argIsa, argAndRestIsa, 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4185exactlyAssertedEL_first(argIsa, argAndRestIsa, 1, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 4186exactlyAssertedEL_first(argIsa, argAndRestIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4187exactlyAssertedEL_first(argIsa, argAndRestIsa, 1, tRelation, 'LogicalTruthMt', vStrDef).
 4188exactlyAssertedEL_first(argIsa, argAndRestGenl, 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4189exactlyAssertedEL_first(argIsa, argAndRestGenl, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4190exactlyAssertedEL_first(argIsa, argAndRestGenl, 1, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 4191exactlyAssertedEL_first(argIsa, arg6SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4192exactlyAssertedEL_first(argIsa, arg6SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4193exactlyAssertedEL_first(argIsa, arg6QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4194exactlyAssertedEL_first(argIsa, arg6QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4195exactlyAssertedEL_first(argIsa, arg6Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4196exactlyAssertedEL_first(argIsa, arg6Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4197exactlyAssertedEL_first(argIsa, arg6Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4198exactlyAssertedEL_first(argIsa, arg6Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4199exactlyAssertedEL_first(argIsa, arg6Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4200exactlyAssertedEL_first(argIsa, arg6Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4201exactlyAssertedEL_first(argIsa, arg5SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4202exactlyAssertedEL_first(argIsa, arg5SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4203exactlyAssertedEL_first(argIsa, arg5QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4204exactlyAssertedEL_first(argIsa, arg5QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4205exactlyAssertedEL_first(argIsa, arg5Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4206exactlyAssertedEL_first(argIsa, arg5Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4207exactlyAssertedEL_first(argIsa, arg5Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4208exactlyAssertedEL_first(argIsa, arg5Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4209exactlyAssertedEL_first(argIsa, arg5Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4210exactlyAssertedEL_first(argIsa, arg5Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4211exactlyAssertedEL_first(argIsa, arg4SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4212exactlyAssertedEL_first(argIsa, arg4SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4213exactlyAssertedEL_first(argIsa, arg4QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4214exactlyAssertedEL_first(argIsa, arg4QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4215exactlyAssertedEL_first(argIsa, arg4Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4216exactlyAssertedEL_first(argIsa, arg4Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4217exactlyAssertedEL_first(argIsa, arg4Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4218exactlyAssertedEL_first(argIsa, arg4Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4219exactlyAssertedEL_first(argIsa, arg4Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4220exactlyAssertedEL_first(argIsa, arg4Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4221exactlyAssertedEL_first(argIsa, arg3SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4222exactlyAssertedEL_first(argIsa, arg3SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4223exactlyAssertedEL_first(argIsa, arg3QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4224exactlyAssertedEL_first(argIsa, arg3QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4225exactlyAssertedEL_first(argIsa, arg3Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4226exactlyAssertedEL_first(argIsa, arg3Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4227exactlyAssertedEL_first(argIsa, arg3Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4228exactlyAssertedEL_first(argIsa, arg3Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4229exactlyAssertedEL_first(argIsa, arg3Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4230exactlyAssertedEL_first(argIsa, arg3Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4231exactlyAssertedEL_first(argIsa, arg2SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4232exactlyAssertedEL_first(argIsa, arg2SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4233exactlyAssertedEL_first(argIsa, arg2QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4234exactlyAssertedEL_first(argIsa, arg2QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4235exactlyAssertedEL_first(argIsa, arg2Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4236exactlyAssertedEL_first(argIsa, arg2Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4237exactlyAssertedEL_first(argIsa, arg2Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4238exactlyAssertedEL_first(argIsa, arg2Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4239exactlyAssertedEL_first(argIsa, arg2Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4240exactlyAssertedEL_first(argIsa, arg2Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4241exactlyAssertedEL_first(argIsa, arg1SometimesIsa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4242exactlyAssertedEL_first(argIsa, arg1SometimesIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4243exactlyAssertedEL_first(argIsa, arg1QuotedIsa, 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4244exactlyAssertedEL_first(argIsa, arg1QuotedIsa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4245exactlyAssertedEL_first(argIsa, arg1Isa, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4246exactlyAssertedEL_first(argIsa, arg1Isa, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4247exactlyAssertedEL_first(argIsa, arg1Genl, 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4248exactlyAssertedEL_first(argIsa, arg1Genl, 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4249exactlyAssertedEL_first(argIsa, arg1Format, 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4250exactlyAssertedEL_first(argIsa, arg1Format, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4251exactlyAssertedEL_first(argIsa, afterRemoving, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4252exactlyAssertedEL_first(argIsa, afterRemoving, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4253exactlyAssertedEL_first(argIsa, afterRemoving, 1, tPred, 'LogicalTruthImplementationMt', vStrDef).
 4254exactlyAssertedEL_first(argIsa, afterAdding, 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4255exactlyAssertedEL_first(argIsa, afterAdding, 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4256exactlyAssertedEL_first(argIsa, afterAdding, 1, tPred, 'LogicalTruthImplementationMt', vStrDef).
 4257exactlyAssertedEL_first(argIsa, admittedNAT, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4258exactlyAssertedEL_first(argIsa, admittedArgument, 3, tRelation, 'UniversalVocabularyMt', vStrDef).
 4259exactlyAssertedEL_first(argIsa, admittedArgument, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4260exactlyAssertedEL_first(argIsa, admittedArgument, 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4261exactlyAssertedEL_first(argIsa, admittedAllArgument, 3, tRelation, 'UniversalVocabularyMt', vStrDef).
 4262exactlyAssertedEL_first(argIsa, admittedAllArgument, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4263exactlyAssertedEL_first(argIsa, admittedAllArgument, 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4264exactlyAssertedEL_first(argIsa, abnormal, 1, 'List', 'UniversalVocabularyMt', vStrDef).
 4265exactlyAssertedEL_first(argIsa, 'Unity', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4266exactlyAssertedEL_first(argIsa, 'UnitProductFn', 2, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4267exactlyAssertedEL_first(argIsa, 'UnitProductFn', 1, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4268exactlyAssertedEL_first(argIsa, 'UncanonicalizerAssertionFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4269exactlyAssertedEL_first(argIsa, 'TLVariableFn', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4270exactlyAssertedEL_first(argIsa, 'TLVariableFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4271exactlyAssertedEL_first(argIsa, 'TLReifiedNatFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4272exactlyAssertedEL_first(argIsa, 'TLAssertionFn', 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4273exactlyAssertedEL_first(argIsa, 'TimesFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4274exactlyAssertedEL_first(argIsa, 'TheSet', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4275exactlyAssertedEL_first(argIsa, 'TheList', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4276exactlyAssertedEL_first(argIsa, 'substring-CaseInsensitive', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4277exactlyAssertedEL_first(argIsa, 'substring-CaseInsensitive', 1, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4278exactlyAssertedEL_first(argIsa, 'SkolemFuncNFn', 4, 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4279exactlyAssertedEL_first(argIsa, 'RoundUpFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4280exactlyAssertedEL_first(argIsa, 'RoundDownFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4281exactlyAssertedEL_first(argIsa, 'RoundClosestFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4282exactlyAssertedEL_first(argIsa, 'RelationInstanceExistsFn', 3, tCol, 'UniversalVocabularyMt', vStrMon).
 4283exactlyAssertedEL_first(argIsa, 'RelationInstanceExistsFn', 2, 'Thing', 'UniversalVocabularyMt', vStrMon).
 4284exactlyAssertedEL_first(argIsa, 'RelationInstanceExistsFn', 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrMon).
 4285exactlyAssertedEL_first(argIsa, 'RelationExistsInstanceFn', 3, 'Thing', 'UniversalVocabularyMt', vStrMon).
 4286exactlyAssertedEL_first(argIsa, 'RelationExistsInstanceFn', 2, tCol, 'UniversalVocabularyMt', vStrMon).
 4287exactlyAssertedEL_first(argIsa, 'RelationExistsInstanceFn', 1, 'BinaryPredicate', 'UniversalVocabularyMt', vStrMon).
 4288exactlyAssertedEL_first(argIsa, 'RelationExistsAllFn', 4, tCol, 'UniversalVocabularyMt', vStrDef).
 4289exactlyAssertedEL_first(argIsa, 'RelationExistsAllFn', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4290exactlyAssertedEL_first(argIsa, 'RelationExistsAllFn', 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4291exactlyAssertedEL_first(argIsa, 'RelationExistsAllFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4292exactlyAssertedEL_first(argIsa, 'RelationAllExistsFn', 4, tCol, 'UniversalVocabularyMt', vStrDef).
 4293exactlyAssertedEL_first(argIsa, 'RelationAllExistsFn', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4294exactlyAssertedEL_first(argIsa, 'RelationAllExistsFn', 2, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4295exactlyAssertedEL_first(argIsa, 'RelationAllExistsFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4296exactlyAssertedEL_first(argIsa, 'QuotientFn', 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4297exactlyAssertedEL_first(argIsa, 'QuotientFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4298exactlyAssertedEL_first(argIsa, 'Quote', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4299exactlyAssertedEL_first(argIsa, 'QuasiQuote', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4300exactlyAssertedEL_first(argIsa, 'QuantityConversionFn', 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4301exactlyAssertedEL_first(argIsa, 'QuantityConversionFn', 1, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4302exactlyAssertedEL_first(argIsa, 'prettyString-Canonical', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4303exactlyAssertedEL_first(argIsa, 'prettyString-Canonical', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4304exactlyAssertedEL_first(argIsa, 'PlusFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4305exactlyAssertedEL_first(argIsa, 'PlusAll', 2, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4306exactlyAssertedEL_first(argIsa, 'PlusAll', 2, 'UnaryFunction', 'BaseKB', vStrDef).
 4307exactlyAssertedEL_first(argIsa, 'PlusAll', 2, 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 4308exactlyAssertedEL_first(argIsa, 'PlusAll', 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4309exactlyAssertedEL_first(argIsa, 'PlusAll', 1, 'SetOrCollection', 'BaseKB', vStrDef).
 4310exactlyAssertedEL_first(argIsa, 'PerFn', 2, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4311exactlyAssertedEL_first(argIsa, 'PerFn', 1, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4312exactlyAssertedEL_first(argIsa, 'Percent', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4313exactlyAssertedEL_first(argIsa, 'MtUnionFn', 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4314exactlyAssertedEL_first(argIsa, 'MtTimeWithGranularityDimFn', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4315exactlyAssertedEL_first(argIsa, 'MtTimeWithGranularityDimFn', 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4316exactlyAssertedEL_first(argIsa, 'MtTimeDimFn', 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4317exactlyAssertedEL_first(argIsa, 'MtSpace', 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4318exactlyAssertedEL_first(argIsa, 'ModuloFn', 2, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 4319exactlyAssertedEL_first(argIsa, 'ModuloFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4320exactlyAssertedEL_first(argIsa, 'MinRangeFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4321exactlyAssertedEL_first(argIsa, 'Minimum', 2, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4322exactlyAssertedEL_first(argIsa, 'Minimum', 2, 'UnaryFunction', 'BaseKB', vStrDef).
 4323exactlyAssertedEL_first(argIsa, 'Minimum', 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4324exactlyAssertedEL_first(argIsa, 'Minimum', 1, 'SetOrCollection', 'BaseKB', vStrDef).
 4325exactlyAssertedEL_first(argIsa, 'MeaningInSystemFn', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4326exactlyAssertedEL_first(argIsa, 'MeaningInSystemFn', 1, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4327exactlyAssertedEL_first(argIsa, 'MaxRangeFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4328exactlyAssertedEL_first(argIsa, 'Maximum', 2, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4329exactlyAssertedEL_first(argIsa, 'Maximum', 2, 'UnaryFunction', 'BaseKB', vStrDef).
 4330exactlyAssertedEL_first(argIsa, 'Maximum', 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4331exactlyAssertedEL_first(argIsa, 'Maximum', 1, 'SetOrCollection', 'BaseKB', vStrDef).
 4332exactlyAssertedEL_first(argIsa, 'LogFn', 1, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 4333exactlyAssertedEL_first(argIsa, 'LogFn', 1, 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4334exactlyAssertedEL_first(argIsa, 'larkc-hasUri', 2, 'CharacterString', 'BaseKB', vStrDef).
 4335exactlyAssertedEL_first(argIsa, 'larkc-hasUri', 1, 'larkc-Plugin', 'BaseKB', vStrDef).
 4336exactlyAssertedEL_first(argIsa, 'larkc-hasScalability', 2, 'CharacterString', 'BaseKB', vStrDef).
 4337exactlyAssertedEL_first(argIsa, 'larkc-hasScalability', 1, 'larkc-Scalability', 'BaseKB', vStrDef).
 4338exactlyAssertedEL_first(argIsa, 'larkc-hasEndpoint', 2, 'CharacterString', 'BaseKB', vStrDef).
 4339exactlyAssertedEL_first(argIsa, 'larkc-hasEndpoint', 1, 'larkc-Plugin', 'BaseKB', vStrDef).
 4340exactlyAssertedEL_first(argIsa, 'larkc-hasCostPerInvocation', 2, 'larkc-euro', 'BaseKB', vStrDef).
 4341exactlyAssertedEL_first(argIsa, 'larkc-hasCostPerInvocation', 1, 'larkc-Cost', 'BaseKB', vStrDef).
 4342exactlyAssertedEL_first(argIsa, 'ist-Asserted', 1, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4343exactlyAssertedEL_first(argIsa, 'IntervalMinFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4344exactlyAssertedEL_first(argIsa, 'IntervalMaxFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4345exactlyAssertedEL_first(argIsa, 'interArgIsa5-4', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4346exactlyAssertedEL_first(argIsa, 'interArgIsa5-4', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4347exactlyAssertedEL_first(argIsa, 'interArgIsa5-4', 1, 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 4348exactlyAssertedEL_first(argIsa, 'interArgIsa5-3', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4349exactlyAssertedEL_first(argIsa, 'interArgIsa5-3', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4350exactlyAssertedEL_first(argIsa, 'interArgIsa5-3', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4351exactlyAssertedEL_first(argIsa, 'interArgIsa5-3', 1, 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 4352exactlyAssertedEL_first(argIsa, 'interArgIsa5-2', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4353exactlyAssertedEL_first(argIsa, 'interArgIsa5-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4354exactlyAssertedEL_first(argIsa, 'interArgIsa5-2', 1, 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 4355exactlyAssertedEL_first(argIsa, 'interArgIsa5-1', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4356exactlyAssertedEL_first(argIsa, 'interArgIsa5-1', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4357exactlyAssertedEL_first(argIsa, 'interArgIsa5-1', 1, 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 4358exactlyAssertedEL_first(argIsa, 'interArgIsa4-5', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4359exactlyAssertedEL_first(argIsa, 'interArgIsa4-5', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4360exactlyAssertedEL_first(argIsa, 'interArgIsa4-5', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4361exactlyAssertedEL_first(argIsa, 'interArgIsa4-3', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4362exactlyAssertedEL_first(argIsa, 'interArgIsa4-3', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4363exactlyAssertedEL_first(argIsa, 'interArgIsa4-3', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4364exactlyAssertedEL_first(argIsa, 'interArgIsa4-2', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4365exactlyAssertedEL_first(argIsa, 'interArgIsa4-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4366exactlyAssertedEL_first(argIsa, 'interArgIsa4-2', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4367exactlyAssertedEL_first(argIsa, 'interArgIsa4-1', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4368exactlyAssertedEL_first(argIsa, 'interArgIsa4-1', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4369exactlyAssertedEL_first(argIsa, 'interArgIsa4-1', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4370exactlyAssertedEL_first(argIsa, 'interArgIsa3-5', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4371exactlyAssertedEL_first(argIsa, 'interArgIsa3-5', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4372exactlyAssertedEL_first(argIsa, 'interArgIsa3-5', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4373exactlyAssertedEL_first(argIsa, 'interArgIsa3-4', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4374exactlyAssertedEL_first(argIsa, 'interArgIsa3-4', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4375exactlyAssertedEL_first(argIsa, 'interArgIsa3-4', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4376exactlyAssertedEL_first(argIsa, 'interArgIsa3-2', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4377exactlyAssertedEL_first(argIsa, 'interArgIsa3-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4378exactlyAssertedEL_first(argIsa, 'interArgIsa3-2', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4379exactlyAssertedEL_first(argIsa, 'interArgIsa3-1', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4380exactlyAssertedEL_first(argIsa, 'interArgIsa3-1', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4381exactlyAssertedEL_first(argIsa, 'interArgIsa3-1', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4382exactlyAssertedEL_first(argIsa, 'interArgIsa2-5', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4383exactlyAssertedEL_first(argIsa, 'interArgIsa2-5', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4384exactlyAssertedEL_first(argIsa, 'interArgIsa2-5', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4385exactlyAssertedEL_first(argIsa, 'interArgIsa2-4', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4386exactlyAssertedEL_first(argIsa, 'interArgIsa2-4', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4387exactlyAssertedEL_first(argIsa, 'interArgIsa2-4', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4388exactlyAssertedEL_first(argIsa, 'interArgIsa2-3', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4389exactlyAssertedEL_first(argIsa, 'interArgIsa2-3', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4390exactlyAssertedEL_first(argIsa, 'interArgIsa2-3', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4391exactlyAssertedEL_first(argIsa, 'interArgIsa2-1', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4392exactlyAssertedEL_first(argIsa, 'interArgIsa2-1', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4393exactlyAssertedEL_first(argIsa, 'interArgIsa2-1', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4394exactlyAssertedEL_first(argIsa, 'interArgIsa1-5', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4395exactlyAssertedEL_first(argIsa, 'interArgIsa1-5', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4396exactlyAssertedEL_first(argIsa, 'interArgIsa1-5', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4397exactlyAssertedEL_first(argIsa, 'interArgIsa1-4', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4398exactlyAssertedEL_first(argIsa, 'interArgIsa1-4', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4399exactlyAssertedEL_first(argIsa, 'interArgIsa1-4', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4400exactlyAssertedEL_first(argIsa, 'interArgIsa1-3', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4401exactlyAssertedEL_first(argIsa, 'interArgIsa1-3', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4402exactlyAssertedEL_first(argIsa, 'interArgIsa1-3', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4403exactlyAssertedEL_first(argIsa, 'interArgIsa1-2', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4404exactlyAssertedEL_first(argIsa, 'interArgIsa1-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4405exactlyAssertedEL_first(argIsa, 'interArgIsa1-2', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4406exactlyAssertedEL_first(argIsa, 'interArgGenl1-2', 3, tCol, 'UniversalVocabularyMt', vStrDef).
 4407exactlyAssertedEL_first(argIsa, 'interArgGenl1-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4408exactlyAssertedEL_first(argIsa, 'interArgGenl1-2', 1, tRelation, 'UniversalVocabularyMt', vStrDef).
 4409exactlyAssertedEL_first(argIsa, 'interArgFormat1-2', 3, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4410exactlyAssertedEL_first(argIsa, 'interArgFormat1-2', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4411exactlyAssertedEL_first(argIsa, 'interArgFormat1-2', 1, tPred, 'UniversalVocabularyMt', vStrDef).
 4412exactlyAssertedEL_first(argIsa, 'genls-SpecDenotesGenlInstances', 2, tCol, 'UniversalVocabularyMt', vStrDef).
 4413exactlyAssertedEL_first(argIsa, 'genls-SpecDenotesGenlInstances', 1, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4414exactlyAssertedEL_first(argIsa, 'genls-GenlDenotesSpecInstances', 2, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4415exactlyAssertedEL_first(argIsa, 'genls-GenlDenotesSpecInstances', 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4416exactlyAssertedEL_first(argIsa, 'FunctionToArg', 2, tPred, 'UniversalVocabularyMt', vStrDef).
 4417exactlyAssertedEL_first(argIsa, 'FunctionToArg', 1, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4418exactlyAssertedEL_first(argIsa, 'FormulaArityFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4419exactlyAssertedEL_first(argIsa, 'FormulaArgSetFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4420exactlyAssertedEL_first(argIsa, 'FormulaArgListFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4421exactlyAssertedEL_first(argIsa, 'FormulaArgFn', 2, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4422exactlyAssertedEL_first(argIsa, 'FormulaArgFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4423exactlyAssertedEL_first(argIsa, 'FOL-TermFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4424exactlyAssertedEL_first(argIsa, 'FOL-PredicateFn', 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4425exactlyAssertedEL_first(argIsa, 'FOL-PredicateFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4426exactlyAssertedEL_first(argIsa, 'FOL-FunctionFn', 2, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4427exactlyAssertedEL_first(argIsa, 'FOL-FunctionFn', 1, tFunction, 'UniversalVocabularyMt', vStrDef).
 4428exactlyAssertedEL_first(argIsa, 'ExpFn', 1, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 4429exactlyAssertedEL_first(argIsa, 'EvaluateSubLFn', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4430exactlyAssertedEL_first(argIsa, 'EscapeQuote', 1, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4431exactlyAssertedEL_first(argIsa, 'equalStrings-CaseInsensitive', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4432exactlyAssertedEL_first(argIsa, 'equalStrings-CaseInsensitive', 1, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4433exactlyAssertedEL_first(argIsa, 'DifferenceFn', 2, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4434exactlyAssertedEL_first(argIsa, 'DifferenceFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4435exactlyAssertedEL_first(argIsa, 'DateEncodeStringFn', 2, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4436exactlyAssertedEL_first(argIsa, 'DateEncodeStringFn', 1, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4437exactlyAssertedEL_first(argIsa, 'DateDecodeStringFn', 2, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4438exactlyAssertedEL_first(argIsa, 'DateDecodeStringFn', 1, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4439exactlyAssertedEL_first(argIsa, 'CycTacticFn', 2, 'CycTactic', 'UniversalVocabularyMt', vStrDef).
 4440exactlyAssertedEL_first(argIsa, 'CycTacticFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4441exactlyAssertedEL_first(argIsa, 'CycProofFn', 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4442exactlyAssertedEL_first(argIsa, 'CycProofFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4443exactlyAssertedEL_first(argIsa, 'CycProblemStoreFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4444exactlyAssertedEL_first(argIsa, 'CycProblemLinkFn', 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4445exactlyAssertedEL_first(argIsa, 'CycProblemLinkFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4446exactlyAssertedEL_first(argIsa, 'CycProblemFn', 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4447exactlyAssertedEL_first(argIsa, 'CycProblemFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4448exactlyAssertedEL_first(argIsa, 'CycInferenceFn', 2, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4449exactlyAssertedEL_first(argIsa, 'CycInferenceFn', 1, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4450exactlyAssertedEL_first(argIsa, 'CollectionRuleTemplateFn', 1, tCol, 'UniversalVocabularyMt', vStrDef).
 4451exactlyAssertedEL_first(argIsa, 'Average', 2, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4452exactlyAssertedEL_first(argIsa, 'Average', 2, 'UnaryFunction', 'BaseKB', vStrDef).
 4453exactlyAssertedEL_first(argIsa, 'Average', 1, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4454exactlyAssertedEL_first(argIsa, 'Average', 1, 'SetOrCollection', 'BaseKB', vStrDef).
 4455exactlyAssertedEL_first(argIsa, 'assertionUtility-1', 2, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 4456exactlyAssertedEL_first(argIsa, 'AbsoluteValueFn', 1, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4457exactlyAssertedEL_first(argAndRestQuotedIsa, or, 1, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrMon).
 4458exactlyAssertedEL_first(argAndRestQuotedIsa, and, 1, 'CycLSentence-Assertible', 'LogicalTruthMt', vStrMon).
 4459exactlyAssertedEL_first(argAndRestIsa, commutativeInArgsAndRest, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrMon).
 4460exactlyAssertedEL_first(argAndRestIsa, commutativeInArgs, 2, 'PositiveInteger', 'UniversalVocabularyMt', vStrMon).
 4461exactlyAssertedEL_first(arg6Format, different, 'SetTheFormat', 'BaseKB', vStrDef).
 4462exactlyAssertedEL_first(arg5Isa, interArgResultIsaReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4463exactlyAssertedEL_first(arg5Isa, interArgResultGenlReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4464exactlyAssertedEL_first(arg5Isa, interArgIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4465exactlyAssertedEL_first(arg5Genl, interArgIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4466exactlyAssertedEL_first(arg5Format, interArgResultIsaReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4467exactlyAssertedEL_first(arg5Format, interArgResultGenlReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4468exactlyAssertedEL_first(arg5Format, interArgIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrMon).
 4469exactlyAssertedEL_first(arg5Format, different, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4470exactlyAssertedEL_first(arg4Isa, relationExistsMinAll, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4471exactlyAssertedEL_first(arg4Isa, relationExistsMaxAll, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4472exactlyAssertedEL_first(arg4Isa, relationExistsCountAll, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4473exactlyAssertedEL_first(arg4Isa, relationAllExistsMin, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4474exactlyAssertedEL_first(arg4Isa, relationAllExistsMax, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4475exactlyAssertedEL_first(arg4Isa, relationAllExistsCount, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4476exactlyAssertedEL_first(arg4Isa, nthSmallestElement, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4477exactlyAssertedEL_first(arg4Isa, nthLargestElement, 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 4478exactlyAssertedEL_first(arg4Isa, interArgResultIsaReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4479exactlyAssertedEL_first(arg4Isa, interArgResultIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4480exactlyAssertedEL_first(arg4Isa, interArgResultGenlReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4481exactlyAssertedEL_first(arg4Isa, interArgResultGenl, tCol, 'UniversalVocabularyMt', vStrDef).
 4482exactlyAssertedEL_first(arg4Isa, interArgIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4483exactlyAssertedEL_first(arg4Isa, extConceptOverlapsColAndReln, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4484exactlyAssertedEL_first(arg4Isa, 'SkolemFuncNFn', 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4485exactlyAssertedEL_first(arg4Isa, 'RelationExistsAllFn', tCol, 'UniversalVocabularyMt', vStrDef).
 4486exactlyAssertedEL_first(arg4Isa, 'RelationAllExistsFn', tCol, 'UniversalVocabularyMt', vStrDef).
 4487exactlyAssertedEL_first(arg4Genl, interArgResultIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4488exactlyAssertedEL_first(arg4Genl, interArgResultGenl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4489exactlyAssertedEL_first(arg4Genl, 'RelationExistsAllFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4490exactlyAssertedEL_first(arg4Genl, 'RelationAllExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4491exactlyAssertedEL_first(arg4Format, relationExistsMinAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4492exactlyAssertedEL_first(arg4Format, relationExistsMaxAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4493exactlyAssertedEL_first(arg4Format, relationExistsCountAll, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4494exactlyAssertedEL_first(arg4Format, relationAllExistsMin, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4495exactlyAssertedEL_first(arg4Format, relationAllExistsMax, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4496exactlyAssertedEL_first(arg4Format, relationAllExistsCount, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4497exactlyAssertedEL_first(arg4Format, nthSmallestElement, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4498exactlyAssertedEL_first(arg4Format, interArgResultIsaReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4499exactlyAssertedEL_first(arg4Format, interArgResultIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4500exactlyAssertedEL_first(arg4Format, interArgResultGenlReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4501exactlyAssertedEL_first(arg4Format, interArgResultGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4502exactlyAssertedEL_first(arg4Format, interArgIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4503exactlyAssertedEL_first(arg4Format, extConceptOverlapsColAndReln, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 4504exactlyAssertedEL_first(arg4Format, different, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4505exactlyAssertedEL_first(arg3QuotedIsa, thereExistExactly, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4506exactlyAssertedEL_first(arg3QuotedIsa, thereExistAtMost, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4507exactlyAssertedEL_first(arg3QuotedIsa, thereExistAtLeast, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4508exactlyAssertedEL_first(arg3QuotedIsa, reformulationPrecondition, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 4509exactlyAssertedEL_first(arg3QuotedIsa, reformulationDirectionInMode, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 4510exactlyAssertedEL_first(arg3QuotedIsa, 'SkolemFunctionFn', 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 4511exactlyAssertedEL_first(arg3QuotedIsa, 'SkolemFuncNFn', 'SubLSymbol', 'UniversalVocabularyMt', vStrDef).
 4512exactlyAssertedEL_first(arg3Isa, unitMultiplicationFactor, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 4513exactlyAssertedEL_first(arg3Isa, unitMultiplicationFactor, 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4514exactlyAssertedEL_first(arg3Isa, transitiveViaArgInverse, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4515exactlyAssertedEL_first(arg3Isa, transitiveViaArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4516exactlyAssertedEL_first(arg3Isa, synonymousExternalConcept, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4517exactlyAssertedEL_first(arg3Isa, relationMemberInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4518exactlyAssertedEL_first(arg3Isa, relationInstanceMember, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4519exactlyAssertedEL_first(arg3Isa, relationInstanceExists, tCol, 'UniversalVocabularyMt', vStrDef).
 4520exactlyAssertedEL_first(arg3Isa, relationInstanceAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4521exactlyAssertedEL_first(arg3Isa, relationExistsMinAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4522exactlyAssertedEL_first(arg3Isa, relationExistsMaxAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4523exactlyAssertedEL_first(arg3Isa, relationExistsInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4524exactlyAssertedEL_first(arg3Isa, relationExistsCountAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4525exactlyAssertedEL_first(arg3Isa, relationExistsAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4526exactlyAssertedEL_first(arg3Isa, relationAllInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4527exactlyAssertedEL_first(arg3Isa, relationAllExistsMin, tCol, 'UniversalVocabularyMt', vStrDef).
 4528exactlyAssertedEL_first(arg3Isa, relationAllExistsMax, tCol, 'UniversalVocabularyMt', vStrDef).
 4529exactlyAssertedEL_first(arg3Isa, relationAllExistsCount, tCol, 'UniversalVocabularyMt', vStrDef).
 4530exactlyAssertedEL_first(arg3Isa, relationAllExists, tCol, 'UniversalVocabularyMt', vStrDef).
 4531exactlyAssertedEL_first(arg3Isa, ratioOfTo, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4532exactlyAssertedEL_first(arg3Isa, overlappingExternalConcept, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4533exactlyAssertedEL_first(arg3Isa, nthSmallestElement, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4534exactlyAssertedEL_first(arg3Isa, nthLargestElement, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4535exactlyAssertedEL_first(arg3Isa, nonAbducibleWithValueInArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4536exactlyAssertedEL_first(arg3Isa, nearestDifferentIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4537exactlyAssertedEL_first(arg3Isa, nearestDifferentGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 4538exactlyAssertedEL_first(arg3Isa, nearestCommonSpecs, tCol, 'UniversalVocabularyMt', vStrDef).
 4539exactlyAssertedEL_first(arg3Isa, nearestCommonIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4540exactlyAssertedEL_first(arg3Isa, nearestCommonGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 4541exactlyAssertedEL_first(arg3Isa, nearestCommonGenlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4542exactlyAssertedEL_first(arg3Isa, natArgument, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4543exactlyAssertedEL_first(arg3Isa, multiplicationUnits, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4544exactlyAssertedEL_first(arg3Isa, interArgResultIsaReln, tPred, 'UniversalVocabularyMt', vStrDef).
 4545exactlyAssertedEL_first(arg3Isa, interArgResultIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4546exactlyAssertedEL_first(arg3Isa, interArgResultGenlReln, tPred, 'UniversalVocabularyMt', vStrDef).
 4547exactlyAssertedEL_first(arg3Isa, interArgResultGenl, tCol, 'UniversalVocabularyMt', vStrDef).
 4548exactlyAssertedEL_first(arg3Isa, interArgIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4549exactlyAssertedEL_first(arg3Isa, interArgDifferent, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4550exactlyAssertedEL_first(arg3Isa, integerBetween, 'Integer', 'UniversalVocabularyMt', vStrDef).
 4551exactlyAssertedEL_first(arg3Isa, genFormat, 'List', 'UniversalVocabularyMt', vStrDef).
 4552exactlyAssertedEL_first(arg3Isa, extConceptOverlapsColAndReln, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4553exactlyAssertedEL_first(arg3Isa, distributesOutOfArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4554exactlyAssertedEL_first(arg3Isa, defaultReformulationDirectionInModeForPred, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', vStrDef).
 4555exactlyAssertedEL_first(arg3Isa, cycTacticID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4556exactlyAssertedEL_first(arg3Isa, cycProofID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4557exactlyAssertedEL_first(arg3Isa, cycProblemLinkID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4558exactlyAssertedEL_first(arg3Isa, cycProblemID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4559exactlyAssertedEL_first(arg3Isa, completeExtentEnumerableForValueInArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4560exactlyAssertedEL_first(arg3Isa, completeExtentDecidableForValueInArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4561exactlyAssertedEL_first(arg3Isa, completeExtentDecidableForValueInArg, 'NonNegativeInteger', 'CoreCycLMt', vStrDef).
 4562exactlyAssertedEL_first(arg3Isa, completeExtentAssertedForValueInArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4563exactlyAssertedEL_first(arg3Isa, completeExtentAssertedForValueInArg, 'NonNegativeInteger', 'CoreCycLMt', vStrDef).
 4564exactlyAssertedEL_first(arg3Isa, commutativeInArgs, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4565exactlyAssertedEL_first(arg3Isa, canonicalizerDirectiveForArgAndRest, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4566exactlyAssertedEL_first(arg3Isa, canonicalizerDirectiveForArgAndRest, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 4567exactlyAssertedEL_first(arg3Isa, canonicalizerDirectiveForArg, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4568exactlyAssertedEL_first(arg3Isa, canonicalizerDirectiveForArg, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 4569exactlyAssertedEL_first(arg3Isa, assertedPredicateArg, tPred, 'UniversalVocabularyMt', vStrDef).
 4570exactlyAssertedEL_first(arg3Isa, argSometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4571exactlyAssertedEL_first(arg3Isa, argQuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4572exactlyAssertedEL_first(arg3Isa, argIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4573exactlyAssertedEL_first(arg3Isa, argAndRestQuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4574exactlyAssertedEL_first(arg3Isa, argAndRestIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4575exactlyAssertedEL_first(arg3Isa, argAndRestGenl, tCol, 'UniversalVocabularyMt', vStrDef).
 4576exactlyAssertedEL_first(arg3Isa, admittedArgument, tRelation, 'UniversalVocabularyMt', vStrDef).
 4577exactlyAssertedEL_first(arg3Isa, admittedAllArgument, tRelation, 'UniversalVocabularyMt', vStrDef).
 4578exactlyAssertedEL_first(arg3Isa, 'RelationInstanceExistsFn', tCol, 'UniversalVocabularyMt', vStrDef).
 4579exactlyAssertedEL_first(arg3Isa, 'RelationExistsInstanceFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4580exactlyAssertedEL_first(arg3Isa, 'RelationExistsAllFn', tCol, 'UniversalVocabularyMt', vStrDef).
 4581exactlyAssertedEL_first(arg3Isa, 'RelationAllExistsFn', tCol, 'UniversalVocabularyMt', vStrDef).
 4582exactlyAssertedEL_first(arg3Isa, 'interArgIsa5-4', tCol, 'UniversalVocabularyMt', vStrDef).
 4583exactlyAssertedEL_first(arg3Isa, 'interArgIsa5-3', tCol, 'UniversalVocabularyMt', vStrDef).
 4584exactlyAssertedEL_first(arg3Isa, 'interArgIsa5-2', tCol, 'UniversalVocabularyMt', vStrDef).
 4585exactlyAssertedEL_first(arg3Isa, 'interArgIsa5-1', tCol, 'UniversalVocabularyMt', vStrDef).
 4586exactlyAssertedEL_first(arg3Isa, 'interArgIsa4-5', tCol, 'UniversalVocabularyMt', vStrDef).
 4587exactlyAssertedEL_first(arg3Isa, 'interArgIsa4-3', tCol, 'UniversalVocabularyMt', vStrDef).
 4588exactlyAssertedEL_first(arg3Isa, 'interArgIsa4-2', tCol, 'UniversalVocabularyMt', vStrDef).
 4589exactlyAssertedEL_first(arg3Isa, 'interArgIsa4-1', tCol, 'UniversalVocabularyMt', vStrDef).
 4590exactlyAssertedEL_first(arg3Isa, 'interArgIsa3-5', tCol, 'UniversalVocabularyMt', vStrDef).
 4591exactlyAssertedEL_first(arg3Isa, 'interArgIsa3-4', tCol, 'UniversalVocabularyMt', vStrDef).
 4592exactlyAssertedEL_first(arg3Isa, 'interArgIsa3-2', tCol, 'UniversalVocabularyMt', vStrDef).
 4593exactlyAssertedEL_first(arg3Isa, 'interArgIsa3-1', tCol, 'UniversalVocabularyMt', vStrDef).
 4594exactlyAssertedEL_first(arg3Isa, 'interArgIsa2-5', tCol, 'UniversalVocabularyMt', vStrDef).
 4595exactlyAssertedEL_first(arg3Isa, 'interArgIsa2-4', tCol, 'UniversalVocabularyMt', vStrDef).
 4596exactlyAssertedEL_first(arg3Isa, 'interArgIsa2-3', tCol, 'UniversalVocabularyMt', vStrDef).
 4597exactlyAssertedEL_first(arg3Isa, 'interArgIsa2-1', tCol, 'UniversalVocabularyMt', vStrDef).
 4598exactlyAssertedEL_first(arg3Isa, 'interArgIsa1-5', tCol, 'UniversalVocabularyMt', vStrDef).
 4599exactlyAssertedEL_first(arg3Isa, 'interArgIsa1-4', tCol, 'UniversalVocabularyMt', vStrDef).
 4600exactlyAssertedEL_first(arg3Isa, 'interArgIsa1-3', tCol, 'UniversalVocabularyMt', vStrDef).
 4601exactlyAssertedEL_first(arg3Isa, 'interArgIsa1-2', tCol, 'UniversalVocabularyMt', vStrDef).
 4602exactlyAssertedEL_first(arg3Isa, 'interArgGenl1-2', tCol, 'UniversalVocabularyMt', vStrDef).
 4603exactlyAssertedEL_first(arg3Isa, 'interArgFormat1-2', 'Individual', 'UniversalVocabularyMt', vStrDef).
 4604exactlyAssertedEL_first(arg3Genl, relationInstanceExists, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4605exactlyAssertedEL_first(arg3Genl, relationInstanceAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4606exactlyAssertedEL_first(arg3Genl, relationExistsMinAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4607exactlyAssertedEL_first(arg3Genl, relationExistsMaxAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4608exactlyAssertedEL_first(arg3Genl, relationExistsCountAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4609exactlyAssertedEL_first(arg3Genl, relationExistsAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4610exactlyAssertedEL_first(arg3Genl, relationAllExistsMin, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4611exactlyAssertedEL_first(arg3Genl, relationAllExistsMax, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4612exactlyAssertedEL_first(arg3Genl, relationAllExistsCount, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4613exactlyAssertedEL_first(arg3Genl, relationAllExists, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4614exactlyAssertedEL_first(arg3Genl, nearestDifferentIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4615exactlyAssertedEL_first(arg3Genl, nearestDifferentGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4616exactlyAssertedEL_first(arg3Genl, nearestCommonSpecs, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4617exactlyAssertedEL_first(arg3Genl, nearestCommonIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4618exactlyAssertedEL_first(arg3Genl, nearestCommonGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4619exactlyAssertedEL_first(arg3Genl, interArgResultIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4620exactlyAssertedEL_first(arg3Genl, interArgResultGenl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4621exactlyAssertedEL_first(arg3Genl, interArgIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4622exactlyAssertedEL_first(arg3Genl, argSometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4623exactlyAssertedEL_first(arg3Genl, argQuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 4624exactlyAssertedEL_first(arg3Genl, argIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4625exactlyAssertedEL_first(arg3Genl, argAndRestQuotedIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4626exactlyAssertedEL_first(arg3Genl, argAndRestQuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 4627exactlyAssertedEL_first(arg3Genl, argAndRestIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4628exactlyAssertedEL_first(arg3Genl, argAndRestGenl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4629exactlyAssertedEL_first(arg3Genl, 'RelationInstanceExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4630exactlyAssertedEL_first(arg3Genl, 'RelationExistsAllFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4631exactlyAssertedEL_first(arg3Genl, 'RelationAllExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4632exactlyAssertedEL_first(arg3Genl, 'interArgIsa5-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4633exactlyAssertedEL_first(arg3Genl, 'interArgIsa5-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4634exactlyAssertedEL_first(arg3Genl, 'interArgIsa5-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4635exactlyAssertedEL_first(arg3Genl, 'interArgIsa5-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4636exactlyAssertedEL_first(arg3Genl, 'interArgIsa4-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4637exactlyAssertedEL_first(arg3Genl, 'interArgIsa4-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4638exactlyAssertedEL_first(arg3Genl, 'interArgIsa4-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4639exactlyAssertedEL_first(arg3Genl, 'interArgIsa4-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4640exactlyAssertedEL_first(arg3Genl, 'interArgIsa3-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4641exactlyAssertedEL_first(arg3Genl, 'interArgIsa3-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4642exactlyAssertedEL_first(arg3Genl, 'interArgIsa3-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4643exactlyAssertedEL_first(arg3Genl, 'interArgIsa3-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4644exactlyAssertedEL_first(arg3Genl, 'interArgIsa2-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4645exactlyAssertedEL_first(arg3Genl, 'interArgIsa2-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4646exactlyAssertedEL_first(arg3Genl, 'interArgIsa2-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4647exactlyAssertedEL_first(arg3Genl, 'interArgIsa2-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4648exactlyAssertedEL_first(arg3Genl, 'interArgIsa1-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4649exactlyAssertedEL_first(arg3Genl, 'interArgIsa1-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4650exactlyAssertedEL_first(arg3Genl, 'interArgIsa1-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4651exactlyAssertedEL_first(arg3Genl, 'interArgIsa1-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 4652exactlyAssertedEL_first(arg3Format, unitMultiplicationFactor, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4653exactlyAssertedEL_first(arg3Format, transitiveViaArgInverse, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4654exactlyAssertedEL_first(arg3Format, transitiveViaArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4655exactlyAssertedEL_first(arg3Format, synonymousExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4656exactlyAssertedEL_first(arg3Format, relationInstanceExists, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4657exactlyAssertedEL_first(arg3Format, relationInstanceAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4658exactlyAssertedEL_first(arg3Format, relationExistsMinAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4659exactlyAssertedEL_first(arg3Format, relationExistsMaxAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4660exactlyAssertedEL_first(arg3Format, relationExistsInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4661exactlyAssertedEL_first(arg3Format, relationExistsCountAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4662exactlyAssertedEL_first(arg3Format, relationExistsAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4663exactlyAssertedEL_first(arg3Format, relationAllInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4664exactlyAssertedEL_first(arg3Format, relationAllExistsMin, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4665exactlyAssertedEL_first(arg3Format, relationAllExistsMax, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4666exactlyAssertedEL_first(arg3Format, relationAllExistsCount, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4667exactlyAssertedEL_first(arg3Format, relationAllExists, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4668exactlyAssertedEL_first(arg3Format, overlappingExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4669exactlyAssertedEL_first(arg3Format, nthSmallestElement, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4670exactlyAssertedEL_first(arg3Format, natArgument, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4671exactlyAssertedEL_first(arg3Format, multiplicationUnits, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4672exactlyAssertedEL_first(arg3Format, interArgResultIsaReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4673exactlyAssertedEL_first(arg3Format, interArgResultIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4674exactlyAssertedEL_first(arg3Format, interArgResultGenlReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4675exactlyAssertedEL_first(arg3Format, interArgResultGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4676exactlyAssertedEL_first(arg3Format, interArgIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4677exactlyAssertedEL_first(arg3Format, interArgDifferent, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4678exactlyAssertedEL_first(arg3Format, integerBetween, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4679exactlyAssertedEL_first(arg3Format, different, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4680exactlyAssertedEL_first(arg3Format, cycTacticID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4681exactlyAssertedEL_first(arg3Format, cycProofID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4682exactlyAssertedEL_first(arg3Format, cycProblemLinkID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4683exactlyAssertedEL_first(arg3Format, cycProblemID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4684exactlyAssertedEL_first(arg3Format, argSometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4685exactlyAssertedEL_first(arg3Format, argIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4686exactlyAssertedEL_first(arg3Format, argAndRestIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4687exactlyAssertedEL_first(arg3Format, argAndRestGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4688exactlyAssertedEL_first(arg3Format, admittedArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 4689exactlyAssertedEL_first(arg3Format, admittedAllArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 4690exactlyAssertedEL_first(arg3Format, 'interArgIsa5-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4691exactlyAssertedEL_first(arg3Format, 'interArgIsa5-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4692exactlyAssertedEL_first(arg3Format, 'interArgIsa5-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4693exactlyAssertedEL_first(arg3Format, 'interArgIsa5-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4694exactlyAssertedEL_first(arg3Format, 'interArgIsa4-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4695exactlyAssertedEL_first(arg3Format, 'interArgIsa4-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4696exactlyAssertedEL_first(arg3Format, 'interArgIsa4-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4697exactlyAssertedEL_first(arg3Format, 'interArgIsa4-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4698exactlyAssertedEL_first(arg3Format, 'interArgIsa3-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4699exactlyAssertedEL_first(arg3Format, 'interArgIsa3-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4700exactlyAssertedEL_first(arg3Format, 'interArgIsa3-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4701exactlyAssertedEL_first(arg3Format, 'interArgIsa3-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4702exactlyAssertedEL_first(arg3Format, 'interArgIsa2-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4703exactlyAssertedEL_first(arg3Format, 'interArgIsa2-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4704exactlyAssertedEL_first(arg3Format, 'interArgIsa2-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4705exactlyAssertedEL_first(arg3Format, 'interArgIsa2-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4706exactlyAssertedEL_first(arg3Format, 'interArgIsa1-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4707exactlyAssertedEL_first(arg3Format, 'interArgIsa1-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4708exactlyAssertedEL_first(arg3Format, 'interArgIsa1-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4709exactlyAssertedEL_first(arg3Format, 'interArgIsa1-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 4710exactlyAssertedEL_first(arg2QuotedIsa, xor, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4711exactlyAssertedEL_first(arg2QuotedIsa, xor, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 4712exactlyAssertedEL_first(arg2QuotedIsa, trueRule, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4713exactlyAssertedEL_first(arg2QuotedIsa, thereExists, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4714exactlyAssertedEL_first(arg2QuotedIsa, thereExistExactly, ftVar, 'UniversalVocabularyMt', vStrDef).
 4715exactlyAssertedEL_first(arg2QuotedIsa, thereExistAtMost, ftVar, 'UniversalVocabularyMt', vStrDef).
 4716exactlyAssertedEL_first(arg2QuotedIsa, thereExistAtLeast, ftVar, 'UniversalVocabularyMt', vStrDef).
 4717exactlyAssertedEL_first(arg2QuotedIsa, termOfUnit, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4718exactlyAssertedEL_first(arg2QuotedIsa, termOfUnit, 'CycLReifiableNonAtomicTerm', 'LogicalTruthImplementationMt', vStrDef).
 4719exactlyAssertedEL_first(arg2QuotedIsa, termDependsOn, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4720exactlyAssertedEL_first(arg2QuotedIsa, sharedNotes, 'DocumentationConstant', 'UniversalVocabularyMt', vStrDef).
 4721exactlyAssertedEL_first(arg2QuotedIsa, sentenceImplies, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4722exactlyAssertedEL_first(arg2QuotedIsa, sentenceEquiv, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4723exactlyAssertedEL_first(arg2QuotedIsa, salientAssertions, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4724exactlyAssertedEL_first(arg2QuotedIsa, ruleAfterRemoving, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4725exactlyAssertedEL_first(arg2QuotedIsa, ruleAfterAdding, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4726exactlyAssertedEL_first(arg2QuotedIsa, rewriteOf, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4727exactlyAssertedEL_first(arg2QuotedIsa, relationExpansion, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4728exactlyAssertedEL_first(arg2QuotedIsa, reformulatorRuleProperties, 'CycLAtomicAssertion', 'UniversalVocabularyMt', vStrDef).
 4729exactlyAssertedEL_first(arg2QuotedIsa, reformulatorRule, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 4730exactlyAssertedEL_first(arg2QuotedIsa, reformulatorEquiv, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 4731exactlyAssertedEL_first(arg2QuotedIsa, reformulatorEquals, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4732exactlyAssertedEL_first(arg2QuotedIsa, quotedDefnSufficient, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4733exactlyAssertedEL_first(arg2QuotedIsa, quotedDefnNecessary, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4734exactlyAssertedEL_first(arg2QuotedIsa, quotedDefnIff, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4735exactlyAssertedEL_first(arg2QuotedIsa, prettyString, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4736exactlyAssertedEL_first(arg2QuotedIsa, pragmaticRequirement, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 4737exactlyAssertedEL_first(arg2QuotedIsa, pragmaticallyNormal, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4738exactlyAssertedEL_first(arg2QuotedIsa, operatorFormulas, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 4739exactlyAssertedEL_first(arg2QuotedIsa, oldConstantName, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4740exactlyAssertedEL_first(arg2QuotedIsa, oldConstantName, 'SubLString', 'BookkeepingMt', vStrDef).
 4741exactlyAssertedEL_first(arg2QuotedIsa, natArgumentsEqual, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4742exactlyAssertedEL_first(arg2QuotedIsa, meetsPragmaticRequirement, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4743exactlyAssertedEL_first(arg2QuotedIsa, ist, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4744exactlyAssertedEL_first(arg2QuotedIsa, irrelevantPredAssertion, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4745exactlyAssertedEL_first(arg2QuotedIsa, implies, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4746exactlyAssertedEL_first(arg2QuotedIsa, implies, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 4747exactlyAssertedEL_first(arg2QuotedIsa, holdsIn, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4748exactlyAssertedEL_first(arg2QuotedIsa, highlyRelevantPredAssertion, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4749exactlyAssertedEL_first(arg2QuotedIsa, genlRules, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 4750exactlyAssertedEL_first(arg2QuotedIsa, genKeyword, 'SubLKeyword', 'UniversalVocabularyMt', vStrDef).
 4751exactlyAssertedEL_first(arg2QuotedIsa, genFormat, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4752exactlyAssertedEL_first(arg2QuotedIsa, forAll, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4753exactlyAssertedEL_first(arg2QuotedIsa, expansionDefn, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4754exactlyAssertedEL_first(arg2QuotedIsa, expansion, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 4755exactlyAssertedEL_first(arg2QuotedIsa, expansion, 'CycLExpression', 'UniversalVocabularyImplementationMt', vStrDef).
 4756exactlyAssertedEL_first(arg2QuotedIsa, exceptWhen, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4757exactlyAssertedEL_first(arg2QuotedIsa, exceptFor, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4758exactlyAssertedEL_first(arg2QuotedIsa, exampleAssertions, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4759exactlyAssertedEL_first(arg2QuotedIsa, evaluationDefn, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4760exactlyAssertedEL_first(arg2QuotedIsa, equiv, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4761exactlyAssertedEL_first(arg2QuotedIsa, equiv, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 4762exactlyAssertedEL_first(arg2QuotedIsa, defnSufficient, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4763exactlyAssertedEL_first(arg2QuotedIsa, defnNecessary, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4764exactlyAssertedEL_first(arg2QuotedIsa, defnIff, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4765exactlyAssertedEL_first(arg2QuotedIsa, cycTransformationProofRule, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 4766exactlyAssertedEL_first(arg2QuotedIsa, cycProblemStoreTerms, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4767exactlyAssertedEL_first(arg2QuotedIsa, cycProblemQueryTerms, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 4768exactlyAssertedEL_first(arg2QuotedIsa, cycProblemQuerySentence, 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 4769exactlyAssertedEL_first(arg2QuotedIsa, constantName, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4770exactlyAssertedEL_first(arg2QuotedIsa, comment, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4771exactlyAssertedEL_first(arg2QuotedIsa, collectionExpansion, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 4772exactlyAssertedEL_first(arg2QuotedIsa, collectionExpansion, 'CycLExpression', 'UniversalVocabularyImplementationMt', vStrDef).
 4773exactlyAssertedEL_first(arg2QuotedIsa, assertedTermSentences, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4774exactlyAssertedEL_first(arg2QuotedIsa, arity, 'SubLNonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4775exactlyAssertedEL_first(arg2QuotedIsa, argSometimesIsa, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4776exactlyAssertedEL_first(arg2QuotedIsa, argIsa, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4777exactlyAssertedEL_first(arg2QuotedIsa, argAndRestIsa, 'SubLPositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4778exactlyAssertedEL_first(arg2QuotedIsa, afterRemoving, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4779exactlyAssertedEL_first(arg2QuotedIsa, afterAdding, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 4780exactlyAssertedEL_first(arg2QuotedIsa, abnormal, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 4781exactlyAssertedEL_first(arg2QuotedIsa, 'TLVariableFn', 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4782exactlyAssertedEL_first(arg2QuotedIsa, 'TLAssertionFn', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4783exactlyAssertedEL_first(arg2QuotedIsa, 'TheSetOf', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4784exactlyAssertedEL_first(arg2QuotedIsa, 'TheCollectionOf', 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 4785exactlyAssertedEL_first(arg2QuotedIsa, 'SkolemFunctionFn', ftVar, 'UniversalVocabularyMt', vStrDef).
 4786exactlyAssertedEL_first(arg2QuotedIsa, 'SkolemFuncNFn', ftVar, 'UniversalVocabularyMt', vStrDef).
 4787exactlyAssertedEL_first(arg2QuotedIsa, 'prettyString-Canonical', 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4788exactlyAssertedEL_first(arg2QuotedIsa, 'Kappa', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4789exactlyAssertedEL_first(arg2QuotedIsa, 'ist-Asserted', 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 4790exactlyAssertedEL_first(arg2QuotedIsa, 'FormulaArgFn', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 4791exactlyAssertedEL_first(arg2QuotedIsa, 'ExpandSubLFn', 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 4792exactlyAssertedEL_first(arg2Isa, unitMultiplicationFactor, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4793exactlyAssertedEL_first(arg2Isa, transitiveViaArgInverse, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4794exactlyAssertedEL_first(arg2Isa, transitiveViaArg, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4795exactlyAssertedEL_first(arg2Isa, termOfUnit, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4796exactlyAssertedEL_first(arg2Isa, termExternalIDString, 'HLExternalIDString', 'UniversalVocabularyMt', vStrDef).
 4797exactlyAssertedEL_first(arg2Isa, termDependsOn, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4798exactlyAssertedEL_first(arg2Isa, synonymousExternalConcept, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4799exactlyAssertedEL_first(arg2Isa, substring, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4800exactlyAssertedEL_first(arg2Isa, subsetOf, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4801exactlyAssertedEL_first(arg2Isa, singleEntryFormatInArgs, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4802exactlyAssertedEL_first(arg2Isa, siblingDisjointExceptions, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4803exactlyAssertedEL_first(arg2Isa, siblingDisjointExceptions, 'SetOrCollection', 'BaseKB', vStrDef).
 4804exactlyAssertedEL_first(arg2Isa, sharedNotes, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4805exactlyAssertedEL_first(arg2Isa, sentenceTruth, 'TruthValue', 'UniversalVocabularyMt', vStrDef).
 4806exactlyAssertedEL_first(arg2Isa, sentenceEquiv, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4807exactlyAssertedEL_first(arg2Isa, sentenceEquiv, 'Thing', 'BaseKB', vStrDef).
 4808exactlyAssertedEL_first(arg2Isa, sentenceEquiv, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4809exactlyAssertedEL_first(arg2Isa, sentenceEquiv, 'Individual', 'BaseKB', vStrDef).
 4810exactlyAssertedEL_first(arg2Isa, sentenceDesignationArgnum, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4811exactlyAssertedEL_first(arg2Isa, scopingArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4812exactlyAssertedEL_first(arg2Isa, ruleTemplateDirection, 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 4813exactlyAssertedEL_first(arg2Isa, ruleAfterRemoving, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4814exactlyAssertedEL_first(arg2Isa, ruleAfterAdding, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4815exactlyAssertedEL_first(arg2Isa, rewriteOf, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4816exactlyAssertedEL_first(arg2Isa, resultQuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4817exactlyAssertedEL_first(arg2Isa, resultIsaArgIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4818exactlyAssertedEL_first(arg2Isa, resultIsaArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4819exactlyAssertedEL_first(arg2Isa, resultIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4820exactlyAssertedEL_first(arg2Isa, resultIsa, tCol, 'BaseKB', vStrDef).
 4821exactlyAssertedEL_first(arg2Isa, resultGenlArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4822exactlyAssertedEL_first(arg2Isa, resultGenl, tCol, 'UniversalVocabularyMt', vStrDef).
 4823exactlyAssertedEL_first(arg2Isa, resultGenl, tCol, 'BaseKB', vStrDef).
 4824exactlyAssertedEL_first(arg2Isa, requiredArg3Pred, tPred, 'UniversalVocabularyMt', vStrDef).
 4825exactlyAssertedEL_first(arg2Isa, requiredArg2Pred, tPred, 'UniversalVocabularyMt', vStrDef).
 4826exactlyAssertedEL_first(arg2Isa, requiredArg1Pred, tPred, 'UniversalVocabularyMt', vStrDef).
 4827exactlyAssertedEL_first(arg2Isa, relationMemberInstance, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4828exactlyAssertedEL_first(arg2Isa, relationInstanceMember, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4829exactlyAssertedEL_first(arg2Isa, relationInstanceExists, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4830exactlyAssertedEL_first(arg2Isa, relationInstanceAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4831exactlyAssertedEL_first(arg2Isa, relationExistsMinAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4832exactlyAssertedEL_first(arg2Isa, relationExistsMaxAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4833exactlyAssertedEL_first(arg2Isa, relationExistsInstance, tCol, 'UniversalVocabularyMt', vStrDef).
 4834exactlyAssertedEL_first(arg2Isa, relationExistsCountAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4835exactlyAssertedEL_first(arg2Isa, relationExistsAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4836exactlyAssertedEL_first(arg2Isa, relationAllInstance, tCol, 'UniversalVocabularyMt', vStrDef).
 4837exactlyAssertedEL_first(arg2Isa, relationAllExistsMin, tCol, 'UniversalVocabularyMt', vStrDef).
 4838exactlyAssertedEL_first(arg2Isa, relationAllExistsMax, tCol, 'UniversalVocabularyMt', vStrDef).
 4839exactlyAssertedEL_first(arg2Isa, relationAllExistsCount, tCol, 'UniversalVocabularyMt', vStrDef).
 4840exactlyAssertedEL_first(arg2Isa, relationAllExists, tCol, 'UniversalVocabularyMt', vStrDef).
 4841exactlyAssertedEL_first(arg2Isa, relationAll, tCol, 'UniversalVocabularyMt', vStrDef).
 4842exactlyAssertedEL_first(arg2Isa, reformulatorRule, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4843exactlyAssertedEL_first(arg2Isa, reformulatorEquals, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4844exactlyAssertedEL_first(arg2Isa, reformulationPrecondition, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4845exactlyAssertedEL_first(arg2Isa, reformulationPrecondition, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 4846exactlyAssertedEL_first(arg2Isa, reformulationDirectionInMode, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4847exactlyAssertedEL_first(arg2Isa, ratioOfTo, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4848exactlyAssertedEL_first(arg2Isa, quotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4849exactlyAssertedEL_first(arg2Isa, quotedDefnSufficient, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4850exactlyAssertedEL_first(arg2Isa, quotedDefnNecessary, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4851exactlyAssertedEL_first(arg2Isa, quotedDefnIff, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4852exactlyAssertedEL_first(arg2Isa, quotedArgument, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4853exactlyAssertedEL_first(arg2Isa, quantitySubsumes, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4854exactlyAssertedEL_first(arg2Isa, quantityIntersects, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4855exactlyAssertedEL_first(arg2Isa, prettyString, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4856exactlyAssertedEL_first(arg2Isa, preservesGenlsInArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4857exactlyAssertedEL_first(arg2Isa, predicateConventionMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4858exactlyAssertedEL_first(arg2Isa, pointQuantValue, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 4859exactlyAssertedEL_first(arg2Isa, overlappingExternalConcept, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4860exactlyAssertedEL_first(arg2Isa, operatorFormulas, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4861exactlyAssertedEL_first(arg2Isa, openEntryFormatInArgs, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4862exactlyAssertedEL_first(arg2Isa, opaqueArgument, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4863exactlyAssertedEL_first(arg2Isa, omitArgIsa, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4864exactlyAssertedEL_first(arg2Isa, oldConstantName, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4865exactlyAssertedEL_first(arg2Isa, oldConstantName, 'CharacterString', 'BookkeepingMt', vStrDef).
 4866exactlyAssertedEL_first(arg2Isa, numericallyEquals, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4867exactlyAssertedEL_first(arg2Isa, numericallyEquals, 'ScalarInterval', 'BaseKB', vStrDef).
 4868exactlyAssertedEL_first(arg2Isa, nthSmallestElement, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4869exactlyAssertedEL_first(arg2Isa, nthLargestElement, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4870exactlyAssertedEL_first(arg2Isa, nonAbducibleWithValueInArg, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4871exactlyAssertedEL_first(arg2Isa, negationPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 4872exactlyAssertedEL_first(arg2Isa, negationMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4873exactlyAssertedEL_first(arg2Isa, negationInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4874exactlyAssertedEL_first(arg2Isa, nearestIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 4875exactlyAssertedEL_first(arg2Isa, nearestGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 4876exactlyAssertedEL_first(arg2Isa, nearestGenlPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 4877exactlyAssertedEL_first(arg2Isa, nearestGenlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4878exactlyAssertedEL_first(arg2Isa, nearestDifferentIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4879exactlyAssertedEL_first(arg2Isa, nearestDifferentGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 4880exactlyAssertedEL_first(arg2Isa, nearestCommonSpecs, tCol, 'UniversalVocabularyMt', vStrDef).
 4881exactlyAssertedEL_first(arg2Isa, nearestCommonIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4882exactlyAssertedEL_first(arg2Isa, nearestCommonGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 4883exactlyAssertedEL_first(arg2Isa, nearestCommonGenlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4884exactlyAssertedEL_first(arg2Isa, natFunction, 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 4885exactlyAssertedEL_first(arg2Isa, natArgumentsEqual, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4886exactlyAssertedEL_first(arg2Isa, natArgument, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4887exactlyAssertedEL_first(arg2Isa, myCreator, 'Cyclist', 'UniversalVocabularyMt', vStrDef).
 4888exactlyAssertedEL_first(arg2Isa, myCreator, 'Cyclist', 'BookkeepingMt', vStrDef).
 4889exactlyAssertedEL_first(arg2Isa, myCreationTime, 'Integer', 'UniversalVocabularyMt', vStrDef).
 4890exactlyAssertedEL_first(arg2Isa, myCreationSecond, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4891exactlyAssertedEL_first(arg2Isa, myCreationPurpose, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4892exactlyAssertedEL_first(arg2Isa, multiplicationUnits, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 4893exactlyAssertedEL_first(arg2Isa, minQuantValue, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 4894exactlyAssertedEL_first(arg2Isa, microtheoryDesignationArgnum, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4895exactlyAssertedEL_first(arg2Isa, means, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4896exactlyAssertedEL_first(arg2Isa, maxQuantValue, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 4897exactlyAssertedEL_first(arg2Isa, isa, tCol, 'UniversalVocabularyMt', vStrDef).
 4898exactlyAssertedEL_first(arg2Isa, isa, tCol, 'BaseKB', vStrDef).
 4899exactlyAssertedEL_first(arg2Isa, interArgResultIsaReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4900exactlyAssertedEL_first(arg2Isa, interArgResultIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4901exactlyAssertedEL_first(arg2Isa, interArgResultGenlReln, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4902exactlyAssertedEL_first(arg2Isa, interArgResultGenl, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4903exactlyAssertedEL_first(arg2Isa, interArgIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4904exactlyAssertedEL_first(arg2Isa, interArgDifferent, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4905exactlyAssertedEL_first(arg2Isa, integerBetween, 'Integer', 'UniversalVocabularyMt', vStrDef).
 4906exactlyAssertedEL_first(arg2Isa, instanceElementType, tCol, 'UniversalVocabularyMt', vStrDef).
 4907exactlyAssertedEL_first(arg2Isa, indexicalReferent, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4908exactlyAssertedEL_first(arg2Isa, independentArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4909exactlyAssertedEL_first(arg2Isa, hlPrototypicalInstance, tCol, 'UniversalVocabularyMt', vStrDef).
 4910exactlyAssertedEL_first(arg2Isa, greaterThanOrEqualTo, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4911exactlyAssertedEL_first(arg2Isa, greaterThanOrEqualTo, 'ScalarInterval', 'BaseKB', vStrDef).
 4912exactlyAssertedEL_first(arg2Isa, greaterThan, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4913exactlyAssertedEL_first(arg2Isa, greaterThan, 'ScalarInterval', 'BaseKB', vStrDef).
 4914exactlyAssertedEL_first(arg2Isa, genls, tCol, 'UniversalVocabularyMt', vStrDef).
 4915exactlyAssertedEL_first(arg2Isa, genls, tCol, 'BaseKB', vStrDef).
 4916exactlyAssertedEL_first(arg2Isa, genlPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 4917exactlyAssertedEL_first(arg2Isa, genlPreds, tPred, 'BaseKB', vStrDef).
 4918exactlyAssertedEL_first(arg2Isa, genlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4919exactlyAssertedEL_first(arg2Isa, genlMt, 'Microtheory', 'BaseKB', vStrDef).
 4920exactlyAssertedEL_first(arg2Isa, genlInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4921exactlyAssertedEL_first(arg2Isa, genlCanonicalizerDirectives, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4922exactlyAssertedEL_first(arg2Isa, genlCanonicalizerDirectives, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 4923exactlyAssertedEL_first(arg2Isa, genFormat, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4924exactlyAssertedEL_first(arg2Isa, formulaArity, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4925exactlyAssertedEL_first(arg2Isa, followingValue, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 4926exactlyAssertedEL_first(arg2Isa, fanOutArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4927exactlyAssertedEL_first(arg2Isa, extentCardinality, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4928exactlyAssertedEL_first(arg2Isa, extConceptOverlapsColAndReln, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4929exactlyAssertedEL_first(arg2Isa, expresses, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4930exactlyAssertedEL_first(arg2Isa, expansionDefn, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4931exactlyAssertedEL_first(arg2Isa, expansion, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4932exactlyAssertedEL_first(arg2Isa, expansion, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 4933exactlyAssertedEL_first(arg2Isa, evaluationResultQuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 4934exactlyAssertedEL_first(arg2Isa, evaluationDefn, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4935exactlyAssertedEL_first(arg2Isa, evaluate, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4936exactlyAssertedEL_first(arg2Isa, equalSymbols, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4937exactlyAssertedEL_first(arg2Isa, equals, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4938exactlyAssertedEL_first(arg2Isa, elInverse, 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 4939exactlyAssertedEL_first(arg2Isa, elInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 4940exactlyAssertedEL_first(arg2Isa, elementOf, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 4941exactlyAssertedEL_first(arg2Isa, distributesOutOfArg, tPred, 'UniversalVocabularyMt', vStrDef).
 4942exactlyAssertedEL_first(arg2Isa, disjointWith, tCol, 'UniversalVocabularyMt', vStrDef).
 4943exactlyAssertedEL_first(arg2Isa, denotes, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4944exactlyAssertedEL_first(arg2Isa, defnSufficient, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4945exactlyAssertedEL_first(arg2Isa, defnNecessary, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4946exactlyAssertedEL_first(arg2Isa, defnIff, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4947exactlyAssertedEL_first(arg2Isa, definingMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4948exactlyAssertedEL_first(arg2Isa, defaultReformulationDirectionInModeForPred, 'Individual', 'UniversalVocabularyMt', vStrDef).
 4949exactlyAssertedEL_first(arg2Isa, cycTransformationProofBindings, 'List', 'UniversalVocabularyMt', vStrDef).
 4950exactlyAssertedEL_first(arg2Isa, cycTacticID, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4951exactlyAssertedEL_first(arg2Isa, cycProofID, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4952exactlyAssertedEL_first(arg2Isa, cycProblemStoreTerms, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4953exactlyAssertedEL_first(arg2Isa, cycProblemStoreProofs, 'CycProof', 'UniversalVocabularyMt', vStrDef).
 4954exactlyAssertedEL_first(arg2Isa, cycProblemStoreProofCount, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4955exactlyAssertedEL_first(arg2Isa, cycProblemStoreProblems, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4956exactlyAssertedEL_first(arg2Isa, cycProblemStoreProblemCount, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4957exactlyAssertedEL_first(arg2Isa, cycProblemStoreLinks, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4958exactlyAssertedEL_first(arg2Isa, cycProblemStoreLinkCount, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4959exactlyAssertedEL_first(arg2Isa, cycProblemStoreInferences, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 4960exactlyAssertedEL_first(arg2Isa, cycProblemStoreInferenceCount, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4961exactlyAssertedEL_first(arg2Isa, cycProblemStoreID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4962exactlyAssertedEL_first(arg2Isa, cycProblemQueryTerms, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4963exactlyAssertedEL_first(arg2Isa, cycProblemProvabilityStatus, tCol, 'UniversalVocabularyMt', vStrDef).
 4964exactlyAssertedEL_first(arg2Isa, cycProblemLinkID, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4965exactlyAssertedEL_first(arg2Isa, cycProblemID, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 4966exactlyAssertedEL_first(arg2Isa, cycProblemDependentLinks, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4967exactlyAssertedEL_first(arg2Isa, cycProblemArgumentLinks, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 4968exactlyAssertedEL_first(arg2Isa, cycInferenceRelevantProblems, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 4969exactlyAssertedEL_first(arg2Isa, cycInferenceAnswerLink, 'CycProblemLink-AnswerLink', 'UniversalVocabularyMt', vStrDef).
 4970exactlyAssertedEL_first(arg2Isa, constrainsArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4971exactlyAssertedEL_first(arg2Isa, constantName, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4972exactlyAssertedEL_first(arg2Isa, constantID, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4973exactlyAssertedEL_first(arg2Isa, constantGUID, 'SubLString', 'UniversalVocabularyMt', vStrDef).
 4974exactlyAssertedEL_first(arg2Isa, conceptuallyRelated, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4975exactlyAssertedEL_first(arg2Isa, completeExtentEnumerableForValueInArg, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4976exactlyAssertedEL_first(arg2Isa, completeExtentEnumerableForArg, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 4977exactlyAssertedEL_first(arg2Isa, completeExtentEnumerableForArg, 'NonNegativeInteger', 'CoreCycLMt', vStrDef).
 4978exactlyAssertedEL_first(arg2Isa, completeExtentDecidableForValueInArg, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4979exactlyAssertedEL_first(arg2Isa, completeExtentDecidableForValueInArg, 'Thing', 'CoreCycLMt', vStrDef).
 4980exactlyAssertedEL_first(arg2Isa, completeExtentAssertedForValueInArg, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4981exactlyAssertedEL_first(arg2Isa, completeExtentAssertedForValueInArg, 'Thing', 'CoreCycLMt', vStrDef).
 4982exactlyAssertedEL_first(arg2Isa, commutativeInArgsAndRest, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4983exactlyAssertedEL_first(arg2Isa, commutativeInArgs, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4984exactlyAssertedEL_first(arg2Isa, comment, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 4985exactlyAssertedEL_first(arg2Isa, collectionExpansion, 'Thing', 'UniversalVocabularyMt', vStrDef).
 4986exactlyAssertedEL_first(arg2Isa, collectionExpansion, 'Thing', 'UniversalVocabularyImplementationMt', vStrDef).
 4987exactlyAssertedEL_first(arg2Isa, collectionConventionMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 4988exactlyAssertedEL_first(arg2Isa, coExtensional, tCol, 'UniversalVocabularyMt', vStrDef).
 4989exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForArgAndRest, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4990exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForArgAndRest, 'PositiveInteger', 'CoreCycLImplementationMt', vStrDef).
 4991exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4992exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForArg, 'PositiveInteger', 'CoreCycLImplementationMt', vStrDef).
 4993exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForAllArgs, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 4994exactlyAssertedEL_first(arg2Isa, canonicalizerDirectiveForAllArgs, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 4995exactlyAssertedEL_first(arg2Isa, backchainForbiddenWhenUnboundInArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4996exactlyAssertedEL_first(arg2Isa, assertionUtility, 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 4997exactlyAssertedEL_first(arg2Isa, assertionDirection, 'CycLAssertionDirection', 'UniversalVocabularyMt', vStrDef).
 4998exactlyAssertedEL_first(arg2Isa, assertedPredicateArg, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 4999exactlyAssertedEL_first(arg2Isa, arityMin, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5000exactlyAssertedEL_first(arg2Isa, arityMax, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5001exactlyAssertedEL_first(arg2Isa, arity, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5002exactlyAssertedEL_first(arg2Isa, arity, 'Integer', 'UniversalVocabularyMt', vStrDef).
 5003exactlyAssertedEL_first(arg2Isa, argsQuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5004exactlyAssertedEL_first(arg2Isa, argSometimesIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5005exactlyAssertedEL_first(arg2Isa, argSometimesIsa, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5006exactlyAssertedEL_first(arg2Isa, argsIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5007exactlyAssertedEL_first(arg2Isa, argsGenl, tCol, 'UniversalVocabularyMt', vStrDef).
 5008exactlyAssertedEL_first(arg2Isa, argQuotedIsa, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5009exactlyAssertedEL_first(arg2Isa, argIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5010exactlyAssertedEL_first(arg2Isa, argIsa, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5011exactlyAssertedEL_first(arg2Isa, argAndRestQuotedIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5012exactlyAssertedEL_first(arg2Isa, argAndRestIsa, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5013exactlyAssertedEL_first(arg2Isa, argAndRestIsa, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5014exactlyAssertedEL_first(arg2Isa, argAndRestGenl, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5015exactlyAssertedEL_first(arg2Isa, arg6SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5016exactlyAssertedEL_first(arg2Isa, arg6QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5017exactlyAssertedEL_first(arg2Isa, arg6Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5018exactlyAssertedEL_first(arg2Isa, arg6Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5019exactlyAssertedEL_first(arg2Isa, arg6Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5020exactlyAssertedEL_first(arg2Isa, arg5SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5021exactlyAssertedEL_first(arg2Isa, arg5QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5022exactlyAssertedEL_first(arg2Isa, arg5Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5023exactlyAssertedEL_first(arg2Isa, arg5Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5024exactlyAssertedEL_first(arg2Isa, arg5Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5025exactlyAssertedEL_first(arg2Isa, arg4SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5026exactlyAssertedEL_first(arg2Isa, arg4QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5027exactlyAssertedEL_first(arg2Isa, arg4Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5028exactlyAssertedEL_first(arg2Isa, arg4Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5029exactlyAssertedEL_first(arg2Isa, arg4Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5030exactlyAssertedEL_first(arg2Isa, arg3SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5031exactlyAssertedEL_first(arg2Isa, arg3QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5032exactlyAssertedEL_first(arg2Isa, arg3Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5033exactlyAssertedEL_first(arg2Isa, arg3Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5034exactlyAssertedEL_first(arg2Isa, arg3Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5035exactlyAssertedEL_first(arg2Isa, arg2SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5036exactlyAssertedEL_first(arg2Isa, arg2QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5037exactlyAssertedEL_first(arg2Isa, arg2Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5038exactlyAssertedEL_first(arg2Isa, arg2Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5039exactlyAssertedEL_first(arg2Isa, arg2Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5040exactlyAssertedEL_first(arg2Isa, arg1SometimesIsa, tCol, 'UniversalVocabularyMt', vStrDef).
 5041exactlyAssertedEL_first(arg2Isa, arg1QuotedIsa, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5042exactlyAssertedEL_first(arg2Isa, arg1Isa, tCol, 'UniversalVocabularyMt', vStrDef).
 5043exactlyAssertedEL_first(arg2Isa, arg1Genl, tCol, 'UniversalVocabularyMt', vStrDef).
 5044exactlyAssertedEL_first(arg2Isa, arg1Format, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5045exactlyAssertedEL_first(arg2Isa, afterRemoving, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5046exactlyAssertedEL_first(arg2Isa, afterAdding, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5047exactlyAssertedEL_first(arg2Isa, admittedArgument, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5048exactlyAssertedEL_first(arg2Isa, admittedAllArgument, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5049exactlyAssertedEL_first(arg2Isa, 'UnitProductFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5050exactlyAssertedEL_first(arg2Isa, 'TLVariableFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5051exactlyAssertedEL_first(arg2Isa, 'substring-CaseInsensitive', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5052exactlyAssertedEL_first(arg2Isa, 'RelationInstanceExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5053exactlyAssertedEL_first(arg2Isa, 'RelationExistsInstanceFn', tCol, 'UniversalVocabularyMt', vStrDef).
 5054exactlyAssertedEL_first(arg2Isa, 'RelationExistsAllFn', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5055exactlyAssertedEL_first(arg2Isa, 'RelationAllExistsFn', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5056exactlyAssertedEL_first(arg2Isa, 'QuotientFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5057exactlyAssertedEL_first(arg2Isa, 'QuantityConversionFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5058exactlyAssertedEL_first(arg2Isa, 'prettyString-Canonical', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5059exactlyAssertedEL_first(arg2Isa, 'PlusAll', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 5060exactlyAssertedEL_first(arg2Isa, 'PlusAll', 'UnaryFunction', 'BaseKB', vStrDef).
 5061exactlyAssertedEL_first(arg2Isa, 'PlusAll', 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 5062exactlyAssertedEL_first(arg2Isa, 'PerFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5063exactlyAssertedEL_first(arg2Isa, 'MtTimeWithGranularityDimFn', tCol, 'UniversalVocabularyMt', vStrDef).
 5064exactlyAssertedEL_first(arg2Isa, 'ModuloFn', 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 5065exactlyAssertedEL_first(arg2Isa, 'Minimum', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 5066exactlyAssertedEL_first(arg2Isa, 'Minimum', 'UnaryFunction', 'BaseKB', vStrDef).
 5067exactlyAssertedEL_first(arg2Isa, 'MeaningInSystemFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5068exactlyAssertedEL_first(arg2Isa, 'Maximum', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 5069exactlyAssertedEL_first(arg2Isa, 'Maximum', 'UnaryFunction', 'BaseKB', vStrDef).
 5070exactlyAssertedEL_first(arg2Isa, 'larkc-hasUri', 'CharacterString', 'BaseKB', vStrDef).
 5071exactlyAssertedEL_first(arg2Isa, 'larkc-hasScalability', 'CharacterString', 'BaseKB', vStrDef).
 5072exactlyAssertedEL_first(arg2Isa, 'larkc-hasEndpoint', 'CharacterString', 'BaseKB', vStrDef).
 5073exactlyAssertedEL_first(arg2Isa, 'larkc-hasCostPerInvocation', 'larkc-euro', 'BaseKB', vStrDef).
 5074exactlyAssertedEL_first(arg2Isa, 'interArgIsa5-4', tCol, 'UniversalVocabularyMt', vStrDef).
 5075exactlyAssertedEL_first(arg2Isa, 'interArgIsa5-3', tCol, 'UniversalVocabularyMt', vStrDef).
 5076exactlyAssertedEL_first(arg2Isa, 'interArgIsa5-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5077exactlyAssertedEL_first(arg2Isa, 'interArgIsa5-1', tCol, 'UniversalVocabularyMt', vStrDef).
 5078exactlyAssertedEL_first(arg2Isa, 'interArgIsa4-5', tCol, 'UniversalVocabularyMt', vStrDef).
 5079exactlyAssertedEL_first(arg2Isa, 'interArgIsa4-3', tCol, 'UniversalVocabularyMt', vStrDef).
 5080exactlyAssertedEL_first(arg2Isa, 'interArgIsa4-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5081exactlyAssertedEL_first(arg2Isa, 'interArgIsa4-1', tCol, 'UniversalVocabularyMt', vStrDef).
 5082exactlyAssertedEL_first(arg2Isa, 'interArgIsa3-5', tCol, 'UniversalVocabularyMt', vStrDef).
 5083exactlyAssertedEL_first(arg2Isa, 'interArgIsa3-4', tCol, 'UniversalVocabularyMt', vStrDef).
 5084exactlyAssertedEL_first(arg2Isa, 'interArgIsa3-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5085exactlyAssertedEL_first(arg2Isa, 'interArgIsa3-1', tCol, 'UniversalVocabularyMt', vStrDef).
 5086exactlyAssertedEL_first(arg2Isa, 'interArgIsa2-5', tCol, 'UniversalVocabularyMt', vStrDef).
 5087exactlyAssertedEL_first(arg2Isa, 'interArgIsa2-4', tCol, 'UniversalVocabularyMt', vStrDef).
 5088exactlyAssertedEL_first(arg2Isa, 'interArgIsa2-3', tCol, 'UniversalVocabularyMt', vStrDef).
 5089exactlyAssertedEL_first(arg2Isa, 'interArgIsa2-1', tCol, 'UniversalVocabularyMt', vStrDef).
 5090exactlyAssertedEL_first(arg2Isa, 'interArgIsa1-5', tCol, 'UniversalVocabularyMt', vStrDef).
 5091exactlyAssertedEL_first(arg2Isa, 'interArgIsa1-4', tCol, 'UniversalVocabularyMt', vStrDef).
 5092exactlyAssertedEL_first(arg2Isa, 'interArgIsa1-3', tCol, 'UniversalVocabularyMt', vStrDef).
 5093exactlyAssertedEL_first(arg2Isa, 'interArgIsa1-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5094exactlyAssertedEL_first(arg2Isa, 'interArgGenl1-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5095exactlyAssertedEL_first(arg2Isa, 'interArgFormat1-2', tCol, 'UniversalVocabularyMt', vStrDef).
 5096exactlyAssertedEL_first(arg2Isa, 'genls-SpecDenotesGenlInstances', tCol, 'UniversalVocabularyMt', vStrDef).
 5097exactlyAssertedEL_first(arg2Isa, 'genls-GenlDenotesSpecInstances', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5098exactlyAssertedEL_first(arg2Isa, 'FunctionToArg', tPred, 'UniversalVocabularyMt', vStrDef).
 5099exactlyAssertedEL_first(arg2Isa, 'FormulaArgFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5100exactlyAssertedEL_first(arg2Isa, 'FOL-PredicateFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5101exactlyAssertedEL_first(arg2Isa, 'FOL-FunctionFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5102exactlyAssertedEL_first(arg2Isa, 'equalStrings-CaseInsensitive', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5103exactlyAssertedEL_first(arg2Isa, 'DifferenceFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5104exactlyAssertedEL_first(arg2Isa, 'DateEncodeStringFn', 'Individual', 'UniversalVocabularyMt', vStrDef).
 5105exactlyAssertedEL_first(arg2Isa, 'DateDecodeStringFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5106exactlyAssertedEL_first(arg2Isa, 'CycTacticFn', 'CycTactic', 'UniversalVocabularyMt', vStrDef).
 5107exactlyAssertedEL_first(arg2Isa, 'CycProofFn', 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5108exactlyAssertedEL_first(arg2Isa, 'CycProblemLinkFn', 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5109exactlyAssertedEL_first(arg2Isa, 'CycProblemFn', 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5110exactlyAssertedEL_first(arg2Isa, 'CycInferenceFn', 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5111exactlyAssertedEL_first(arg2Isa, 'Average', 'UnaryFunction', 'UniversalVocabularyMt', vStrDef).
 5112exactlyAssertedEL_first(arg2Isa, 'Average', 'UnaryFunction', 'BaseKB', vStrDef).
 5113exactlyAssertedEL_first(arg2Isa, 'assertionUtility-1', 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 5114exactlyAssertedEL_first(arg2Genl, siblingDisjointExceptions, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5115exactlyAssertedEL_first(arg2Genl, resultQuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5116exactlyAssertedEL_first(arg2Genl, resultIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5117exactlyAssertedEL_first(arg2Genl, resultGenl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5118exactlyAssertedEL_first(arg2Genl, relationExistsMinAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5119exactlyAssertedEL_first(arg2Genl, relationExistsMaxAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5120exactlyAssertedEL_first(arg2Genl, relationExistsInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5121exactlyAssertedEL_first(arg2Genl, relationExistsCountAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5122exactlyAssertedEL_first(arg2Genl, relationExistsAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5123exactlyAssertedEL_first(arg2Genl, relationAllInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5124exactlyAssertedEL_first(arg2Genl, relationAllExistsMin, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5125exactlyAssertedEL_first(arg2Genl, relationAllExistsMax, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5126exactlyAssertedEL_first(arg2Genl, relationAllExistsCount, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5127exactlyAssertedEL_first(arg2Genl, relationAllExists, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5128exactlyAssertedEL_first(arg2Genl, relationAll, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5129exactlyAssertedEL_first(arg2Genl, quotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5130exactlyAssertedEL_first(arg2Genl, nearestIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5131exactlyAssertedEL_first(arg2Genl, nearestGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5132exactlyAssertedEL_first(arg2Genl, nearestDifferentGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5133exactlyAssertedEL_first(arg2Genl, nearestCommonSpecs, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5134exactlyAssertedEL_first(arg2Genl, nearestCommonGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5135exactlyAssertedEL_first(arg2Genl, isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5136exactlyAssertedEL_first(arg2Genl, instanceElementType, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5137exactlyAssertedEL_first(arg2Genl, genls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5138exactlyAssertedEL_first(arg2Genl, evaluationResultQuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5139exactlyAssertedEL_first(arg2Genl, disjointWith, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5140exactlyAssertedEL_first(arg2Genl, cycProblemProvabilityStatus, 'CycProvabilityStatus', 'UniversalVocabularyMt', vStrDef).
 5141exactlyAssertedEL_first(arg2Genl, coExtensional, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5142exactlyAssertedEL_first(arg2Genl, argsQuotedIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5143exactlyAssertedEL_first(arg2Genl, argsQuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5144exactlyAssertedEL_first(arg2Genl, argsIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5145exactlyAssertedEL_first(arg2Genl, argsGenl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5146exactlyAssertedEL_first(arg2Genl, arg6SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5147exactlyAssertedEL_first(arg2Genl, arg6QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5148exactlyAssertedEL_first(arg2Genl, arg6Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5149exactlyAssertedEL_first(arg2Genl, arg6Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5150exactlyAssertedEL_first(arg2Genl, arg5SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5151exactlyAssertedEL_first(arg2Genl, arg5QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5152exactlyAssertedEL_first(arg2Genl, arg5Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5153exactlyAssertedEL_first(arg2Genl, arg5Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5154exactlyAssertedEL_first(arg2Genl, arg4SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5155exactlyAssertedEL_first(arg2Genl, arg4QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5156exactlyAssertedEL_first(arg2Genl, arg4Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5157exactlyAssertedEL_first(arg2Genl, arg4Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5158exactlyAssertedEL_first(arg2Genl, arg3SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5159exactlyAssertedEL_first(arg2Genl, arg3QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5160exactlyAssertedEL_first(arg2Genl, arg3Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5161exactlyAssertedEL_first(arg2Genl, arg3Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5162exactlyAssertedEL_first(arg2Genl, arg2SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5163exactlyAssertedEL_first(arg2Genl, arg2QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5164exactlyAssertedEL_first(arg2Genl, arg2Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5165exactlyAssertedEL_first(arg2Genl, arg2Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5166exactlyAssertedEL_first(arg2Genl, arg1SometimesIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5167exactlyAssertedEL_first(arg2Genl, arg1QuotedIsa, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5168exactlyAssertedEL_first(arg2Genl, arg1Isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5169exactlyAssertedEL_first(arg2Genl, arg1Genl, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5170exactlyAssertedEL_first(arg2Genl, 'RelationExistsInstanceFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5171exactlyAssertedEL_first(arg2Genl, 'larkc-pluginByDataConnectsTo', 'larkc-Plugin', 'BaseKB', vStrDef).
 5172exactlyAssertedEL_first(arg2Genl, 'larkc-hasOutputType', 'larkc-Resource', 'BaseKB', vStrDef).
 5173exactlyAssertedEL_first(arg2Genl, 'larkc-hasInputType', 'larkc-Resource', 'BaseKB', vStrDef).
 5174exactlyAssertedEL_first(arg2Genl, 'interArgIsa5-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5175exactlyAssertedEL_first(arg2Genl, 'interArgIsa5-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5176exactlyAssertedEL_first(arg2Genl, 'interArgIsa5-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5177exactlyAssertedEL_first(arg2Genl, 'interArgIsa5-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5178exactlyAssertedEL_first(arg2Genl, 'interArgIsa4-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5179exactlyAssertedEL_first(arg2Genl, 'interArgIsa4-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5180exactlyAssertedEL_first(arg2Genl, 'interArgIsa4-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5181exactlyAssertedEL_first(arg2Genl, 'interArgIsa4-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5182exactlyAssertedEL_first(arg2Genl, 'interArgIsa3-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5183exactlyAssertedEL_first(arg2Genl, 'interArgIsa3-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5184exactlyAssertedEL_first(arg2Genl, 'interArgIsa3-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5185exactlyAssertedEL_first(arg2Genl, 'interArgIsa3-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5186exactlyAssertedEL_first(arg2Genl, 'interArgIsa2-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5187exactlyAssertedEL_first(arg2Genl, 'interArgIsa2-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5188exactlyAssertedEL_first(arg2Genl, 'interArgIsa2-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5189exactlyAssertedEL_first(arg2Genl, 'interArgIsa2-1', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5190exactlyAssertedEL_first(arg2Genl, 'interArgIsa1-5', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5191exactlyAssertedEL_first(arg2Genl, 'interArgIsa1-4', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5192exactlyAssertedEL_first(arg2Genl, 'interArgIsa1-3', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5193exactlyAssertedEL_first(arg2Genl, 'interArgIsa1-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5194exactlyAssertedEL_first(arg2Genl, 'interArgFormat1-2', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5195exactlyAssertedEL_first(arg2Genl, 'genls-GenlDenotesSpecInstances', 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5196exactlyAssertedEL_first(arg2Format, unitMultiplicationFactor, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5197exactlyAssertedEL_first(arg2Format, transitiveViaArgInverse, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5198exactlyAssertedEL_first(arg2Format, transitiveViaArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5199exactlyAssertedEL_first(arg2Format, termOfUnit, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5200exactlyAssertedEL_first(arg2Format, termExternalIDString, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5201exactlyAssertedEL_first(arg2Format, synonymousExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5202exactlyAssertedEL_first(arg2Format, subsetOf, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5203exactlyAssertedEL_first(arg2Format, sharedNotes, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5204exactlyAssertedEL_first(arg2Format, sentenceTruth, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5205exactlyAssertedEL_first(arg2Format, salientAssertions, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5206exactlyAssertedEL_first(arg2Format, ruleAfterRemoving, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5207exactlyAssertedEL_first(arg2Format, ruleAfterAdding, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5208exactlyAssertedEL_first(arg2Format, rewriteOf, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5209exactlyAssertedEL_first(arg2Format, resultQuotedIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5210exactlyAssertedEL_first(arg2Format, resultIsaArgIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5211exactlyAssertedEL_first(arg2Format, resultIsaArg, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5212exactlyAssertedEL_first(arg2Format, requiredArg2Pred, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5213exactlyAssertedEL_first(arg2Format, requiredArg1Pred, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5214exactlyAssertedEL_first(arg2Format, relationInstanceExists, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5215exactlyAssertedEL_first(arg2Format, relationInstanceAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5216exactlyAssertedEL_first(arg2Format, relationExpansion, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5217exactlyAssertedEL_first(arg2Format, relationExistsMinAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5218exactlyAssertedEL_first(arg2Format, relationExistsMaxAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5219exactlyAssertedEL_first(arg2Format, relationExistsInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5220exactlyAssertedEL_first(arg2Format, relationExistsCountAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5221exactlyAssertedEL_first(arg2Format, relationExistsAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5222exactlyAssertedEL_first(arg2Format, relationAllInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5223exactlyAssertedEL_first(arg2Format, relationAllExistsMin, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5224exactlyAssertedEL_first(arg2Format, relationAllExistsMax, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5225exactlyAssertedEL_first(arg2Format, relationAllExistsCount, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5226exactlyAssertedEL_first(arg2Format, relationAllExists, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5227exactlyAssertedEL_first(arg2Format, relationAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5228exactlyAssertedEL_first(arg2Format, prettyString, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5229exactlyAssertedEL_first(arg2Format, preservesGenlsInArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5230exactlyAssertedEL_first(arg2Format, predicateConventionMt, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5231exactlyAssertedEL_first(arg2Format, pointQuantValue, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5232exactlyAssertedEL_first(arg2Format, overlappingExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5233exactlyAssertedEL_first(arg2Format, operatorFormulas, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5234exactlyAssertedEL_first(arg2Format, opaqueArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5235exactlyAssertedEL_first(arg2Format, numericallyEquals, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5236exactlyAssertedEL_first(arg2Format, nthSmallestElement, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5237exactlyAssertedEL_first(arg2Format, negationPreds, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5238exactlyAssertedEL_first(arg2Format, negationInverse, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5239exactlyAssertedEL_first(arg2Format, natFunction, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5240exactlyAssertedEL_first(arg2Format, natArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5241exactlyAssertedEL_first(arg2Format, myCreator, 'SingleEntry', 'BookkeepingMt', vStrMon).
 5242exactlyAssertedEL_first(arg2Format, myCreationTime, 'SingleEntry', 'BookkeepingMt', vStrMon).
 5243exactlyAssertedEL_first(arg2Format, myCreationSecond, 'SingleEntry', 'BookkeepingMt', vStrMon).
 5244exactlyAssertedEL_first(arg2Format, myCreationPurpose, singleEntryFormatInArgs, 'BookkeepingMt', vStrDef).
 5245exactlyAssertedEL_first(arg2Format, multiplicationUnits, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5246exactlyAssertedEL_first(arg2Format, minQuantValue, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5247exactlyAssertedEL_first(arg2Format, means, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5248exactlyAssertedEL_first(arg2Format, maxQuantValue, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5249exactlyAssertedEL_first(arg2Format, isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5250exactlyAssertedEL_first(arg2Format, interArgResultIsaReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5251exactlyAssertedEL_first(arg2Format, interArgResultIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5252exactlyAssertedEL_first(arg2Format, interArgResultGenlReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5253exactlyAssertedEL_first(arg2Format, interArgResultGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5254exactlyAssertedEL_first(arg2Format, interArgIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5255exactlyAssertedEL_first(arg2Format, interArgDifferent, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5256exactlyAssertedEL_first(arg2Format, integerBetween, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5257exactlyAssertedEL_first(arg2Format, independentArg, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5258exactlyAssertedEL_first(arg2Format, greaterThanOrEqualTo, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5259exactlyAssertedEL_first(arg2Format, greaterThan, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5260exactlyAssertedEL_first(arg2Format, genls, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5261exactlyAssertedEL_first(arg2Format, genlMt, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5262exactlyAssertedEL_first(arg2Format, genKeyword, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5263exactlyAssertedEL_first(arg2Format, formulaArity, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5264exactlyAssertedEL_first(arg2Format, followingValue, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5265exactlyAssertedEL_first(arg2Format, fanOutArg, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5266exactlyAssertedEL_first(arg2Format, extentCardinality, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5267exactlyAssertedEL_first(arg2Format, expresses, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5268exactlyAssertedEL_first(arg2Format, expansionDefn, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5269exactlyAssertedEL_first(arg2Format, expansion, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5270exactlyAssertedEL_first(arg2Format, exampleAssertions, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5271exactlyAssertedEL_first(arg2Format, evaluationDefn, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5272exactlyAssertedEL_first(arg2Format, elInverse, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5273exactlyAssertedEL_first(arg2Format, elementOf, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5274exactlyAssertedEL_first(arg2Format, disjointWith, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5275exactlyAssertedEL_first(arg2Format, different, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5276exactlyAssertedEL_first(arg2Format, denotes, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5277exactlyAssertedEL_first(arg2Format, defnSufficient, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5278exactlyAssertedEL_first(arg2Format, defnIff, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5279exactlyAssertedEL_first(arg2Format, definingMt, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5280exactlyAssertedEL_first(arg2Format, cycTransformationProofBindings, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5281exactlyAssertedEL_first(arg2Format, cycProblemStoreTerms, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5282exactlyAssertedEL_first(arg2Format, cycProblemStoreProofs, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5283exactlyAssertedEL_first(arg2Format, cycProblemStoreProofCount, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5284exactlyAssertedEL_first(arg2Format, cycProblemStoreProblems, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5285exactlyAssertedEL_first(arg2Format, cycProblemStoreProblemCount, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5286exactlyAssertedEL_first(arg2Format, cycProblemStoreLinks, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5287exactlyAssertedEL_first(arg2Format, cycProblemStoreLinkCount, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5288exactlyAssertedEL_first(arg2Format, cycProblemStoreInferences, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5289exactlyAssertedEL_first(arg2Format, cycProblemStoreInferenceCount, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5290exactlyAssertedEL_first(arg2Format, cycProblemStoreID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5291exactlyAssertedEL_first(arg2Format, cycProblemQueryTerms, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5292exactlyAssertedEL_first(arg2Format, cycProblemQuerySentence, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5293exactlyAssertedEL_first(arg2Format, cycProblemProvabilityStatus, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5294exactlyAssertedEL_first(arg2Format, cycProblemDependentLinks, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5295exactlyAssertedEL_first(arg2Format, cycProblemArgumentLinks, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5296exactlyAssertedEL_first(arg2Format, cycInferenceRelevantProblems, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5297exactlyAssertedEL_first(arg2Format, cycInferenceAnswerLink, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5298exactlyAssertedEL_first(arg2Format, constrainsArg, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5299exactlyAssertedEL_first(arg2Format, constantName, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5300exactlyAssertedEL_first(arg2Format, constantName, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5301exactlyAssertedEL_first(arg2Format, constantID, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5302exactlyAssertedEL_first(arg2Format, constantGUID, 'SingleEntry', 'UniversalVocabularyMt', vStrMon).
 5303exactlyAssertedEL_first(arg2Format, conceptuallyRelated, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5304exactlyAssertedEL_first(arg2Format, commutativeInArgsAndRest, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5305exactlyAssertedEL_first(arg2Format, comment, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5306exactlyAssertedEL_first(arg2Format, collectionConventionMt, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5307exactlyAssertedEL_first(arg2Format, assertionDirection, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5308exactlyAssertedEL_first(arg2Format, arityMin, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5309exactlyAssertedEL_first(arg2Format, arityMax, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5310exactlyAssertedEL_first(arg2Format, arity, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5311exactlyAssertedEL_first(arg2Format, argSometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5312exactlyAssertedEL_first(arg2Format, argsIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5313exactlyAssertedEL_first(arg2Format, argsGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5314exactlyAssertedEL_first(arg2Format, argIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5315exactlyAssertedEL_first(arg2Format, argAndRestIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5316exactlyAssertedEL_first(arg2Format, argAndRestGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5317exactlyAssertedEL_first(arg2Format, arg6SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5318exactlyAssertedEL_first(arg2Format, arg6Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5319exactlyAssertedEL_first(arg2Format, arg6Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5320exactlyAssertedEL_first(arg2Format, arg5SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5321exactlyAssertedEL_first(arg2Format, arg5Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5322exactlyAssertedEL_first(arg2Format, arg5Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5323exactlyAssertedEL_first(arg2Format, arg4SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5324exactlyAssertedEL_first(arg2Format, arg4Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5325exactlyAssertedEL_first(arg2Format, arg4Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5326exactlyAssertedEL_first(arg2Format, arg3SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5327exactlyAssertedEL_first(arg2Format, arg3Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5328exactlyAssertedEL_first(arg2Format, arg3Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5329exactlyAssertedEL_first(arg2Format, arg2SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5330exactlyAssertedEL_first(arg2Format, arg2Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5331exactlyAssertedEL_first(arg2Format, arg2Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5332exactlyAssertedEL_first(arg2Format, arg1SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5333exactlyAssertedEL_first(arg2Format, arg1Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5334exactlyAssertedEL_first(arg2Format, arg1Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5335exactlyAssertedEL_first(arg2Format, afterAdding, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5336exactlyAssertedEL_first(arg2Format, admittedArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5337exactlyAssertedEL_first(arg2Format, admittedAllArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5338exactlyAssertedEL_first(arg2Format, 'prettyString-Canonical', 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5339exactlyAssertedEL_first(arg2Format, 'interArgIsa5-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5340exactlyAssertedEL_first(arg2Format, 'interArgIsa5-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5341exactlyAssertedEL_first(arg2Format, 'interArgIsa5-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5342exactlyAssertedEL_first(arg2Format, 'interArgIsa5-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5343exactlyAssertedEL_first(arg2Format, 'interArgIsa4-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5344exactlyAssertedEL_first(arg2Format, 'interArgIsa4-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5345exactlyAssertedEL_first(arg2Format, 'interArgIsa4-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5346exactlyAssertedEL_first(arg2Format, 'interArgIsa4-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5347exactlyAssertedEL_first(arg2Format, 'interArgIsa3-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5348exactlyAssertedEL_first(arg2Format, 'interArgIsa3-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5349exactlyAssertedEL_first(arg2Format, 'interArgIsa3-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5350exactlyAssertedEL_first(arg2Format, 'interArgIsa3-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5351exactlyAssertedEL_first(arg2Format, 'interArgIsa2-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5352exactlyAssertedEL_first(arg2Format, 'interArgIsa2-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5353exactlyAssertedEL_first(arg2Format, 'interArgIsa2-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5354exactlyAssertedEL_first(arg2Format, 'interArgIsa2-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5355exactlyAssertedEL_first(arg2Format, 'interArgIsa1-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5356exactlyAssertedEL_first(arg2Format, 'interArgIsa1-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5357exactlyAssertedEL_first(arg2Format, 'interArgIsa1-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5358exactlyAssertedEL_first(arg2Format, 'interArgIsa1-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5359exactlyAssertedEL_first(arg2Format, 'interArgFormat1-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5360exactlyAssertedEL_first(arg1QuotedIsa, xor, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5361exactlyAssertedEL_first(arg1QuotedIsa, xor, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 5362exactlyAssertedEL_first(arg1QuotedIsa, unknownSentence, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 5363exactlyAssertedEL_first(arg1QuotedIsa, trueSubL, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5364exactlyAssertedEL_first(arg1QuotedIsa, trueSentence, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5365exactlyAssertedEL_first(arg1QuotedIsa, thereExists, ftVar, 'UniversalVocabularyMt', vStrDef).
 5366exactlyAssertedEL_first(arg1QuotedIsa, termOfUnit, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5367exactlyAssertedEL_first(arg1QuotedIsa, termExternalIDString, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 5368exactlyAssertedEL_first(arg1QuotedIsa, termDependsOn, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5369exactlyAssertedEL_first(arg1QuotedIsa, sharedNotes, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 5370exactlyAssertedEL_first(arg1QuotedIsa, sentenceImplies, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5371exactlyAssertedEL_first(arg1QuotedIsa, sentenceEquiv, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5372exactlyAssertedEL_first(arg1QuotedIsa, salientAssertions, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5373exactlyAssertedEL_first(arg1QuotedIsa, rewriteOf, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5374exactlyAssertedEL_first(arg1QuotedIsa, reformulatorRule, 'CycLExpression', 'UniversalVocabularyMt', vStrDef).
 5375exactlyAssertedEL_first(arg1QuotedIsa, reformulatorEquiv, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 5376exactlyAssertedEL_first(arg1QuotedIsa, reformulatorEquals, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5377exactlyAssertedEL_first(arg1QuotedIsa, querySentence, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 5378exactlyAssertedEL_first(arg1QuotedIsa, pragmaticRequirement, 'CycLSentence-Askable', 'UniversalVocabularyMt', vStrDef).
 5379exactlyAssertedEL_first(arg1QuotedIsa, pointQuantValue, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5380exactlyAssertedEL_first(arg1QuotedIsa, performSubL, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5381exactlyAssertedEL_first(arg1QuotedIsa, or, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5382exactlyAssertedEL_first(arg1QuotedIsa, operatorFormulas, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5383exactlyAssertedEL_first(arg1QuotedIsa, oldConstantName, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5384exactlyAssertedEL_first(arg1QuotedIsa, oldConstantName, 'CycLConstant', 'BookkeepingMt', vStrDef).
 5385exactlyAssertedEL_first(arg1QuotedIsa, not, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5386exactlyAssertedEL_first(arg1QuotedIsa, not, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 5387exactlyAssertedEL_first(arg1QuotedIsa, natFunction, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5388exactlyAssertedEL_first(arg1QuotedIsa, natArgumentsEqual, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5389exactlyAssertedEL_first(arg1QuotedIsa, natArgument, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5390exactlyAssertedEL_first(arg1QuotedIsa, myCreator, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5391exactlyAssertedEL_first(arg1QuotedIsa, myCreator, 'CycLReifiableDenotationalTerm', 'BookkeepingMt', vStrDef).
 5392exactlyAssertedEL_first(arg1QuotedIsa, myCreationTime, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5393exactlyAssertedEL_first(arg1QuotedIsa, myCreationTime, 'CycLConstant', 'BookkeepingMt', vStrDef).
 5394exactlyAssertedEL_first(arg1QuotedIsa, myCreationSecond, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5395exactlyAssertedEL_first(arg1QuotedIsa, myCreationSecond, 'CycLConstant', 'BookkeepingMt', vStrDef).
 5396exactlyAssertedEL_first(arg1QuotedIsa, myCreationPurpose, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5397exactlyAssertedEL_first(arg1QuotedIsa, myCreationPurpose, 'CycLReifiableDenotationalTerm', 'BookkeepingMt', vStrDef).
 5398exactlyAssertedEL_first(arg1QuotedIsa, minimize, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5399exactlyAssertedEL_first(arg1QuotedIsa, knownSentence, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5400exactlyAssertedEL_first(arg1QuotedIsa, knownAntecedentRule, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 5401exactlyAssertedEL_first(arg1QuotedIsa, irrelevantTerm, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5402exactlyAssertedEL_first(arg1QuotedIsa, irrelevantAssertion, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5403exactlyAssertedEL_first(arg1QuotedIsa, indexicalReferent, 'IndeterminateTerm', 'UniversalVocabularyMt', vStrDef).
 5404exactlyAssertedEL_first(arg1QuotedIsa, implies, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5405exactlyAssertedEL_first(arg1QuotedIsa, implies, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 5406exactlyAssertedEL_first(arg1QuotedIsa, hypotheticalTerm, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5407exactlyAssertedEL_first(arg1QuotedIsa, hlPrototypicalInstance, 'HLPrototypicalTerm', 'UniversalVocabularyMt', vStrDef).
 5408exactlyAssertedEL_first(arg1QuotedIsa, hlPrototypicalInstance, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 5409exactlyAssertedEL_first(arg1QuotedIsa, highlyRelevantTerm, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5410exactlyAssertedEL_first(arg1QuotedIsa, highlyRelevantAssertion, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5411exactlyAssertedEL_first(arg1QuotedIsa, genMassNoun, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5412exactlyAssertedEL_first(arg1QuotedIsa, genlRules, 'CycLRuleAssertion', 'UniversalVocabularyMt', vStrDef).
 5413exactlyAssertedEL_first(arg1QuotedIsa, genKeyword, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5414exactlyAssertedEL_first(arg1QuotedIsa, forwardNonTriggerLiteral, 'CycLOpenSentence', 'UniversalVocabularyMt', vStrDef).
 5415exactlyAssertedEL_first(arg1QuotedIsa, formulaArity, 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 5416exactlyAssertedEL_first(arg1QuotedIsa, forAll, ftVar, 'UniversalVocabularyMt', vStrDef).
 5417exactlyAssertedEL_first(arg1QuotedIsa, exceptWhen, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5418exactlyAssertedEL_first(arg1QuotedIsa, exceptFor, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5419exactlyAssertedEL_first(arg1QuotedIsa, except, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5420exactlyAssertedEL_first(arg1QuotedIsa, exampleAssertions, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5421exactlyAssertedEL_first(arg1QuotedIsa, exactlyAssertedEL_next, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5422exactlyAssertedEL_first(arg1QuotedIsa, equiv, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5423exactlyAssertedEL_first(arg1QuotedIsa, equiv, 'CycLSentence-Assertible', 'BaseKB', vStrDef).
 5424exactlyAssertedEL_first(arg1QuotedIsa, ephemeralTerm, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5425exactlyAssertedEL_first(arg1QuotedIsa, definingMt, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5426exactlyAssertedEL_first(arg1QuotedIsa, constraint, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5427exactlyAssertedEL_first(arg1QuotedIsa, constantName, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5428exactlyAssertedEL_first(arg1QuotedIsa, constantID, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5429exactlyAssertedEL_first(arg1QuotedIsa, constantGUID, 'CycLConstant', 'UniversalVocabularyMt', vStrDef).
 5430exactlyAssertedEL_first(arg1QuotedIsa, consistent, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5431exactlyAssertedEL_first(arg1QuotedIsa, comment, 'CycLIndexedTerm', 'UniversalVocabularyMt', vStrDef).
 5432exactlyAssertedEL_first(arg1QuotedIsa, assertionUtility, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5433exactlyAssertedEL_first(arg1QuotedIsa, assertionDirection, 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5434exactlyAssertedEL_first(arg1QuotedIsa, assertedTermSentences, 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 5435exactlyAssertedEL_first(arg1QuotedIsa, knownSentence, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5436exactlyAssertedEL_first(arg1QuotedIsa, and, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5437exactlyAssertedEL_first(arg1QuotedIsa, admittedSentence, 'CycLSentence-Assertible', 'UniversalVocabularyMt', vStrDef).
 5438exactlyAssertedEL_first(arg1QuotedIsa, admittedNAT, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5439exactlyAssertedEL_first(arg1QuotedIsa, 'UncanonicalizerAssertionFn', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5440exactlyAssertedEL_first(arg1QuotedIsa, 'TheSetOf', ftVar, 'UniversalVocabularyMt', vStrDef).
 5441exactlyAssertedEL_first(arg1QuotedIsa, 'TheCollectionOf', ftVar, 'UniversalVocabularyMt', vStrDef).
 5442exactlyAssertedEL_first(arg1QuotedIsa, 'SubLQuoteFn', 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5443exactlyAssertedEL_first(arg1QuotedIsa, 'SkolemFunctionFn', 'SubLList', 'UniversalVocabularyMt', vStrDef).
 5444exactlyAssertedEL_first(arg1QuotedIsa, 'SkolemFuncNFn', 'SubLList', 'UniversalVocabularyMt', vStrDef).
 5445exactlyAssertedEL_first(arg1QuotedIsa, 'Quote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 5446exactlyAssertedEL_first(arg1QuotedIsa, 'QuasiQuote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 5447exactlyAssertedEL_first(arg1QuotedIsa, 'Kappa', 'SubLList', 'UniversalVocabularyMt', vStrDef).
 5448exactlyAssertedEL_first(arg1QuotedIsa, 'FormulaArityFn', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 5449exactlyAssertedEL_first(arg1QuotedIsa, 'FormulaArgSetFn', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 5450exactlyAssertedEL_first(arg1QuotedIsa, 'FormulaArgListFn', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 5451exactlyAssertedEL_first(arg1QuotedIsa, 'ExpandSubLFn', 'SubLList', 'UniversalVocabularyMt', vStrDef).
 5452exactlyAssertedEL_first(arg1QuotedIsa, 'EvaluateSubLFn', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 5453exactlyAssertedEL_first(arg1QuotedIsa, 'EscapeQuote', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 5454exactlyAssertedEL_first(arg1QuotedIsa, 'assertionUtility-1', 'CycLAssertion', 'UniversalVocabularyMt', vStrDef).
 5455exactlyAssertedEL_first(arg1Isa, unitMultiplicationFactor, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5456exactlyAssertedEL_first(arg1Isa, trueSubL, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5457exactlyAssertedEL_first(arg1Isa, trueRule, 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 5458exactlyAssertedEL_first(arg1Isa, transitiveViaArgInverse, tPred, 'UniversalVocabularyMt', vStrDef).
 5459exactlyAssertedEL_first(arg1Isa, transitiveViaArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5460exactlyAssertedEL_first(arg1Isa, thereExistExactly, 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5461exactlyAssertedEL_first(arg1Isa, thereExistAtMost, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5462exactlyAssertedEL_first(arg1Isa, thereExistAtLeast, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5463exactlyAssertedEL_first(arg1Isa, termOfUnit, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5464exactlyAssertedEL_first(arg1Isa, termExternalIDString, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5465exactlyAssertedEL_first(arg1Isa, termDependsOn, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5466exactlyAssertedEL_first(arg1Isa, termChosen, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5467exactlyAssertedEL_first(arg1Isa, synonymousExternalConcept, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5468exactlyAssertedEL_first(arg1Isa, substring, 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5469exactlyAssertedEL_first(arg1Isa, subsetOf, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5470exactlyAssertedEL_first(arg1Isa, skolemizeForward, 'ReifiableFunction', 'UniversalVocabularyMt', vStrDef).
 5471exactlyAssertedEL_first(arg1Isa, skolem, 'SkolemFunction', 'UniversalVocabularyMt', vStrDef).
 5472exactlyAssertedEL_first(arg1Isa, singleEntryFormatInArgs, tPred, 'UniversalVocabularyMt', vStrDef).
 5473exactlyAssertedEL_first(arg1Isa, siblingDisjointExceptions, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5474exactlyAssertedEL_first(arg1Isa, siblingDisjointExceptions, 'SetOrCollection', 'BaseKB', vStrDef).
 5475exactlyAssertedEL_first(arg1Isa, sharedNotes, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5476exactlyAssertedEL_first(arg1Isa, sentenceEquiv, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5477exactlyAssertedEL_first(arg1Isa, sentenceEquiv, 'Thing', 'BaseKB', vStrDef).
 5478exactlyAssertedEL_first(arg1Isa, sentenceEquiv, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5479exactlyAssertedEL_first(arg1Isa, sentenceEquiv, 'Individual', 'BaseKB', vStrDef).
 5480exactlyAssertedEL_first(arg1Isa, sentenceDesignationArgnum, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 5481exactlyAssertedEL_first(arg1Isa, scopingArg, 'ScopingRelation', 'UniversalVocabularyMt', vStrDef).
 5482exactlyAssertedEL_first(arg1Isa, salientAssertions, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5483exactlyAssertedEL_first(arg1Isa, ruleTemplateDirection, 'RuleTemplate', 'UniversalVocabularyMt', vStrDef).
 5484exactlyAssertedEL_first(arg1Isa, ruleAfterRemoving, tPred, 'UniversalVocabularyMt', vStrDef).
 5485exactlyAssertedEL_first(arg1Isa, ruleAfterRemoving, tPred, 'CoreCycLImplementationMt', vStrDef).
 5486exactlyAssertedEL_first(arg1Isa, ruleAfterAdding, tPred, 'UniversalVocabularyMt', vStrDef).
 5487exactlyAssertedEL_first(arg1Isa, ruleAfterAdding, tPred, 'CoreCycLImplementationMt', vStrDef).
 5488exactlyAssertedEL_first(arg1Isa, rewriteOf, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5489exactlyAssertedEL_first(arg1Isa, resultQuotedIsa, tFunction, 'UniversalVocabularyMt', vStrDef).
 5490exactlyAssertedEL_first(arg1Isa, resultIsaArgIsa, tFunction, 'UniversalVocabularyMt', vStrDef).
 5491exactlyAssertedEL_first(arg1Isa, resultIsaArg, tFunction, 'UniversalVocabularyMt', vStrDef).
 5492exactlyAssertedEL_first(arg1Isa, resultIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5493exactlyAssertedEL_first(arg1Isa, resultIsa, tRelation, 'BaseKB', vStrDef).
 5494exactlyAssertedEL_first(arg1Isa, resultIsa, tFunction, 'UniversalVocabularyMt', vStrDef).
 5495exactlyAssertedEL_first(arg1Isa, resultGenlArg, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 5496exactlyAssertedEL_first(arg1Isa, resultGenl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5497exactlyAssertedEL_first(arg1Isa, resultGenl, tRelation, 'BaseKB', vStrDef).
 5498exactlyAssertedEL_first(arg1Isa, resultGenl, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 5499exactlyAssertedEL_first(arg1Isa, requiredArg3Pred, tCol, 'UniversalVocabularyMt', vStrDef).
 5500exactlyAssertedEL_first(arg1Isa, requiredArg2Pred, tCol, 'UniversalVocabularyMt', vStrDef).
 5501exactlyAssertedEL_first(arg1Isa, requiredArg1Pred, tCol, 'UniversalVocabularyMt', vStrDef).
 5502exactlyAssertedEL_first(arg1Isa, relationMemberInstance, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5503exactlyAssertedEL_first(arg1Isa, relationInstanceMember, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5504exactlyAssertedEL_first(arg1Isa, relationInstanceExists, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5505exactlyAssertedEL_first(arg1Isa, relationInstanceAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5506exactlyAssertedEL_first(arg1Isa, relationExpansion, tPred, 'UniversalVocabularyMt', vStrDef).
 5507exactlyAssertedEL_first(arg1Isa, relationExistsMinAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5508exactlyAssertedEL_first(arg1Isa, relationExistsMaxAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5509exactlyAssertedEL_first(arg1Isa, relationExistsInstance, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5510exactlyAssertedEL_first(arg1Isa, relationExistsCountAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5511exactlyAssertedEL_first(arg1Isa, relationExistsAll, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5512exactlyAssertedEL_first(arg1Isa, relationAllInstance, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5513exactlyAssertedEL_first(arg1Isa, relationAllExistsMin, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5514exactlyAssertedEL_first(arg1Isa, relationAllExistsMax, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5515exactlyAssertedEL_first(arg1Isa, relationAllExistsCount, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5516exactlyAssertedEL_first(arg1Isa, relationAllExists, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5517exactlyAssertedEL_first(arg1Isa, relationAll, 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5518exactlyAssertedEL_first(arg1Isa, reformulatorRuleProperties, tCol, 'UniversalVocabularyMt', vStrDef).
 5519exactlyAssertedEL_first(arg1Isa, reformulatorRule, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5520exactlyAssertedEL_first(arg1Isa, reformulatorEquals, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5521exactlyAssertedEL_first(arg1Isa, reformulationPrecondition, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5522exactlyAssertedEL_first(arg1Isa, reformulationDirectionInMode, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5523exactlyAssertedEL_first(arg1Isa, ratioOfTo, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5524exactlyAssertedEL_first(arg1Isa, quotedIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5525exactlyAssertedEL_first(arg1Isa, quotedDefnSufficient, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5526exactlyAssertedEL_first(arg1Isa, quotedDefnNecessary, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5527exactlyAssertedEL_first(arg1Isa, quotedDefnIff, 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5528exactlyAssertedEL_first(arg1Isa, quotedArgument, tRelation, 'UniversalVocabularyMt', vStrDef).
 5529exactlyAssertedEL_first(arg1Isa, quantitySubsumes, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5530exactlyAssertedEL_first(arg1Isa, quantityIntersects, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5531exactlyAssertedEL_first(arg1Isa, prettyString, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5532exactlyAssertedEL_first(arg1Isa, preservesGenlsInArg, 'CollectionDenotingFunction', 'UniversalVocabularyMt', vStrDef).
 5533exactlyAssertedEL_first(arg1Isa, predicateConventionMt, tPred, 'UniversalVocabularyMt', vStrDef).
 5534exactlyAssertedEL_first(arg1Isa, pragmaticallyNormal, 'List', 'UniversalVocabularyMt', vStrDef).
 5535exactlyAssertedEL_first(arg1Isa, pointQuantValue, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5536exactlyAssertedEL_first(arg1Isa, pointQuantValue, 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 5537exactlyAssertedEL_first(arg1Isa, performSubL, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5538exactlyAssertedEL_first(arg1Isa, operatorFormulas, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5539exactlyAssertedEL_first(arg1Isa, operatorFormulas, tRelation, 'UniversalVocabularyMt', vStrDef).
 5540exactlyAssertedEL_first(arg1Isa, openEntryFormatInArgs, tPred, 'UniversalVocabularyMt', vStrDef).
 5541exactlyAssertedEL_first(arg1Isa, opaqueArgument, tRelation, 'UniversalVocabularyMt', vStrDef).
 5542exactlyAssertedEL_first(arg1Isa, omitArgIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5543exactlyAssertedEL_first(arg1Isa, oldConstantName, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5544exactlyAssertedEL_first(arg1Isa, oldConstantName, 'Thing', 'BookkeepingMt', vStrDef).
 5545exactlyAssertedEL_first(arg1Isa, numericallyEquals, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5546exactlyAssertedEL_first(arg1Isa, numericallyEquals, 'ScalarInterval', 'BaseKB', vStrDef).
 5547exactlyAssertedEL_first(arg1Isa, nthSmallestElement, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5548exactlyAssertedEL_first(arg1Isa, nthLargestElement, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5549exactlyAssertedEL_first(arg1Isa, notAssertibleMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5550exactlyAssertedEL_first(arg1Isa, notAssertibleCollection, tCol, 'UniversalVocabularyMt', vStrDef).
 5551exactlyAssertedEL_first(arg1Isa, notAssertible, tPred, 'UniversalVocabularyMt', vStrDef).
 5552exactlyAssertedEL_first(arg1Isa, nonAbducibleWithValueInArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5553exactlyAssertedEL_first(arg1Isa, negationPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 5554exactlyAssertedEL_first(arg1Isa, negationMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5555exactlyAssertedEL_first(arg1Isa, negationInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5556exactlyAssertedEL_first(arg1Isa, nearestIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5557exactlyAssertedEL_first(arg1Isa, nearestGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 5558exactlyAssertedEL_first(arg1Isa, nearestGenlPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 5559exactlyAssertedEL_first(arg1Isa, nearestGenlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5560exactlyAssertedEL_first(arg1Isa, nearestDifferentIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5561exactlyAssertedEL_first(arg1Isa, nearestDifferentGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 5562exactlyAssertedEL_first(arg1Isa, nearestCommonSpecs, tCol, 'UniversalVocabularyMt', vStrDef).
 5563exactlyAssertedEL_first(arg1Isa, nearestCommonIsa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5564exactlyAssertedEL_first(arg1Isa, nearestCommonGenls, tCol, 'UniversalVocabularyMt', vStrDef).
 5565exactlyAssertedEL_first(arg1Isa, nearestCommonGenlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5566exactlyAssertedEL_first(arg1Isa, natFunction, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5567exactlyAssertedEL_first(arg1Isa, natArgumentsEqual, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5568exactlyAssertedEL_first(arg1Isa, natArgument, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5569exactlyAssertedEL_first(arg1Isa, myCreator, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5570exactlyAssertedEL_first(arg1Isa, myCreator, 'Thing', 'BookkeepingMt', vStrDef).
 5571exactlyAssertedEL_first(arg1Isa, myCreationTime, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5572exactlyAssertedEL_first(arg1Isa, myCreationTime, 'Thing', 'BookkeepingMt', vStrDef).
 5573exactlyAssertedEL_first(arg1Isa, myCreationSecond, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5574exactlyAssertedEL_first(arg1Isa, myCreationSecond, 'Thing', 'BookkeepingMt', vStrDef).
 5575exactlyAssertedEL_first(arg1Isa, myCreationPurpose, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5576exactlyAssertedEL_first(arg1Isa, myCreationPurpose, 'Thing', 'BookkeepingMt', vStrDef).
 5577exactlyAssertedEL_first(arg1Isa, multiplicationUnits, 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5578exactlyAssertedEL_first(arg1Isa, mtVisible, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5579exactlyAssertedEL_first(arg1Isa, minQuantValue, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5580exactlyAssertedEL_first(arg1Isa, minimizeExtent, tPred, 'UniversalVocabularyMt', vStrDef).
 5581exactlyAssertedEL_first(arg1Isa, microtheoryDesignationArgnum, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', vStrDef).
 5582exactlyAssertedEL_first(arg1Isa, meetsPragmaticRequirement, 'List', 'UniversalVocabularyMt', vStrDef).
 5583exactlyAssertedEL_first(arg1Isa, means, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5584exactlyAssertedEL_first(arg1Isa, maxQuantValue, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5585exactlyAssertedEL_first(arg1Isa, ist, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5586exactlyAssertedEL_first(arg1Isa, isa, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5587exactlyAssertedEL_first(arg1Isa, isa, 'Thing', 'BaseKB', vStrDef).
 5588exactlyAssertedEL_first(arg1Isa, irrelevantTerm, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5589exactlyAssertedEL_first(arg1Isa, irrelevantPredAssertion, tPred, 'UniversalVocabularyMt', vStrDef).
 5590exactlyAssertedEL_first(arg1Isa, irrelevantMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5591exactlyAssertedEL_first(arg1Isa, interArgResultIsaReln, tFunction, 'UniversalVocabularyMt', vStrDef).
 5592exactlyAssertedEL_first(arg1Isa, interArgResultIsa, tFunction, 'UniversalVocabularyMt', vStrDef).
 5593exactlyAssertedEL_first(arg1Isa, interArgResultGenlReln, tFunction, 'UniversalVocabularyMt', vStrDef).
 5594exactlyAssertedEL_first(arg1Isa, interArgResultGenl, tFunction, 'UniversalVocabularyMt', vStrDef).
 5595exactlyAssertedEL_first(arg1Isa, interArgIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5596exactlyAssertedEL_first(arg1Isa, interArgDifferent, tRelation, 'UniversalVocabularyMt', vStrDef).
 5597exactlyAssertedEL_first(arg1Isa, integerBetween, 'Integer', 'UniversalVocabularyMt', vStrDef).
 5598exactlyAssertedEL_first(arg1Isa, instanceElementType, tCol, 'UniversalVocabularyMt', vStrDef).
 5599exactlyAssertedEL_first(arg1Isa, indexicalReferent, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5600exactlyAssertedEL_first(arg1Isa, independentArg, 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5601exactlyAssertedEL_first(arg1Isa, independentArg, 'ArgConstraintPredicate', 'UniversalVocabularyMt', vStrDef).
 5602exactlyAssertedEL_first(arg1Isa, hypotheticalTerm, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5603exactlyAssertedEL_first(arg1Isa, holdsIn, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5604exactlyAssertedEL_first(arg1Isa, hlPrototypicalInstance, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5605exactlyAssertedEL_first(arg1Isa, highlyRelevantTerm, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5606exactlyAssertedEL_first(arg1Isa, highlyRelevantPredAssertion, tPred, 'UniversalVocabularyMt', vStrDef).
 5607exactlyAssertedEL_first(arg1Isa, highlyRelevantMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5608exactlyAssertedEL_first(arg1Isa, greaterThanOrEqualTo, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5609exactlyAssertedEL_first(arg1Isa, greaterThanOrEqualTo, 'ScalarInterval', 'BaseKB', vStrDef).
 5610exactlyAssertedEL_first(arg1Isa, greaterThan, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5611exactlyAssertedEL_first(arg1Isa, greaterThan, 'ScalarInterval', 'BaseKB', vStrDef).
 5612exactlyAssertedEL_first(arg1Isa, genMassNoun, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5613exactlyAssertedEL_first(arg1Isa, genls, tCol, 'UniversalVocabularyMt', vStrDef).
 5614exactlyAssertedEL_first(arg1Isa, genls, tCol, 'BaseKB', vStrDef).
 5615exactlyAssertedEL_first(arg1Isa, genlPreds, tPred, 'UniversalVocabularyMt', vStrDef).
 5616exactlyAssertedEL_first(arg1Isa, genlPreds, tPred, 'BaseKB', vStrDef).
 5617exactlyAssertedEL_first(arg1Isa, genlMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5618exactlyAssertedEL_first(arg1Isa, genlMt, 'Microtheory', 'BaseKB', vStrDef).
 5619exactlyAssertedEL_first(arg1Isa, genlInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5620exactlyAssertedEL_first(arg1Isa, genlCanonicalizerDirectives, 'CanonicalizerDirective', 'UniversalVocabularyMt', vStrDef).
 5621exactlyAssertedEL_first(arg1Isa, genlCanonicalizerDirectives, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrDef).
 5622exactlyAssertedEL_first(arg1Isa, genKeyword, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5623exactlyAssertedEL_first(arg1Isa, genFormat, tRelation, 'UniversalVocabularyMt', vStrDef).
 5624exactlyAssertedEL_first(arg1Isa, formulaArity, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5625exactlyAssertedEL_first(arg1Isa, followingValue, 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5626exactlyAssertedEL_first(arg1Isa, fanOutArg, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5627exactlyAssertedEL_first(arg1Isa, extentCardinality, 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5628exactlyAssertedEL_first(arg1Isa, extConceptOverlapsColAndReln, tCol, 'UniversalVocabularyMt', vStrDef).
 5629exactlyAssertedEL_first(arg1Isa, expresses, 'CycLSentence', 'UniversalVocabularyMt', vStrDef).
 5630exactlyAssertedEL_first(arg1Isa, expansionDefn, tRelation, 'UniversalVocabularyMt', vStrDef).
 5631exactlyAssertedEL_first(arg1Isa, expansion, tRelation, 'UniversalVocabularyMt', vStrDef).
 5632exactlyAssertedEL_first(arg1Isa, exceptMt, 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5633exactlyAssertedEL_first(arg1Isa, exceptFor, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5634exactlyAssertedEL_first(arg1Isa, exampleAssertions, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5635exactlyAssertedEL_first(arg1Isa, evaluationResultQuotedIsa, 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 5636exactlyAssertedEL_first(arg1Isa, evaluationDefn, 'EvaluatableRelation', 'UniversalVocabularyMt', vStrDef).
 5637exactlyAssertedEL_first(arg1Isa, evaluateImmediately, 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 5638exactlyAssertedEL_first(arg1Isa, evaluateAtEL, 'EvaluatableFunction', 'UniversalVocabularyMt', vStrDef).
 5639exactlyAssertedEL_first(arg1Isa, evaluate, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5640exactlyAssertedEL_first(arg1Isa, equalSymbols, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5641exactlyAssertedEL_first(arg1Isa, equals, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5642exactlyAssertedEL_first(arg1Isa, ephemeralTerm, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5643exactlyAssertedEL_first(arg1Isa, elInverse, 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5644exactlyAssertedEL_first(arg1Isa, elementOf, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5645exactlyAssertedEL_first(arg1Isa, distributesOutOfArg, tRelation, 'UniversalVocabularyMt', vStrDef).
 5646exactlyAssertedEL_first(arg1Isa, disjointWith, tCol, 'UniversalVocabularyMt', vStrDef).
 5647exactlyAssertedEL_first(arg1Isa, different, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5648exactlyAssertedEL_first(arg1Isa, denotes, 'CycLDenotationalTerm', 'UniversalVocabularyMt', vStrDef).
 5649exactlyAssertedEL_first(arg1Isa, defnSufficient, tCol, 'UniversalVocabularyMt', vStrDef).
 5650exactlyAssertedEL_first(arg1Isa, defnNecessary, tCol, 'UniversalVocabularyMt', vStrDef).
 5651exactlyAssertedEL_first(arg1Isa, defnIff, tCol, 'UniversalVocabularyMt', vStrDef).
 5652exactlyAssertedEL_first(arg1Isa, definingMt, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5653exactlyAssertedEL_first(arg1Isa, defaultReformulatorModePrecedence, 'Individual', 'UniversalVocabularyMt', vStrDef).
 5654exactlyAssertedEL_first(arg1Isa, defaultReformulationDirectionInModeForPred, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5655exactlyAssertedEL_first(arg1Isa, decontextualizedPredicate, tPred, 'UniversalVocabularyMt', vStrDef).
 5656exactlyAssertedEL_first(arg1Isa, decontextualizedCollection, tCol, 'UniversalVocabularyMt', vStrDef).
 5657exactlyAssertedEL_first(arg1Isa, cycTransformationProofRule, 'CycTransformationProof', 'UniversalVocabularyMt', vStrDef).
 5658exactlyAssertedEL_first(arg1Isa, cycTransformationProofBindings, 'CycTransformationProof', 'UniversalVocabularyMt', vStrDef).
 5659exactlyAssertedEL_first(arg1Isa, cycTacticID, 'CycTactic', 'UniversalVocabularyMt', vStrDef).
 5660exactlyAssertedEL_first(arg1Isa, cycProofID, 'CycProof', 'UniversalVocabularyMt', vStrDef).
 5661exactlyAssertedEL_first(arg1Isa, cycProblemStoreTerms, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5662exactlyAssertedEL_first(arg1Isa, cycProblemStoreProofs, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5663exactlyAssertedEL_first(arg1Isa, cycProblemStoreProofCount, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5664exactlyAssertedEL_first(arg1Isa, cycProblemStoreProblems, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5665exactlyAssertedEL_first(arg1Isa, cycProblemStoreProblemCount, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5666exactlyAssertedEL_first(arg1Isa, cycProblemStoreLinks, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5667exactlyAssertedEL_first(arg1Isa, cycProblemStoreLinkCount, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5668exactlyAssertedEL_first(arg1Isa, cycProblemStoreInferences, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5669exactlyAssertedEL_first(arg1Isa, cycProblemStoreInferenceCount, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5670exactlyAssertedEL_first(arg1Isa, cycProblemStoreID, 'CycProblemStore', 'UniversalVocabularyMt', vStrDef).
 5671exactlyAssertedEL_first(arg1Isa, cycProblemQueryTerms, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5672exactlyAssertedEL_first(arg1Isa, cycProblemQuerySentence, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5673exactlyAssertedEL_first(arg1Isa, cycProblemProvabilityStatus, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5674exactlyAssertedEL_first(arg1Isa, cycProblemLinkID, 'CycProblemLink', 'UniversalVocabularyMt', vStrDef).
 5675exactlyAssertedEL_first(arg1Isa, cycProblemID, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5676exactlyAssertedEL_first(arg1Isa, cycProblemDependentLinks, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5677exactlyAssertedEL_first(arg1Isa, cycProblemArgumentLinks, 'CycProblem', 'UniversalVocabularyMt', vStrDef).
 5678exactlyAssertedEL_first(arg1Isa, cycInferenceRelevantProblems, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 5679exactlyAssertedEL_first(arg1Isa, cycInferenceAnswerLink, 'CycInference', 'UniversalVocabularyMt', vStrDef).
 5680exactlyAssertedEL_first(arg1Isa, constrainsArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5681exactlyAssertedEL_first(arg1Isa, constantName, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5682exactlyAssertedEL_first(arg1Isa, constantID, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5683exactlyAssertedEL_first(arg1Isa, constantGUID, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5684exactlyAssertedEL_first(arg1Isa, conceptuallyRelated, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5685exactlyAssertedEL_first(arg1Isa, completelyEnumerableCollection, tCol, 'UniversalVocabularyMt', vStrDef).
 5686exactlyAssertedEL_first(arg1Isa, completelyDecidableCollection, tCol, 'UniversalVocabularyMt', vStrDef).
 5687exactlyAssertedEL_first(arg1Isa, completelyDecidableCollection, tCol, 'CoreCycLMt', vStrDef).
 5688exactlyAssertedEL_first(arg1Isa, completeExtentEnumerableViaBackchain, tPred, 'UniversalVocabularyMt', vStrDef).
 5689exactlyAssertedEL_first(arg1Isa, completeExtentEnumerableForValueInArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5690exactlyAssertedEL_first(arg1Isa, completeExtentEnumerableForArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5691exactlyAssertedEL_first(arg1Isa, completeExtentEnumerableForArg, tPred, 'CoreCycLMt', vStrDef).
 5692exactlyAssertedEL_first(arg1Isa, completeExtentEnumerable, tPred, 'UniversalVocabularyMt', vStrDef).
 5693exactlyAssertedEL_first(arg1Isa, completeExtentDecidableForValueInArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5694exactlyAssertedEL_first(arg1Isa, completeExtentDecidableForValueInArg, tPred, 'CoreCycLMt', vStrDef).
 5695exactlyAssertedEL_first(arg1Isa, completeExtentDecidable, tPred, 'UniversalVocabularyMt', vStrDef).
 5696exactlyAssertedEL_first(arg1Isa, completeExtentDecidable, tPred, 'CoreCycLMt', vStrDef).
 5697exactlyAssertedEL_first(arg1Isa, completeExtentAssertedForValueInArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5698exactlyAssertedEL_first(arg1Isa, completeExtentAssertedForValueInArg, tPred, 'CoreCycLMt', vStrDef).
 5699exactlyAssertedEL_first(arg1Isa, completeExtentAsserted, tPred, 'UniversalVocabularyMt', vStrDef).
 5700exactlyAssertedEL_first(arg1Isa, completeExtentAsserted, tPred, 'CoreCycLMt', vStrDef).
 5701exactlyAssertedEL_first(arg1Isa, commutativeInArgsAndRest, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrDef).
 5702exactlyAssertedEL_first(arg1Isa, commutativeInArgs, tRelation, 'UniversalVocabularyMt', vStrDef).
 5703exactlyAssertedEL_first(arg1Isa, comment, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5704exactlyAssertedEL_first(arg1Isa, collectionIsaBackchainRequired, tCol, 'UniversalVocabularyMt', vStrDef).
 5705exactlyAssertedEL_first(arg1Isa, collectionIsaBackchainEncouraged, tCol, 'UniversalVocabularyMt', vStrDef).
 5706exactlyAssertedEL_first(arg1Isa, collectionGenlsBackchainRequired, tCol, 'UniversalVocabularyMt', vStrDef).
 5707exactlyAssertedEL_first(arg1Isa, collectionGenlsBackchainEncouraged, tCol, 'UniversalVocabularyMt', vStrDef).
 5708exactlyAssertedEL_first(arg1Isa, collectionExpansion, tCol, 'UniversalVocabularyMt', vStrDef).
 5709exactlyAssertedEL_first(arg1Isa, collectionConventionMt, tCol, 'UniversalVocabularyMt', vStrDef).
 5710exactlyAssertedEL_first(arg1Isa, collectionCompletelyEnumerableViaBackchain, tCol, 'UniversalVocabularyMt', vStrDef).
 5711exactlyAssertedEL_first(arg1Isa, collectionBackchainRequired, tCol, 'UniversalVocabularyMt', vStrDef).
 5712exactlyAssertedEL_first(arg1Isa, collectionBackchainEncouraged, tCol, 'UniversalVocabularyMt', vStrDef).
 5713exactlyAssertedEL_first(arg1Isa, coExtensional, tCol, 'UniversalVocabularyMt', vStrDef).
 5714exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForArgAndRest, tRelation, 'UniversalVocabularyMt', vStrDef).
 5715exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForArgAndRest, tRelation, 'CoreCycLImplementationMt', vStrDef).
 5716exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForArg, tRelation, 'UniversalVocabularyMt', vStrDef).
 5717exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForArg, tRelation, 'CoreCycLImplementationMt', vStrDef).
 5718exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForAllArgs, tRelation, 'UniversalVocabularyMt', vStrDef).
 5719exactlyAssertedEL_first(arg1Isa, canonicalizerDirectiveForAllArgs, tRelation, 'CoreCycLImplementationMt', vStrDef).
 5720exactlyAssertedEL_first(arg1Isa, backchainRequired, tPred, 'UniversalVocabularyMt', vStrDef).
 5721exactlyAssertedEL_first(arg1Isa, backchainForbiddenWhenUnboundInArg, tPred, 'UniversalVocabularyMt', vStrDef).
 5722exactlyAssertedEL_first(arg1Isa, backchainForbidden, tPred, 'UniversalVocabularyMt', vStrDef).
 5723exactlyAssertedEL_first(arg1Isa, assertedTermSentences, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5724exactlyAssertedEL_first(arg1Isa, assertedPredicateArg, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5725exactlyAssertedEL_first(arg1Isa, arityMin, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 5726exactlyAssertedEL_first(arg1Isa, arityMax, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 5727exactlyAssertedEL_first(arg1Isa, arity, 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 5728exactlyAssertedEL_first(arg1Isa, argsQuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5729exactlyAssertedEL_first(arg1Isa, argSometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5730exactlyAssertedEL_first(arg1Isa, argsIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5731exactlyAssertedEL_first(arg1Isa, argsGenl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5732exactlyAssertedEL_first(arg1Isa, argQuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5733exactlyAssertedEL_first(arg1Isa, argIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5734exactlyAssertedEL_first(arg1Isa, argAndRestQuotedIsa, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 5735exactlyAssertedEL_first(arg1Isa, argAndRestIsa, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 5736exactlyAssertedEL_first(arg1Isa, argAndRestIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5737exactlyAssertedEL_first(arg1Isa, argAndRestGenl, 'VariableArityRelation', 'UniversalVocabularyMt', vStrDef).
 5738exactlyAssertedEL_first(arg1Isa, arg6SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5739exactlyAssertedEL_first(arg1Isa, arg6QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5740exactlyAssertedEL_first(arg1Isa, arg6Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5741exactlyAssertedEL_first(arg1Isa, arg6Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5742exactlyAssertedEL_first(arg1Isa, arg6Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5743exactlyAssertedEL_first(arg1Isa, arg5SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5744exactlyAssertedEL_first(arg1Isa, arg5QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5745exactlyAssertedEL_first(arg1Isa, arg5Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5746exactlyAssertedEL_first(arg1Isa, arg5Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5747exactlyAssertedEL_first(arg1Isa, arg5Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5748exactlyAssertedEL_first(arg1Isa, arg4SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5749exactlyAssertedEL_first(arg1Isa, arg4QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5750exactlyAssertedEL_first(arg1Isa, arg4Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5751exactlyAssertedEL_first(arg1Isa, arg4Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5752exactlyAssertedEL_first(arg1Isa, arg4Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5753exactlyAssertedEL_first(arg1Isa, arg3SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5754exactlyAssertedEL_first(arg1Isa, arg3QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5755exactlyAssertedEL_first(arg1Isa, arg3Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5756exactlyAssertedEL_first(arg1Isa, arg3Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5757exactlyAssertedEL_first(arg1Isa, arg3Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5758exactlyAssertedEL_first(arg1Isa, arg2SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5759exactlyAssertedEL_first(arg1Isa, arg2QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5760exactlyAssertedEL_first(arg1Isa, arg2Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5761exactlyAssertedEL_first(arg1Isa, arg2Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5762exactlyAssertedEL_first(arg1Isa, arg2Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5763exactlyAssertedEL_first(arg1Isa, arg1SometimesIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5764exactlyAssertedEL_first(arg1Isa, arg1QuotedIsa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5765exactlyAssertedEL_first(arg1Isa, arg1Isa, tRelation, 'UniversalVocabularyMt', vStrDef).
 5766exactlyAssertedEL_first(arg1Isa, arg1Genl, tRelation, 'UniversalVocabularyMt', vStrDef).
 5767exactlyAssertedEL_first(arg1Isa, arg1Format, tPred, 'UniversalVocabularyMt', vStrDef).
 5768exactlyAssertedEL_first(arg1Isa, afterRemoving, tPred, 'UniversalVocabularyMt', vStrDef).
 5769exactlyAssertedEL_first(arg1Isa, afterAdding, tPred, 'UniversalVocabularyMt', vStrDef).
 5770exactlyAssertedEL_first(arg1Isa, admittedNAT, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5771exactlyAssertedEL_first(arg1Isa, admittedArgument, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5772exactlyAssertedEL_first(arg1Isa, admittedAllArgument, tCol, 'UniversalVocabularyMt', vStrDef).
 5773exactlyAssertedEL_first(arg1Isa, abnormal, 'List', 'UniversalVocabularyMt', vStrDef).
 5774exactlyAssertedEL_first(arg1Isa, 'Unity', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5775exactlyAssertedEL_first(arg1Isa, 'UnitProductFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5776exactlyAssertedEL_first(arg1Isa, 'UncanonicalizerAssertionFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5777exactlyAssertedEL_first(arg1Isa, 'TLVariableFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5778exactlyAssertedEL_first(arg1Isa, 'TLReifiedNatFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5779exactlyAssertedEL_first(arg1Isa, 'TLAssertionFn', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5780exactlyAssertedEL_first(arg1Isa, 'TimesFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5781exactlyAssertedEL_first(arg1Isa, 'TheSet', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5782exactlyAssertedEL_first(arg1Isa, 'TheList', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5783exactlyAssertedEL_first(arg1Isa, 'substring-CaseInsensitive', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5784exactlyAssertedEL_first(arg1Isa, 'RoundUpFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5785exactlyAssertedEL_first(arg1Isa, 'RoundDownFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5786exactlyAssertedEL_first(arg1Isa, 'RoundClosestFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5787exactlyAssertedEL_first(arg1Isa, 'RelationInstanceExistsFn', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5788exactlyAssertedEL_first(arg1Isa, 'RelationExistsInstanceFn', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 5789exactlyAssertedEL_first(arg1Isa, 'RelationExistsAllFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5790exactlyAssertedEL_first(arg1Isa, 'RelationAllExistsFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5791exactlyAssertedEL_first(arg1Isa, 'QuotientFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5792exactlyAssertedEL_first(arg1Isa, 'Quote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5793exactlyAssertedEL_first(arg1Isa, 'QuasiQuote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5794exactlyAssertedEL_first(arg1Isa, 'QuantityConversionFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5795exactlyAssertedEL_first(arg1Isa, 'prettyString-Canonical', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5796exactlyAssertedEL_first(arg1Isa, 'PlusFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5797exactlyAssertedEL_first(arg1Isa, 'PlusAll', 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5798exactlyAssertedEL_first(arg1Isa, 'PlusAll', 'SetOrCollection', 'BaseKB', vStrDef).
 5799exactlyAssertedEL_first(arg1Isa, 'PerFn', 'UnitOfMeasure', 'UniversalVocabularyMt', vStrDef).
 5800exactlyAssertedEL_first(arg1Isa, 'Percent', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5801exactlyAssertedEL_first(arg1Isa, 'MtUnionFn', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5802exactlyAssertedEL_first(arg1Isa, 'MtTimeWithGranularityDimFn', 'Individual', 'UniversalVocabularyMt', vStrDef).
 5803exactlyAssertedEL_first(arg1Isa, 'MtTimeDimFn', 'Individual', 'UniversalVocabularyMt', vStrDef).
 5804exactlyAssertedEL_first(arg1Isa, 'MtSpace', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5805exactlyAssertedEL_first(arg1Isa, 'ModuloFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5806exactlyAssertedEL_first(arg1Isa, 'MinRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5807exactlyAssertedEL_first(arg1Isa, 'Minimum', 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5808exactlyAssertedEL_first(arg1Isa, 'Minimum', 'SetOrCollection', 'BaseKB', vStrDef).
 5809exactlyAssertedEL_first(arg1Isa, 'MeaningInSystemFn', 'Individual', 'UniversalVocabularyMt', vStrDef).
 5810exactlyAssertedEL_first(arg1Isa, 'MaxRangeFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5811exactlyAssertedEL_first(arg1Isa, 'Maximum', 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5812exactlyAssertedEL_first(arg1Isa, 'Maximum', 'SetOrCollection', 'BaseKB', vStrDef).
 5813exactlyAssertedEL_first(arg1Isa, 'LogFn', 'RealNumber', 'UniversalVocabularyMt', vStrDef).
 5814exactlyAssertedEL_first(arg1Isa, 'LogFn', 'NonNegativeScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5815exactlyAssertedEL_first(arg1Isa, 'larkc-hasUri', 'larkc-Plugin', 'BaseKB', vStrDef).
 5816exactlyAssertedEL_first(arg1Isa, 'larkc-hasScalability', 'larkc-Scalability', 'BaseKB', vStrDef).
 5817exactlyAssertedEL_first(arg1Isa, 'larkc-hasEndpoint', 'larkc-Plugin', 'BaseKB', vStrDef).
 5818exactlyAssertedEL_first(arg1Isa, 'larkc-hasCostPerInvocation', 'larkc-Cost', 'BaseKB', vStrDef).
 5819exactlyAssertedEL_first(arg1Isa, 'ist-Asserted', 'Microtheory', 'UniversalVocabularyMt', vStrDef).
 5820exactlyAssertedEL_first(arg1Isa, 'IntervalMinFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5821exactlyAssertedEL_first(arg1Isa, 'IntervalMaxFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5822exactlyAssertedEL_first(arg1Isa, 'interArgIsa5-4', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 5823exactlyAssertedEL_first(arg1Isa, 'interArgIsa5-3', tRelation, 'UniversalVocabularyMt', vStrDef).
 5824exactlyAssertedEL_first(arg1Isa, 'interArgIsa5-3', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 5825exactlyAssertedEL_first(arg1Isa, 'interArgIsa5-2', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 5826exactlyAssertedEL_first(arg1Isa, 'interArgIsa5-1', 'QuintaryRelation', 'UniversalVocabularyMt', vStrDef).
 5827exactlyAssertedEL_first(arg1Isa, 'interArgIsa4-5', tRelation, 'UniversalVocabularyMt', vStrDef).
 5828exactlyAssertedEL_first(arg1Isa, 'interArgIsa4-3', tRelation, 'UniversalVocabularyMt', vStrDef).
 5829exactlyAssertedEL_first(arg1Isa, 'interArgIsa4-2', tRelation, 'UniversalVocabularyMt', vStrDef).
 5830exactlyAssertedEL_first(arg1Isa, 'interArgIsa4-1', tRelation, 'UniversalVocabularyMt', vStrDef).
 5831exactlyAssertedEL_first(arg1Isa, 'interArgIsa3-5', tRelation, 'UniversalVocabularyMt', vStrDef).
 5832exactlyAssertedEL_first(arg1Isa, 'interArgIsa3-4', tRelation, 'UniversalVocabularyMt', vStrDef).
 5833exactlyAssertedEL_first(arg1Isa, 'interArgIsa3-2', tRelation, 'UniversalVocabularyMt', vStrDef).
 5834exactlyAssertedEL_first(arg1Isa, 'interArgIsa3-1', tRelation, 'UniversalVocabularyMt', vStrDef).
 5835exactlyAssertedEL_first(arg1Isa, 'interArgIsa2-5', tRelation, 'UniversalVocabularyMt', vStrDef).
 5836exactlyAssertedEL_first(arg1Isa, 'interArgIsa2-4', tRelation, 'UniversalVocabularyMt', vStrDef).
 5837exactlyAssertedEL_first(arg1Isa, 'interArgIsa2-3', tRelation, 'UniversalVocabularyMt', vStrDef).
 5838exactlyAssertedEL_first(arg1Isa, 'interArgIsa2-1', tRelation, 'UniversalVocabularyMt', vStrDef).
 5839exactlyAssertedEL_first(arg1Isa, 'interArgIsa1-5', tRelation, 'UniversalVocabularyMt', vStrDef).
 5840exactlyAssertedEL_first(arg1Isa, 'interArgIsa1-4', tRelation, 'UniversalVocabularyMt', vStrDef).
 5841exactlyAssertedEL_first(arg1Isa, 'interArgIsa1-3', tRelation, 'UniversalVocabularyMt', vStrDef).
 5842exactlyAssertedEL_first(arg1Isa, 'interArgIsa1-2', tRelation, 'UniversalVocabularyMt', vStrDef).
 5843exactlyAssertedEL_first(arg1Isa, 'interArgGenl1-2', tRelation, 'UniversalVocabularyMt', vStrDef).
 5844exactlyAssertedEL_first(arg1Isa, 'interArgFormat1-2', tPred, 'UniversalVocabularyMt', vStrDef).
 5845exactlyAssertedEL_first(arg1Isa, 'genls-SpecDenotesGenlInstances', 'SubLExpressionType', 'UniversalVocabularyMt', vStrDef).
 5846exactlyAssertedEL_first(arg1Isa, 'genls-GenlDenotesSpecInstances', tCol, 'UniversalVocabularyMt', vStrDef).
 5847exactlyAssertedEL_first(arg1Isa, 'FunctionToArg', 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 5848exactlyAssertedEL_first(arg1Isa, 'FormulaArityFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5849exactlyAssertedEL_first(arg1Isa, 'FormulaArgSetFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5850exactlyAssertedEL_first(arg1Isa, 'FormulaArgListFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5851exactlyAssertedEL_first(arg1Isa, 'FormulaArgFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5852exactlyAssertedEL_first(arg1Isa, 'FOL-TermFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5853exactlyAssertedEL_first(arg1Isa, 'FOL-PredicateFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5854exactlyAssertedEL_first(arg1Isa, 'FOL-FunctionFn', tFunction, 'UniversalVocabularyMt', vStrDef).
 5855exactlyAssertedEL_first(arg1Isa, 'ExpFn', 'ScalarPointValue', 'UniversalVocabularyMt', vStrDef).
 5856exactlyAssertedEL_first(arg1Isa, 'EvaluateSubLFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5857exactlyAssertedEL_first(arg1Isa, 'EscapeQuote', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5858exactlyAssertedEL_first(arg1Isa, 'equalStrings-CaseInsensitive', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5859exactlyAssertedEL_first(arg1Isa, 'DifferenceFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5860exactlyAssertedEL_first(arg1Isa, 'DateEncodeStringFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5861exactlyAssertedEL_first(arg1Isa, 'DateDecodeStringFn', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 5862exactlyAssertedEL_first(arg1Isa, 'CycTacticFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5863exactlyAssertedEL_first(arg1Isa, 'CycProofFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5864exactlyAssertedEL_first(arg1Isa, 'CycProblemStoreFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5865exactlyAssertedEL_first(arg1Isa, 'CycProblemLinkFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5866exactlyAssertedEL_first(arg1Isa, 'CycProblemFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5867exactlyAssertedEL_first(arg1Isa, 'CycInferenceFn', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 5868exactlyAssertedEL_first(arg1Isa, 'CollectionRuleTemplateFn', tCol, 'UniversalVocabularyMt', vStrDef).
 5869exactlyAssertedEL_first(arg1Isa, 'Average', 'SetOrCollection', 'UniversalVocabularyMt', vStrDef).
 5870exactlyAssertedEL_first(arg1Isa, 'Average', 'SetOrCollection', 'BaseKB', vStrDef).
 5871exactlyAssertedEL_first(arg1Isa, 'AbsoluteValueFn', 'ScalarInterval', 'UniversalVocabularyMt', vStrDef).
 5872exactlyAssertedEL_first(arg1Genl, siblingDisjointExceptions, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5873exactlyAssertedEL_first(arg1Genl, requiredArg3Pred, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5874exactlyAssertedEL_first(arg1Genl, requiredArg2Pred, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5875exactlyAssertedEL_first(arg1Genl, requiredArg1Pred, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5876exactlyAssertedEL_first(arg1Genl, quotedDefnSufficient, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5877exactlyAssertedEL_first(arg1Genl, quotedDefnNecessary, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5878exactlyAssertedEL_first(arg1Genl, quotedDefnIff, 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5879exactlyAssertedEL_first(arg1Genl, notAssertibleCollection, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5880exactlyAssertedEL_first(arg1Genl, nearestGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5881exactlyAssertedEL_first(arg1Genl, nearestDifferentGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5882exactlyAssertedEL_first(arg1Genl, nearestCommonSpecs, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5883exactlyAssertedEL_first(arg1Genl, nearestCommonGenls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5884exactlyAssertedEL_first(arg1Genl, instanceElementType, 'Set-Mathematical', 'UniversalVocabularyMt', vStrDef).
 5885exactlyAssertedEL_first(arg1Genl, genls, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5886exactlyAssertedEL_first(arg1Genl, extConceptOverlapsColAndReln, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5887exactlyAssertedEL_first(arg1Genl, disjointWith, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5888exactlyAssertedEL_first(arg1Genl, defnSufficient, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5889exactlyAssertedEL_first(arg1Genl, defnNecessary, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5890exactlyAssertedEL_first(arg1Genl, defnIff, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5891exactlyAssertedEL_first(arg1Genl, decontextualizedCollection, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5892exactlyAssertedEL_first(arg1Genl, completelyEnumerableCollection, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5893exactlyAssertedEL_first(arg1Genl, completelyDecidableCollection, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5894exactlyAssertedEL_first(arg1Genl, collectionIsaBackchainRequired, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5895exactlyAssertedEL_first(arg1Genl, collectionIsaBackchainEncouraged, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5896exactlyAssertedEL_first(arg1Genl, collectionGenlsBackchainRequired, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5897exactlyAssertedEL_first(arg1Genl, collectionGenlsBackchainEncouraged, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5898exactlyAssertedEL_first(arg1Genl, collectionConventionMt, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5899exactlyAssertedEL_first(arg1Genl, collectionCompletelyEnumerableViaBackchain, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5900exactlyAssertedEL_first(arg1Genl, collectionBackchainRequired, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5901exactlyAssertedEL_first(arg1Genl, collectionBackchainEncouraged, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5902exactlyAssertedEL_first(arg1Genl, coExtensional, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5903exactlyAssertedEL_first(arg1Genl, admittedAllArgument, 'Thing', 'UniversalVocabularyMt', vStrDef).
 5904exactlyAssertedEL_first(arg1Genl, 'larkc-pluginByDataConnectsTo', 'larkc-Plugin', 'BaseKB', vStrDef).
 5905exactlyAssertedEL_first(arg1Genl, 'larkc-hasOutputType', 'larkc-Plugin', 'BaseKB', vStrDef).
 5906exactlyAssertedEL_first(arg1Genl, 'larkc-hasInputType', 'larkc-Plugin', 'BaseKB', vStrDef).
 5907exactlyAssertedEL_first(arg1Genl, 'genls-SpecDenotesGenlInstances', 'SubLSExpression', 'UniversalVocabularyMt', vStrDef).
 5908exactlyAssertedEL_first(arg1Genl, 'CollectionRuleTemplateFn', 'Thing', 'UniversalVocabularyMt', vStrDef).
 5909exactlyAssertedEL_first(arg1Format, unitMultiplicationFactor, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5910exactlyAssertedEL_first(arg1Format, transitiveViaArgInverse, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5911exactlyAssertedEL_first(arg1Format, transitiveViaArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5912exactlyAssertedEL_first(arg1Format, termOfUnit, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5913exactlyAssertedEL_first(arg1Format, termOfUnit, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5914exactlyAssertedEL_first(arg1Format, termExternalIDString, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5915exactlyAssertedEL_first(arg1Format, synonymousExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5916exactlyAssertedEL_first(arg1Format, sharedNotes, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5917exactlyAssertedEL_first(arg1Format, salientAssertions, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5918exactlyAssertedEL_first(arg1Format, rewriteOf, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5919exactlyAssertedEL_first(arg1Format, resultQuotedIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5920exactlyAssertedEL_first(arg1Format, resultIsaArgIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5921exactlyAssertedEL_first(arg1Format, resultIsaArg, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5922exactlyAssertedEL_first(arg1Format, resultIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5923exactlyAssertedEL_first(arg1Format, resultGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5924exactlyAssertedEL_first(arg1Format, requiredArg2Pred, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5925exactlyAssertedEL_first(arg1Format, requiredArg1Pred, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5926exactlyAssertedEL_first(arg1Format, relationInstanceExists, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5927exactlyAssertedEL_first(arg1Format, relationInstanceAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5928exactlyAssertedEL_first(arg1Format, relationExistsMinAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5929exactlyAssertedEL_first(arg1Format, relationExistsMaxAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5930exactlyAssertedEL_first(arg1Format, relationExistsInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5931exactlyAssertedEL_first(arg1Format, relationExistsCountAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5932exactlyAssertedEL_first(arg1Format, relationExistsAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5933exactlyAssertedEL_first(arg1Format, relationAllInstance, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5934exactlyAssertedEL_first(arg1Format, relationAllExistsMin, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5935exactlyAssertedEL_first(arg1Format, relationAllExistsMax, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5936exactlyAssertedEL_first(arg1Format, relationAllExistsCount, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5937exactlyAssertedEL_first(arg1Format, relationAllExists, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5938exactlyAssertedEL_first(arg1Format, relationAll, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5939exactlyAssertedEL_first(arg1Format, quotedIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5940exactlyAssertedEL_first(arg1Format, prettyString, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5941exactlyAssertedEL_first(arg1Format, preservesGenlsInArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5942exactlyAssertedEL_first(arg1Format, pointQuantValue, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5943exactlyAssertedEL_first(arg1Format, overlappingExternalConcept, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5944exactlyAssertedEL_first(arg1Format, operatorFormulas, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5945exactlyAssertedEL_first(arg1Format, opaqueArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5946exactlyAssertedEL_first(arg1Format, numericallyEquals, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5947exactlyAssertedEL_first(arg1Format, nthSmallestElement, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5948exactlyAssertedEL_first(arg1Format, negationPreds, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5949exactlyAssertedEL_first(arg1Format, negationInverse, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5950exactlyAssertedEL_first(arg1Format, natFunction, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5951exactlyAssertedEL_first(arg1Format, natArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5952exactlyAssertedEL_first(arg1Format, myCreationTime, 'SetTheFormat', 'BookkeepingMt', vStrMon).
 5953exactlyAssertedEL_first(arg1Format, myCreationPurpose, openEntryFormatInArgs, 'BookkeepingMt', vStrDef).
 5954exactlyAssertedEL_first(arg1Format, multiplicationUnits, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5955exactlyAssertedEL_first(arg1Format, minQuantValue, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5956exactlyAssertedEL_first(arg1Format, minimizeExtent, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5957exactlyAssertedEL_first(arg1Format, means, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5958exactlyAssertedEL_first(arg1Format, maxQuantValue, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5959exactlyAssertedEL_first(arg1Format, isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5960exactlyAssertedEL_first(arg1Format, interArgResultIsaReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5961exactlyAssertedEL_first(arg1Format, interArgResultIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5962exactlyAssertedEL_first(arg1Format, interArgResultGenlReln, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5963exactlyAssertedEL_first(arg1Format, interArgResultGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5964exactlyAssertedEL_first(arg1Format, interArgIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5965exactlyAssertedEL_first(arg1Format, interArgDifferent, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5966exactlyAssertedEL_first(arg1Format, integerBetween, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5967exactlyAssertedEL_first(arg1Format, independentArg, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5968exactlyAssertedEL_first(arg1Format, greaterThanOrEqualTo, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5969exactlyAssertedEL_first(arg1Format, greaterThan, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5970exactlyAssertedEL_first(arg1Format, genls, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5971exactlyAssertedEL_first(arg1Format, genlMt, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5972exactlyAssertedEL_first(arg1Format, genKeyword, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5973exactlyAssertedEL_first(arg1Format, followingValue, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5974exactlyAssertedEL_first(arg1Format, fanOutArg, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5975exactlyAssertedEL_first(arg1Format, expresses, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5976exactlyAssertedEL_first(arg1Format, evaluationResultQuotedIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5977exactlyAssertedEL_first(arg1Format, evaluationDefn, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5978exactlyAssertedEL_first(arg1Format, elInverse, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5979exactlyAssertedEL_first(arg1Format, elementOf, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5980exactlyAssertedEL_first(arg1Format, disjointWith, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5981exactlyAssertedEL_first(arg1Format, different, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5982exactlyAssertedEL_first(arg1Format, denotes, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5983exactlyAssertedEL_first(arg1Format, defnSufficient, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5984exactlyAssertedEL_first(arg1Format, defaultReformulationDirectionInModeForPred, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5985exactlyAssertedEL_first(arg1Format, cycInferenceAnswerLink, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5986exactlyAssertedEL_first(arg1Format, constrainsArg, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5987exactlyAssertedEL_first(arg1Format, constantName, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5988exactlyAssertedEL_first(arg1Format, constantID, 'SingleEntry', 'UniversalVocabularyMt', vStrDef).
 5989exactlyAssertedEL_first(arg1Format, constantGUID, singleEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 5990exactlyAssertedEL_first(arg1Format, conceptuallyRelated, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5991exactlyAssertedEL_first(arg1Format, completelyEnumerableCollection, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5992exactlyAssertedEL_first(arg1Format, completelyDecidableCollection, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5993exactlyAssertedEL_first(arg1Format, completeExtentEnumerable, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5994exactlyAssertedEL_first(arg1Format, completeExtentDecidable, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5995exactlyAssertedEL_first(arg1Format, completeExtentAsserted, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5996exactlyAssertedEL_first(arg1Format, commutativeInArgsAndRest, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 5997exactlyAssertedEL_first(arg1Format, comment, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5998exactlyAssertedEL_first(arg1Format, arityMin, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 5999exactlyAssertedEL_first(arg1Format, arityMax, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6000exactlyAssertedEL_first(arg1Format, arity, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6001exactlyAssertedEL_first(arg1Format, argSometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6002exactlyAssertedEL_first(arg1Format, argsIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6003exactlyAssertedEL_first(arg1Format, argsGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6004exactlyAssertedEL_first(arg1Format, argIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6005exactlyAssertedEL_first(arg1Format, argAndRestIsa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6006exactlyAssertedEL_first(arg1Format, argAndRestGenl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6007exactlyAssertedEL_first(arg1Format, arg6SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6008exactlyAssertedEL_first(arg1Format, arg6Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6009exactlyAssertedEL_first(arg1Format, arg6Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6010exactlyAssertedEL_first(arg1Format, arg6Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6011exactlyAssertedEL_first(arg1Format, arg5SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6012exactlyAssertedEL_first(arg1Format, arg5Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6013exactlyAssertedEL_first(arg1Format, arg5Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6014exactlyAssertedEL_first(arg1Format, arg5Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6015exactlyAssertedEL_first(arg1Format, arg4SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6016exactlyAssertedEL_first(arg1Format, arg4Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6017exactlyAssertedEL_first(arg1Format, arg4Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6018exactlyAssertedEL_first(arg1Format, arg4Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6019exactlyAssertedEL_first(arg1Format, arg3SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6020exactlyAssertedEL_first(arg1Format, arg3Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6021exactlyAssertedEL_first(arg1Format, arg3Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6022exactlyAssertedEL_first(arg1Format, arg3Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6023exactlyAssertedEL_first(arg1Format, arg2SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6024exactlyAssertedEL_first(arg1Format, arg2Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6025exactlyAssertedEL_first(arg1Format, arg2Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6026exactlyAssertedEL_first(arg1Format, arg2Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6027exactlyAssertedEL_first(arg1Format, arg1SometimesIsa, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6028exactlyAssertedEL_first(arg1Format, arg1Isa, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6029exactlyAssertedEL_first(arg1Format, arg1Genl, 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6030exactlyAssertedEL_first(arg1Format, arg1Format, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6031exactlyAssertedEL_first(arg1Format, admittedArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrMon).
 6032exactlyAssertedEL_first(arg1Format, admittedAllArgument, openEntryFormatInArgs, 'UniversalVocabularyMt', vStrDef).
 6033exactlyAssertedEL_first(arg1Format, 'prettyString-Canonical', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6034exactlyAssertedEL_first(arg1Format, 'interArgIsa5-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6035exactlyAssertedEL_first(arg1Format, 'interArgIsa5-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6036exactlyAssertedEL_first(arg1Format, 'interArgIsa5-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6037exactlyAssertedEL_first(arg1Format, 'interArgIsa5-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6038exactlyAssertedEL_first(arg1Format, 'interArgIsa4-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6039exactlyAssertedEL_first(arg1Format, 'interArgIsa4-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6040exactlyAssertedEL_first(arg1Format, 'interArgIsa4-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6041exactlyAssertedEL_first(arg1Format, 'interArgIsa4-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6042exactlyAssertedEL_first(arg1Format, 'interArgIsa3-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6043exactlyAssertedEL_first(arg1Format, 'interArgIsa3-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6044exactlyAssertedEL_first(arg1Format, 'interArgIsa3-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6045exactlyAssertedEL_first(arg1Format, 'interArgIsa3-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6046exactlyAssertedEL_first(arg1Format, 'interArgIsa2-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6047exactlyAssertedEL_first(arg1Format, 'interArgIsa2-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6048exactlyAssertedEL_first(arg1Format, 'interArgIsa2-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6049exactlyAssertedEL_first(arg1Format, 'interArgIsa2-1', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6050exactlyAssertedEL_first(arg1Format, 'interArgIsa1-5', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6051exactlyAssertedEL_first(arg1Format, 'interArgIsa1-4', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6052exactlyAssertedEL_first(arg1Format, 'interArgIsa1-3', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6053exactlyAssertedEL_first(arg1Format, 'interArgIsa1-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6054exactlyAssertedEL_first(arg1Format, 'interArgFormat1-2', 'SetTheFormat', 'UniversalVocabularyMt', vStrDef).
 6055
 6056exactlyAssertedEL_next(singleEntryFormatInArgs, unitMultiplicationFactor, 3, 'UniversalVocabularyMt', vStrMon).
 6057exactlyAssertedEL_next(singleEntryFormatInArgs, unitMultiplicationFactor, 2, 'UniversalVocabularyMt', vStrDef).
 6058exactlyAssertedEL_next(singleEntryFormatInArgs, unitMultiplicationFactor, 1, 'UniversalVocabularyMt', vStrDef).
 6059exactlyAssertedEL_next(singleEntryFormatInArgs, sentenceTruth, 2, 'UniversalVocabularyMt', vStrMon).
 6060exactlyAssertedEL_next(singleEntryFormatInArgs, rewriteOf, 1, 'UniversalVocabularyMt', vStrDef).
 6061exactlyAssertedEL_next(singleEntryFormatInArgs, pointQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 6062exactlyAssertedEL_next(singleEntryFormatInArgs, operatorFormulas, 1, 'UniversalVocabularyMt', vStrMon).
 6063exactlyAssertedEL_next(singleEntryFormatInArgs, myCreationPurpose, 2, 'BookkeepingMt', vStrDef).
 6064exactlyAssertedEL_next(singleEntryFormatInArgs, multiplicationUnits, 3, 'UniversalVocabularyMt', vStrMon).
 6065exactlyAssertedEL_next(singleEntryFormatInArgs, multiplicationUnits, 2, 'UniversalVocabularyMt', vStrDef).
 6066exactlyAssertedEL_next(singleEntryFormatInArgs, multiplicationUnits, 1, 'UniversalVocabularyMt', vStrDef).
 6067exactlyAssertedEL_next(singleEntryFormatInArgs, minQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 6068exactlyAssertedEL_next(singleEntryFormatInArgs, means, 2, 'UniversalVocabularyMt', vStrDef).
 6069exactlyAssertedEL_next(singleEntryFormatInArgs, maxQuantValue, 2, 'UniversalVocabularyMt', vStrDef).
 6070exactlyAssertedEL_next(singleEntryFormatInArgs, expresses, 2, 'UniversalVocabularyMt', vStrDef).
 6071exactlyAssertedEL_next(singleEntryFormatInArgs, expansion, 2, 'UniversalVocabularyMt', vStrMon).
 6072exactlyAssertedEL_next(singleEntryFormatInArgs, evaluationDefn, 2, 'UniversalVocabularyMt', vStrDef).
 6073exactlyAssertedEL_next(singleEntryFormatInArgs, cycTacticID, 3, 'UniversalVocabularyMt', vStrMon).
 6074exactlyAssertedEL_next(singleEntryFormatInArgs, cycProofID, 3, 'UniversalVocabularyMt', vStrMon).
 6075exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemStoreProofCount, 2, 'UniversalVocabularyMt', vStrMon).
 6076exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemStoreProblemCount, 2, 'UniversalVocabularyMt', vStrMon).
 6077exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemStoreLinkCount, 2, 'UniversalVocabularyMt', vStrMon).
 6078exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemStoreInferenceCount, 2, 'UniversalVocabularyMt', vStrMon).
 6079exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemStoreID, 2, 'UniversalVocabularyMt', vStrMon).
 6080exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemQuerySentence, 2, 'UniversalVocabularyMt', vStrMon).
 6081exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemProvabilityStatus, 2, 'UniversalVocabularyMt', vStrMon).
 6082exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemLinkID, 3, 'UniversalVocabularyMt', vStrMon).
 6083exactlyAssertedEL_next(singleEntryFormatInArgs, cycProblemID, 3, 'UniversalVocabularyMt', vStrMon).
 6084exactlyAssertedEL_next(singleEntryFormatInArgs, cycInferenceAnswerLink, 2, 'UniversalVocabularyMt', vStrMon).
 6085exactlyAssertedEL_next(singleEntryFormatInArgs, cycInferenceAnswerLink, 1, 'UniversalVocabularyMt', vStrMon).
 6086exactlyAssertedEL_next(sentenceDesignationArgnum, ist, 2, 'BaseKB', vStrDef).
 6087exactlyAssertedEL_next(sentenceDesignationArgnum, 'TLAssertionFn', 2, 'BaseKB', vStrDef).
 6088exactlyAssertedEL_next(sentenceDesignationArgnum, 'ist-Asserted', 2, 'BaseKB', vStrDef).
 6089exactlyAssertedEL_next(scopingArg, thereExists, 1, 'BaseKB', vStrDef).
 6090exactlyAssertedEL_next(scopingArg, thereExistExactly, 2, 'BaseKB', vStrDef).
 6091exactlyAssertedEL_next(scopingArg, thereExistAtMost, 2, 'BaseKB', vStrDef).
 6092exactlyAssertedEL_next(scopingArg, thereExistAtLeast, 2, 'BaseKB', vStrDef).
 6093exactlyAssertedEL_next(scopingArg, forAll, 1, 'BaseKB', vStrDef).
 6094exactlyAssertedEL_next(scopingArg, 'TheSetOf', 1, 'BaseKB', vStrDef).
 6095exactlyAssertedEL_next(scopingArg, 'TheCollectionOf', 1, 'BaseKB', vStrDef).
 6096exactlyAssertedEL_next(scopingArg, 'Kappa', 1, 'BaseKB', vStrDef).
 6097exactlyAssertedEL_next(ruleTemplateDirection, 'NART'(['CollectionRuleTemplateFn', 'HypotheticalContext']), 'Forward-AssertionDirection', 'UniversalVocabularyMt', vStrMon).
 6098exactlyAssertedEL_next(ruleTemplateDirection, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), 'Forward-AssertionDirection', 'BaseKB', vStrMon).
 6099exactlyAssertedEL_next(rewriteOf, 'TheEmptySet', 'TheSet', 'UniversalVocabularyMt', vStrMon).
 6100exactlyAssertedEL_next(requiredArg1Pred, 'TernaryRelation', arg3Isa, 'UniversalVocabularyMt', vStrDef).
 6101exactlyAssertedEL_next(requiredArg1Pred, 'TernaryRelation', arg2Isa, 'UniversalVocabularyMt', vStrDef).
 6102exactlyAssertedEL_next(requiredArg1Pred, 'SetOrCollection', subsetOf, 'UniversalVocabularyMt', vStrMon).
 6103exactlyAssertedEL_next(requiredArg1Pred, 'ScopingRelation', scopingArg, 'UniversalVocabularyMt', vStrDef).
 6104exactlyAssertedEL_next(requiredArg1Pred, tRelation, genFormat, 'EnglishParaphraseMt', vStrDef).
 6105exactlyAssertedEL_next(requiredArg1Pred, 'QuintaryRelation', arg5Isa, 'UniversalVocabularyMt', vStrDef).
 6106exactlyAssertedEL_next(requiredArg1Pred, 'QuintaryRelation', arg4Isa, 'UniversalVocabularyMt', vStrDef).
 6107exactlyAssertedEL_next(requiredArg1Pred, 'QuintaryRelation', arg3Isa, 'UniversalVocabularyMt', vStrDef).
 6108exactlyAssertedEL_next(requiredArg1Pred, 'QuintaryRelation', arg2Isa, 'UniversalVocabularyMt', vStrDef).
 6109exactlyAssertedEL_next(requiredArg1Pred, 'QuaternaryRelation', arg4Isa, 'UniversalVocabularyMt', vStrDef).
 6110exactlyAssertedEL_next(requiredArg1Pred, 'QuaternaryRelation', arg3Isa, 'UniversalVocabularyMt', vStrDef).
 6111exactlyAssertedEL_next(requiredArg1Pred, 'QuaternaryRelation', arg2Isa, 'UniversalVocabularyMt', vStrDef).
 6112exactlyAssertedEL_next(requiredArg1Pred, tPred, arity, 'UniversalVocabularyMt', vStrDef).
 6113exactlyAssertedEL_next(requiredArg1Pred, tPred, argIsa, 'UniversalVocabularyMt', vStrDef).
 6114exactlyAssertedEL_next(requiredArg1Pred, tFunction, resultIsa, 'UniversalVocabularyMt', vStrDef).
 6115exactlyAssertedEL_next(requiredArg1Pred, 'FixedArityRelation', arity, 'UniversalVocabularyMt', vStrDef).
 6116exactlyAssertedEL_next(requiredArg1Pred, 'FixedArityRelation', argIsa, 'UniversalVocabularyMt', vStrDef).
 6117exactlyAssertedEL_next(requiredArg1Pred, 'FixedArityRelation', arg1Isa, 'UniversalVocabularyMt', vStrDef).
 6118exactlyAssertedEL_next(requiredArg1Pred, 'EvaluatableRelation', evaluationDefn, 'UniversalVocabularyMt', vStrDef).
 6119exactlyAssertedEL_next(requiredArg1Pred, 'CycLAssertion', assertionDirection, 'UniversalVocabularyMt', vStrMon).
 6120exactlyAssertedEL_next(requiredArg1Pred, 'CollectionDenotingFunction', resultGenl, 'UniversalVocabularyMt', vStrDef).
 6121exactlyAssertedEL_next(requiredArg1Pred, 'BinaryRelation', arg2Isa, 'UniversalVocabularyMt', vStrDef).
 6122
 6123exactlyAssertedEL_next(afterRemoving, unitMultiplicationFactor, 'SubLQuoteFn'('CLEAR-UNIT-MULTIPLICATION-FACTOR-CACHES'), 'UniversalVocabularyImplementationMt', vStrMon).
 6124exactlyAssertedEL_next(afterRemoving, transitiveViaArgInverse, 'SubLQuoteFn'('REMOVE-TRANSITIVE-VIA-ARG-INVERSE'), 'BaseKB', vStrDef).
 6125exactlyAssertedEL_next(afterRemoving, transitiveViaArgInverse, 'SubLQuoteFn'('CLEAR-CACHED-SOME-TVA-CHECKS'), 'BaseKB', vStrDef).
 6126exactlyAssertedEL_next(afterRemoving, transitiveViaArg, 'SubLQuoteFn'('REMOVE-TRANSITIVE-VIA-ARG'), 'BaseKB', vStrDef).
 6127exactlyAssertedEL_next(afterRemoving, transitiveViaArg, 'SubLQuoteFn'('CLEAR-CACHED-TVA-CHECKS'), 'BaseKB', vStrDef).
 6128exactlyAssertedEL_next(afterRemoving, termOfUnit, 'SubLQuoteFn'('REMOVE-TERM-OF-UNIT'), 'LogicalTruthImplementationMt', vStrMon).
 6129exactlyAssertedEL_next(afterRemoving, termDependsOn, 'SubLQuoteFn'('REMOVE-DEPENDENT-TERM'), 'BaseKB', vStrDef).
 6130exactlyAssertedEL_next(afterRemoving, substring, 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6131exactlyAssertedEL_next(afterRemoving, substring, 'SubLQuoteFn'('REMOVE-TVA-CACHE-KEY'), 'BaseKB', vStrDef).
 6132exactlyAssertedEL_next(afterRemoving, skolem, 'SubLQuoteFn'('SKOLEM-AFTER-REMOVING'), 'UniversalVocabularyMt', vStrDef).
 6133exactlyAssertedEL_next(afterRemoving, ruleAfterRemoving, 'SubLQuoteFn'('DECACHE-RULE-AFTER-REMOVINGS'), 'CoreCycLImplementationMt', vStrMon).
 6134exactlyAssertedEL_next(afterRemoving, ruleAfterAdding, 'SubLQuoteFn'('DECACHE-RULE-AFTER-ADDINGS'), 'CoreCycLImplementationMt', vStrMon).
 6135exactlyAssertedEL_next(afterRemoving, rewriteOf, 'SubLQuoteFn'('DECACHE-SOME-SOURCE-REWRITE-OF-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6136exactlyAssertedEL_next(afterRemoving, rewriteOf, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6137exactlyAssertedEL_next(afterRemoving, rewriteOf, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6138exactlyAssertedEL_next(afterRemoving, resultQuotedIsa, 'SubLQuoteFn'('REMOVE-SUF-QUOTED-FUNCTION'), 'CoreCycLImplementationMt', vStrDef).
 6139exactlyAssertedEL_next(afterRemoving, resultIsa, 'SubLQuoteFn'('REMOVE-SUF-FUNCTION'), 'LogicalTruthImplementationMt', vStrMon).
 6140exactlyAssertedEL_next(afterRemoving, relationExpansion, 'SubLQuoteFn'('REMOVE-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6141exactlyAssertedEL_next(afterRemoving, reformulatorRuleProperties, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6142exactlyAssertedEL_next(afterRemoving, reformulatorRule, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6143exactlyAssertedEL_next(afterRemoving, reformulatorEquiv, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6144exactlyAssertedEL_next(afterRemoving, reformulatorEquals, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6145exactlyAssertedEL_next(afterRemoving, reformulationPrecondition, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6146exactlyAssertedEL_next(afterRemoving, reformulationDirectionInMode, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6147exactlyAssertedEL_next(afterRemoving, quotedIsa, 'SubLQuoteFn'('QUOTED-INSTANCEOF-AFTER-REMOVING'), 'LogicalTruthImplementationMt', vStrMon).
 6148exactlyAssertedEL_next(afterRemoving, quotedDefnSufficient, 'SubLQuoteFn'('REMOVE-SUF-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6149exactlyAssertedEL_next(afterRemoving, quotedDefnNecessary, 'SubLQuoteFn'('REMOVE-NEC-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6150exactlyAssertedEL_next(afterRemoving, quotedDefnIff, 'SubLQuoteFn'('REMOVE-IFF-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6151exactlyAssertedEL_next(afterRemoving, prettyString, 'SubLQuoteFn'('REMOVE-SEMANTIC-ASSERTION'), 'BaseKB', vStrDef).
 6152exactlyAssertedEL_next(afterRemoving, prettyString, 'SubLQuoteFn'('REMOVE-PROPER-NAME-PREDICATE'), 'BaseKB', vStrDef).
 6153exactlyAssertedEL_next(afterRemoving, oldConstantName, 'SubLQuoteFn'('REMOVE-OLD-CONSTANT-NAME'), 'BaseKB', vStrMon).
 6154exactlyAssertedEL_next(afterRemoving, negationPreds, 'SubLQuoteFn'('NEGATION-PREDICATE-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6155exactlyAssertedEL_next(afterRemoving, negationInverse, 'SubLQuoteFn'('REMOVE-NEGATION-INVERSE'), 'BaseKB', vStrDef).
 6156exactlyAssertedEL_next(afterRemoving, nearestGenls, 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6157exactlyAssertedEL_next(afterRemoving, natFunction, 'SubLQuoteFn'('REMOVE-DEPENDENT-TERM'), 'BaseKB', vStrDef).
 6158exactlyAssertedEL_next(afterRemoving, knownAntecedentRule, 'SubLQuoteFn'('CYC-REMOVE-KNOWN-ANTECEDENT-RULE'), 'UniversalVocabularyImplementationMt', vStrMon).
 6159exactlyAssertedEL_next(afterRemoving, isa, 'SubLQuoteFn'('INSTANCEOF-AFTER-REMOVING'), 'LogicalTruthImplementationMt', vStrMon).
 6160exactlyAssertedEL_next(afterRemoving, isa, 'SubLQuoteFn'('CLEAR-ISA-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6161exactlyAssertedEL_next(afterRemoving, interArgIsa, 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6162exactlyAssertedEL_next(afterRemoving, indexicalReferent, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6163exactlyAssertedEL_next(afterRemoving, hlPrototypicalInstance, 'SubLQuoteFn'('HL-PROTOTYPICAL-INSTANCE-AFTER-REMOVING'), 'CoreCycLImplementationMt', vStrDef).
 6164exactlyAssertedEL_next(afterRemoving, highlyRelevantTerm, 'SubLQuoteFn'('CYC-REMOVE-RELEVANT-TERM'), 'CoreCycLImplementationMt', vStrDef).
 6165exactlyAssertedEL_next(afterRemoving, genls, 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6166exactlyAssertedEL_next(afterRemoving, genls, 'SubLQuoteFn'('PGIA-AFTER-REMOVING-GENLS'), 'LogicalTruthImplementationMt', vStrMon).
 6167exactlyAssertedEL_next(afterRemoving, genls, 'SubLQuoteFn'('GENLS-AFTER-REMOVING'), 'LogicalTruthImplementationMt', vStrMon).
 6168exactlyAssertedEL_next(afterRemoving, genls, 'SubLQuoteFn'('CLEAR-GENLS-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6169exactlyAssertedEL_next(afterRemoving, genlPreds, 'SubLQuoteFn'('REMOVE-GENL-PREDICATE'), 'BaseKB', vStrDef).
 6170exactlyAssertedEL_next(afterRemoving, genlMt, 'SubLQuoteFn'('REMOVE-BASE-MT'), 'LogicalTruthImplementationMt', vStrMon).
 6171exactlyAssertedEL_next(afterRemoving, genlMt, 'SubLQuoteFn'('CLEAR-MT-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6172exactlyAssertedEL_next(afterRemoving, genlInverse, 'SubLQuoteFn'('REMOVE-GENL-INVERSE'), 'BaseKB', vStrDef).
 6173exactlyAssertedEL_next(afterRemoving, genKeyword, 'SubLQuoteFn'('REMOVE-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6174exactlyAssertedEL_next(afterRemoving, genFormat, 'SubLQuoteFn'('REMOVE-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6175exactlyAssertedEL_next(afterRemoving, expansion, 'SubLQuoteFn'('REMOVE-GEN-TEMPLATE-EXPANSION'), 'BaseKB', vStrDef).
 6176exactlyAssertedEL_next(afterRemoving, expansion, 'SubLQuoteFn'('REMOVE-FROM-CONTRACTION-HT'), 'BaseKB', vStrDef).
 6177exactlyAssertedEL_next(afterRemoving, expansion, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6178exactlyAssertedEL_next(afterRemoving, except, 'SubLQuoteFn'('CYC-EXCEPT-REMOVED'), 'CoreCycLImplementationMt', vStrMon).
 6179exactlyAssertedEL_next(afterRemoving, evaluationResultQuotedIsa, 'SubLQuoteFn'('REMOVE-SUF-QUOTED-FUNCTION'), 'CoreCycLImplementationMt', vStrMon).
 6180exactlyAssertedEL_next(afterRemoving, evaluationDefn, 'SubLQuoteFn'('DECACHE-LISP-DEFUN'), 'BaseKB', vStrDef).
 6181exactlyAssertedEL_next(afterRemoving, equalSymbols, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6182exactlyAssertedEL_next(afterRemoving, equals, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'LogicalTruthImplementationMt', vStrMon).
 6183exactlyAssertedEL_next(afterRemoving, equals, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6184exactlyAssertedEL_next(afterRemoving, disjointWith, 'SubLQuoteFn'('MDW-AFTER-REMOVING'), 'LogicalTruthImplementationMt', vStrMon).
 6185exactlyAssertedEL_next(afterRemoving, defnSufficient, 'SubLQuoteFn'('REMOVE-SUF-DEFN'), 'BaseKB', vStrMon).
 6186exactlyAssertedEL_next(afterRemoving, defnNecessary, 'SubLQuoteFn'('REMOVE-NEC-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6187exactlyAssertedEL_next(afterRemoving, defnIff, 'SubLQuoteFn'('REMOVE-IFF-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6188exactlyAssertedEL_next(afterRemoving, definingMt, 'SubLQuoteFn'('REMOVE-DEPENDENT-TERM'), 'BaseKB', vStrDef).
 6189exactlyAssertedEL_next(afterRemoving, defaultReformulatorModePrecedence, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6190exactlyAssertedEL_next(afterRemoving, defaultReformulationDirectionInModeForPred, 'SubLQuoteFn'('CYC-REMOVE-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6191exactlyAssertedEL_next(afterRemoving, coExtensional, 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6192exactlyAssertedEL_next(afterRemoving, canonicalizerDirectiveForArgAndRest, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6193exactlyAssertedEL_next(afterRemoving, canonicalizerDirectiveForArg, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6194exactlyAssertedEL_next(afterRemoving, canonicalizerDirectiveForAllArgs, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6195exactlyAssertedEL_next(afterRemoving, arityMin, 'SubLQuoteFn'('REMOVE-MAX-ARITY'), 'BaseKB', vStrDef).
 6196exactlyAssertedEL_next(afterRemoving, arityMin, 'SubLQuoteFn'('REMOVE-ARITY-MIN'), 'LogicalTruthImplementationMt', vStrMon).
 6197exactlyAssertedEL_next(afterRemoving, arityMax, 'SubLQuoteFn'('REMOVE-MAX-ARITY'), 'BaseKB', vStrDef).
 6198exactlyAssertedEL_next(afterRemoving, arityMax, 'SubLQuoteFn'('REMOVE-ARITY-MAX'), 'LogicalTruthImplementationMt', vStrMon).
 6199exactlyAssertedEL_next(afterRemoving, arity, 'SubLQuoteFn'('REMOVE-ARITY'), 'LogicalTruthImplementationMt', vStrMon).
 6200exactlyAssertedEL_next(afterRemoving, arg6Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6201exactlyAssertedEL_next(afterRemoving, arg5Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6202exactlyAssertedEL_next(afterRemoving, arg4Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6203exactlyAssertedEL_next(afterRemoving, arg3Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6204exactlyAssertedEL_next(afterRemoving, arg2Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6205exactlyAssertedEL_next(afterRemoving, arg1Isa, 'SubLQuoteFn'('CYC-REMOVE-FROM-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6206exactlyAssertedEL_next(afterRemoving, afterRemoving, 'SubLQuoteFn'('DECACHE-AFTER-REMOVINGS'), 'LogicalTruthImplementationMt', vStrMon).
 6207exactlyAssertedEL_next(afterRemoving, afterAdding, 'SubLQuoteFn'('DECACHE-AFTER-ADDINGS'), 'LogicalTruthImplementationMt', vStrMon).
 6208exactlyAssertedEL_next(afterRemoving, 'prettyString-Canonical', 'SubLQuoteFn'('REMOVE-SEMANTIC-ASSERTION'), 'BaseKB', vStrDef).
 6209exactlyAssertedEL_next(afterRemoving, 'prettyString-Canonical', 'SubLQuoteFn'('REMOVE-PROPER-NAME-PREDICATE'), 'BaseKB', vStrDef).
 6210exactlyAssertedEL_next(afterRemoving, 'interArgIsa5-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6211exactlyAssertedEL_next(afterRemoving, 'interArgIsa5-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6212exactlyAssertedEL_next(afterRemoving, 'interArgIsa5-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6213exactlyAssertedEL_next(afterRemoving, 'interArgIsa5-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6214exactlyAssertedEL_next(afterRemoving, 'interArgIsa4-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6215exactlyAssertedEL_next(afterRemoving, 'interArgIsa4-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6216exactlyAssertedEL_next(afterRemoving, 'interArgIsa4-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6217exactlyAssertedEL_next(afterRemoving, 'interArgIsa4-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6218exactlyAssertedEL_next(afterRemoving, 'interArgIsa3-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6219exactlyAssertedEL_next(afterRemoving, 'interArgIsa3-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6220exactlyAssertedEL_next(afterRemoving, 'interArgIsa3-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6221exactlyAssertedEL_next(afterRemoving, 'interArgIsa3-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6222exactlyAssertedEL_next(afterRemoving, 'interArgIsa2-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6223exactlyAssertedEL_next(afterRemoving, 'interArgIsa2-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6224exactlyAssertedEL_next(afterRemoving, 'interArgIsa2-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6225exactlyAssertedEL_next(afterRemoving, 'interArgIsa2-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6226exactlyAssertedEL_next(afterRemoving, 'interArgIsa1-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6227exactlyAssertedEL_next(afterRemoving, 'interArgIsa1-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6228exactlyAssertedEL_next(afterRemoving, 'interArgIsa1-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6229exactlyAssertedEL_next(afterRemoving, 'interArgIsa1-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6230exactlyAssertedEL_next(afterRemoving, 'interArgFormat1-2', 'SubLQuoteFn'('INTER-ARG-FORMAT-AFTER-REMOVING'), 'BaseKB', vStrDef).
 6231exactlyAssertedEL_next(afterRemoving, 'equalStrings-CaseInsensitive', 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6232exactlyAssertedEL_next(afterAdding, unitMultiplicationFactor, 'SubLQuoteFn'('CLEAR-UNIT-MULTIPLICATION-FACTOR-CACHES'), 'UniversalVocabularyImplementationMt', vStrMon).
 6233exactlyAssertedEL_next(afterAdding, trueRule, 'SubLQuoteFn'('ADD-TRUE-RULE'), 'BaseKB', vStrMon).
 6234exactlyAssertedEL_next(afterAdding, transitiveViaArgInverse, 'SubLQuoteFn'('CLEAR-CACHED-SOME-TVA-CHECKS'), 'BaseKB', vStrDef).
 6235exactlyAssertedEL_next(afterAdding, transitiveViaArgInverse, 'SubLQuoteFn'('ADD-TRANSITIVE-VIA-ARG-INVERSE'), 'BaseKB', vStrDef).
 6236exactlyAssertedEL_next(afterAdding, transitiveViaArg, 'SubLQuoteFn'('CLEAR-CACHED-TVA-CHECKS'), 'BaseKB', vStrDef).
 6237exactlyAssertedEL_next(afterAdding, transitiveViaArg, 'SubLQuoteFn'('ADD-TRANSITIVE-VIA-ARG'), 'BaseKB', vStrDef).
 6238exactlyAssertedEL_next(afterAdding, termOfUnit, 'SubLQuoteFn'('ADD-TERM-OF-UNIT'), 'LogicalTruthImplementationMt', vStrMon).
 6239exactlyAssertedEL_next(afterAdding, substring, 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6240exactlyAssertedEL_next(afterAdding, substring, 'SubLQuoteFn'('ADD-TVA-CACHE-KEY'), 'BaseKB', vStrDef).
 6241exactlyAssertedEL_next(afterAdding, ruleAfterRemoving, 'SubLQuoteFn'('DECACHE-RULE-AFTER-REMOVINGS'), 'CoreCycLImplementationMt', vStrMon).
 6242exactlyAssertedEL_next(afterAdding, ruleAfterAdding, 'SubLQuoteFn'('DECACHE-RULE-AFTER-ADDINGS'), 'CoreCycLImplementationMt', vStrMon).
 6243exactlyAssertedEL_next(afterAdding, rewriteOf, 'SubLQuoteFn'('REWRITE-OF-AFTER-ADDING'), 'BaseKB', vStrDef).
 6244exactlyAssertedEL_next(afterAdding, rewriteOf, 'SubLQuoteFn'('DECACHE-SOME-SOURCE-REWRITE-OF-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6245exactlyAssertedEL_next(afterAdding, rewriteOf, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6246exactlyAssertedEL_next(afterAdding, rewriteOf, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6247exactlyAssertedEL_next(afterAdding, resultQuotedIsa, 'SubLQuoteFn'('ADD-SUF-QUOTED-FUNCTION'), 'CoreCycLImplementationMt', vStrDef).
 6248exactlyAssertedEL_next(afterAdding, resultIsa, 'SubLQuoteFn'('ADD-SUF-FUNCTION'), 'LogicalTruthImplementationMt', vStrMon).
 6249exactlyAssertedEL_next(afterAdding, relationExpansion, 'SubLQuoteFn'('ADD-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6250exactlyAssertedEL_next(afterAdding, reformulatorRuleProperties, 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-ISA'), 'BaseKB', vStrDef).
 6251exactlyAssertedEL_next(afterAdding, reformulatorRuleProperties, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6252exactlyAssertedEL_next(afterAdding, reformulatorRule, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6253exactlyAssertedEL_next(afterAdding, reformulatorEquiv, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6254exactlyAssertedEL_next(afterAdding, reformulatorEquals, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6255exactlyAssertedEL_next(afterAdding, reformulationPrecondition, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6256exactlyAssertedEL_next(afterAdding, reformulationDirectionInMode, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6257exactlyAssertedEL_next(afterAdding, quotedIsa, 'SubLQuoteFn'('QUOTED-INSTANCEOF-AFTER-ADDING'), 'LogicalTruthImplementationMt', vStrMon).
 6258exactlyAssertedEL_next(afterAdding, quotedDefnSufficient, 'SubLQuoteFn'('ADD-SUF-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6259exactlyAssertedEL_next(afterAdding, quotedDefnNecessary, 'SubLQuoteFn'('ADD-NEC-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6260exactlyAssertedEL_next(afterAdding, quotedDefnIff, 'SubLQuoteFn'('ADD-IFF-QUOTED-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6261exactlyAssertedEL_next(afterAdding, prettyString, 'SubLQuoteFn'('ADD-SEMANTIC-ASSERTION'), 'BaseKB', vStrDef).
 6262exactlyAssertedEL_next(afterAdding, prettyString, 'SubLQuoteFn'('ADD-PROPER-NAME-PREDICATE'), 'BaseKB', vStrDef).
 6263exactlyAssertedEL_next(afterAdding, preservesGenlsInArg, 'SubLQuoteFn'('PGIA-AFTER-ADDING-PGIA'), 'BaseKB', vStrMon).
 6264exactlyAssertedEL_next(afterAdding, oldConstantName, 'SubLQuoteFn'('ADD-OLD-CONSTANT-NAME'), 'BaseKB', vStrMon).
 6265exactlyAssertedEL_next(afterAdding, negationPreds, 'SubLQuoteFn'('NEGATION-PREDICATE-AFTER-ADDING'), 'BaseKB', vStrDef).
 6266exactlyAssertedEL_next(afterAdding, negationInverse, 'SubLQuoteFn'('ADD-NEGATION-INVERSE'), 'BaseKB', vStrDef).
 6267exactlyAssertedEL_next(afterAdding, nearestIsa, 'SubLQuoteFn'('PROPAGATE-TO-ISA'), 'BaseKB', vStrDef).
 6268exactlyAssertedEL_next(afterAdding, nearestGenls, 'SubLQuoteFn'('PROPAGATE-TO-GENLS'), 'BaseKB', vStrDef).
 6269exactlyAssertedEL_next(afterAdding, nearestGenls, 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6270exactlyAssertedEL_next(afterAdding, nearestGenlPreds, 'SubLQuoteFn'('PROPAGATE-TO-GENLPREDS'), 'BaseKB', vStrDef).
 6271exactlyAssertedEL_next(afterAdding, nearestGenlMt, 'SubLQuoteFn'('PROPAGATE-TO-GENLMT'), 'BaseKB', vStrDef).
 6272exactlyAssertedEL_next(afterAdding, knownAntecedentRule, 'SubLQuoteFn'('CYC-ADD-KNOWN-ANTECEDENT-RULE'), 'UniversalVocabularyImplementationMt', vStrMon).
 6273exactlyAssertedEL_next(afterAdding, ist, 'SubLQuoteFn'('ADD-IST'), 'BaseKB', vStrDef).
 6274exactlyAssertedEL_next(afterAdding, isa, 'SubLQuoteFn'('PGIA-AFTER-ADDING-ISA'), 'LogicalTruthImplementationMt', vStrMon).
 6275exactlyAssertedEL_next(afterAdding, isa, 'SubLQuoteFn'('INSTANCEOF-AFTER-ADDING'), 'LogicalTruthImplementationMt', vStrMon).
 6276exactlyAssertedEL_next(afterAdding, isa, 'SubLQuoteFn'('CLEAR-ISA-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6277exactlyAssertedEL_next(afterAdding, irrelevantTerm, 'SubLQuoteFn'('CYC-REMOVE-IRRELEVANT-TERM'), 'CoreCycLImplementationMt', vStrDef).
 6278exactlyAssertedEL_next(afterAdding, irrelevantTerm, 'SubLQuoteFn'('CYC-ADD-IRRELEVANT-TERM'), 'CoreCycLImplementationMt', vStrDef).
 6279exactlyAssertedEL_next(afterAdding, interArgIsa, 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6280exactlyAssertedEL_next(afterAdding, indexicalReferent, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6281exactlyAssertedEL_next(afterAdding, hlPrototypicalInstance, 'SubLQuoteFn'('HL-PROTOTYPICAL-INSTANCE-AFTER-ADDING'), 'CoreCycLImplementationMt', vStrDef).
 6282exactlyAssertedEL_next(afterAdding, highlyRelevantTerm, 'SubLQuoteFn'('CYC-ADD-RELEVANT-TERM'), 'CoreCycLImplementationMt', vStrDef).
 6283exactlyAssertedEL_next(afterAdding, genls, 'SubLQuoteFn'('GENLS-AFTER-ADDING'), 'LogicalTruthImplementationMt', vStrMon).
 6284exactlyAssertedEL_next(afterAdding, genls, 'SubLQuoteFn'('CLEAR-GENLS-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6285exactlyAssertedEL_next(afterAdding, genls, 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6286exactlyAssertedEL_next(afterAdding, genlPreds, 'SubLQuoteFn'('ADD-GENL-PREDICATE'), 'BaseKB', vStrDef).
 6287exactlyAssertedEL_next(afterAdding, genlMt, 'SubLQuoteFn'('CLEAR-MT-DEPENDENT-CACHES'), 'LogicalTruthImplementationMt', vStrMon).
 6288exactlyAssertedEL_next(afterAdding, genlMt, 'SubLQuoteFn'('ADD-BASE-MT'), 'LogicalTruthImplementationMt', vStrMon).
 6289exactlyAssertedEL_next(afterAdding, genlInverse, 'SubLQuoteFn'('ADD-GENL-INVERSE'), 'BaseKB', vStrDef).
 6290exactlyAssertedEL_next(afterAdding, genKeyword, 'SubLQuoteFn'('ADD-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6291exactlyAssertedEL_next(afterAdding, genKeyword, 'SubLQuoteFn'('ADD-GEN-KEYWORD'), 'BaseKB', vStrDef).
 6292exactlyAssertedEL_next(afterAdding, genFormat, 'SubLQuoteFn'('ADD-GENERATION-ASSERTION'), 'UniversalVocabularyMt', vStrDef).
 6293exactlyAssertedEL_next(afterAdding, expansion, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6294exactlyAssertedEL_next(afterAdding, expansion, 'SubLQuoteFn'('ADD-TO-CONTRACTION-HT'), 'BaseKB', vStrDef).
 6295exactlyAssertedEL_next(afterAdding, expansion, 'SubLQuoteFn'('ADD-GEN-TEMPLATE-EXPANSION'), 'BaseKB', vStrDef).
 6296exactlyAssertedEL_next(afterAdding, except, 'SubLQuoteFn'('CYC-EXCEPT-ADDED'), 'CoreCycLImplementationMt', vStrMon).
 6297exactlyAssertedEL_next(afterAdding, evaluationResultQuotedIsa, 'SubLQuoteFn'('ADD-SUF-QUOTED-FUNCTION'), 'CoreCycLImplementationMt', vStrMon).
 6298exactlyAssertedEL_next(afterAdding, evaluationDefn, 'SubLQuoteFn'('DECACHE-LISP-DEFUN'), 'BaseKB', vStrDef).
 6299exactlyAssertedEL_next(afterAdding, equalSymbols, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6300exactlyAssertedEL_next(afterAdding, equals, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'LogicalTruthImplementationMt', vStrMon).
 6301exactlyAssertedEL_next(afterAdding, equals, 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6302exactlyAssertedEL_next(afterAdding, elInverse, 'SubLQuoteFn'('PROPAGATE-TO-GENLINVERSE'), 'BaseKB', vStrDef).
 6303exactlyAssertedEL_next(afterAdding, elInverse, 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLINVERSE'), 'BaseKB', vStrDef).
 6304exactlyAssertedEL_next(afterAdding, elementOf, 'SubLQuoteFn'('CYC-ADD-ELEMENT-OF'), 'BaseKB', vStrMon).
 6305exactlyAssertedEL_next(afterAdding, disjointWith, 'SubLQuoteFn'('MDW-AFTER-ADDING'), 'LogicalTruthImplementationMt', vStrMon).
 6306exactlyAssertedEL_next(afterAdding, defnSufficient, 'SubLQuoteFn'('ADD-SUF-DEFN'), 'BaseKB', vStrMon).
 6307exactlyAssertedEL_next(afterAdding, defnNecessary, 'SubLQuoteFn'('ADD-NEC-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6308exactlyAssertedEL_next(afterAdding, defnIff, 'SubLQuoteFn'('ADD-IFF-DEFN'), 'LogicalTruthImplementationMt', vStrMon).
 6309exactlyAssertedEL_next(afterAdding, defaultReformulatorModePrecedence, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6310exactlyAssertedEL_next(afterAdding, defaultReformulationDirectionInModeForPred, 'SubLQuoteFn'('CYC-ADD-REFORMULATION-ASSERTION'), 'BaseKB', vStrDef).
 6311exactlyAssertedEL_next(afterAdding, coExtensional, 'SubLQuoteFn'('PROPAGATE-TO-GENLS'), 'BaseKB', vStrDef).
 6312exactlyAssertedEL_next(afterAdding, coExtensional, 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLS'), 'BaseKB', vStrDef).
 6313exactlyAssertedEL_next(afterAdding, coExtensional, 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE'), 'BaseKB', vStrDef).
 6314exactlyAssertedEL_next(afterAdding, canonicalizerDirectiveForArgAndRest, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6315exactlyAssertedEL_next(afterAdding, canonicalizerDirectiveForArg, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6316exactlyAssertedEL_next(afterAdding, canonicalizerDirectiveForAllArgs, 'SubLQuoteFn'('RECACHE-SOME-CANONICALIZER-DIRECTIVE-ASSERTIONS-SOMEWHERE'), 'CoreCycLImplementationMt', vStrDef).
 6317exactlyAssertedEL_next(afterAdding, arityMin, 'SubLQuoteFn'('ADD-MAX-ARITY'), 'BaseKB', vStrDef).
 6318exactlyAssertedEL_next(afterAdding, arityMin, 'SubLQuoteFn'('ADD-ARITY-MIN'), 'LogicalTruthImplementationMt', vStrMon).
 6319exactlyAssertedEL_next(afterAdding, arityMax, 'SubLQuoteFn'('ADD-MAX-ARITY'), 'BaseKB', vStrDef).
 6320exactlyAssertedEL_next(afterAdding, arityMax, 'SubLQuoteFn'('ADD-ARITY-MAX'), 'LogicalTruthImplementationMt', vStrMon).
 6321exactlyAssertedEL_next(afterAdding, arity, 'SubLQuoteFn'('ADD-ARITY'), 'LogicalTruthImplementationMt', vStrMon).
 6322exactlyAssertedEL_next(afterAdding, arg6Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6323exactlyAssertedEL_next(afterAdding, arg5Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6324exactlyAssertedEL_next(afterAdding, arg4Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6325exactlyAssertedEL_next(afterAdding, arg3Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6326exactlyAssertedEL_next(afterAdding, arg2Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6327exactlyAssertedEL_next(afterAdding, arg1Isa, 'SubLQuoteFn'('CYC-ADD-TO-ARG-TYPE-CACHE'), 'CoreCycLImplementationMt', vStrDef).
 6328exactlyAssertedEL_next(afterAdding, afterRemoving, 'SubLQuoteFn'('DECACHE-AFTER-REMOVINGS'), 'LogicalTruthImplementationMt', vStrMon).
 6329exactlyAssertedEL_next(afterAdding, afterAdding, 'SubLQuoteFn'('DECACHE-AFTER-ADDINGS'), 'LogicalTruthImplementationMt', vStrMon).
 6330exactlyAssertedEL_next(afterAdding, 'prettyString-Canonical', 'SubLQuoteFn'('ADD-SEMANTIC-ASSERTION'), 'BaseKB', vStrDef).
 6331exactlyAssertedEL_next(afterAdding, 'prettyString-Canonical', 'SubLQuoteFn'('ADD-PROPER-NAME-PREDICATE'), 'BaseKB', vStrDef).
 6332exactlyAssertedEL_next(afterAdding, 'interArgIsa5-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6333exactlyAssertedEL_next(afterAdding, 'interArgIsa5-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6334exactlyAssertedEL_next(afterAdding, 'interArgIsa5-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6335exactlyAssertedEL_next(afterAdding, 'interArgIsa5-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6336exactlyAssertedEL_next(afterAdding, 'interArgIsa4-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6337exactlyAssertedEL_next(afterAdding, 'interArgIsa4-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6338exactlyAssertedEL_next(afterAdding, 'interArgIsa4-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6339exactlyAssertedEL_next(afterAdding, 'interArgIsa4-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6340exactlyAssertedEL_next(afterAdding, 'interArgIsa3-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6341exactlyAssertedEL_next(afterAdding, 'interArgIsa3-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6342exactlyAssertedEL_next(afterAdding, 'interArgIsa3-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6343exactlyAssertedEL_next(afterAdding, 'interArgIsa3-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6344exactlyAssertedEL_next(afterAdding, 'interArgIsa2-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6345exactlyAssertedEL_next(afterAdding, 'interArgIsa2-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6346exactlyAssertedEL_next(afterAdding, 'interArgIsa2-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6347exactlyAssertedEL_next(afterAdding, 'interArgIsa2-1', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6348exactlyAssertedEL_next(afterAdding, 'interArgIsa1-5', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6349exactlyAssertedEL_next(afterAdding, 'interArgIsa1-4', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6350exactlyAssertedEL_next(afterAdding, 'interArgIsa1-3', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6351exactlyAssertedEL_next(afterAdding, 'interArgIsa1-2', 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING'), 'BaseKB', vStrDef).
 6352exactlyAssertedEL_next(afterAdding, 'interArgFormat1-2', 'SubLQuoteFn'('INTER-ARG-FORMAT-AFTER-ADDING'), 'BaseKB', vStrDef).
 6353exactlyAssertedEL_next(afterAdding, 'equalStrings-CaseInsensitive', 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE'), 'BaseKB', vStrDef).
 6354
 6355exactlyAssertedEL_next('larkc-pluginByDataConnectsTo', 'larkc-GateTransformer', 'larkc-CycSelecter', 'BaseKB', vStrDef).
 6356exactlyAssertedEL_next('larkc-pluginByDataConnectsTo', 'larkc-GateTransformer', 'larkc-CycReasoner', 'BaseKB', vStrDef).
 6357exactlyAssertedEL_next('larkc-pluginByDataConnectsTo', 'larkc-CycSelecter', 'larkc-CycSelecter', 'BaseKB', vStrDef).
 6358exactlyAssertedEL_next('larkc-pluginByDataConnectsTo', 'larkc-CycSelecter', 'larkc-CycReasoner', 'BaseKB', vStrDef).
 6359exactlyAssertedEL_next('larkc-pluginByDataConnectsTo', 'larkc-ArticleIdentifier', 'larkc-GateTransformer', 'BaseKB', vStrDef).
 6360exactlyAssertedEL_next('larkc-hasOutputType', 'larkc-GateTransformer', 'larkc-RdfGraph', 'BaseKB', vStrDef).
 6361exactlyAssertedEL_next('larkc-hasOutputType', 'larkc-CycSelecter', 'larkc-RdfGraph', 'BaseKB', vStrDef).
 6362exactlyAssertedEL_next('larkc-hasOutputType', 'larkc-CycReasoner', 'larkc-VariableBinding', 'BaseKB', vStrDef).
 6363exactlyAssertedEL_next('larkc-hasOutputType', 'larkc-ArticleIdentifier', 'larkc-NaturalLanguageDocument', 'BaseKB', vStrDef).
 6364exactlyAssertedEL_next('larkc-hasInputType', 'larkc-GateTransformer', 'larkc-NaturalLanguageDocument', 'BaseKB', vStrDef).
 6365exactlyAssertedEL_next('larkc-hasInputType', 'larkc-CycSelecter', 'larkc-SetOfStatements', 'BaseKB', vStrDef).
 6366exactlyAssertedEL_next('larkc-hasInputType', 'larkc-CycReasoner', 'larkc-SetOfStatements', 'BaseKB', vStrDef).
 6367exactlyAssertedEL_next('larkc-hasInputType', 'larkc-ArticleIdentifier', 'larkc-SPARQLQuery', 'BaseKB', vStrDef).
 6368exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'VariableArityRelation', 'VariableArityRelation', 'UniversalVocabularyMt', vStrMon).
 6369exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'UnaryPredicate', 'UnaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6370exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'TernaryPredicate', 'TernaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6371exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'QuintaryPredicate', 'QuintaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6372exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'QuaternaryPredicate', 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6373exactlyAssertedEL_next('interArgIsa2-1', negationPreds, 'BinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6374exactlyAssertedEL_next('interArgIsa2-1', genls, 'SubLExpressionType', 'SubLExpressionType', 'UniversalVocabularyMt', vStrMon).
 6375exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'UnaryPredicate', 'UnaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6376exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'TernaryPredicate', 'TernaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6377exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'QuintaryPredicate', 'QuintaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6378exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'QuaternaryPredicate', 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6379exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'FixedArityRelation', 'FixedArityRelation', 'UniversalVocabularyMt', vStrDef).
 6380exactlyAssertedEL_next('interArgIsa2-1', genlPreds, 'BinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrMon).
 6381exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'VariableArityRelation', 'VariableArityRelation', 'UniversalVocabularyMt', vStrMon).
 6382exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'UnaryPredicate', 'UnaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6383exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'TernaryPredicate', 'TernaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6384exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'QuintaryPredicate', 'QuintaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6385exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'QuaternaryPredicate', 'QuaternaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6386exactlyAssertedEL_next('interArgIsa1-2', negationPreds, 'BinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6387exactlyAssertedEL_next('interArgIsa1-2', genlPreds, 'VariableArityRelation', 'VariableArityRelation', 'UniversalVocabularyMt', vStrMon).
 6388exactlyAssertedEL_next('interArgIsa1-2', arity, tPred, 'PositiveInteger', 'UniversalVocabularyMt', vStrDef).
 6389exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'TheTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6390exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLString', 'CharacterString', 'UniversalVocabularyMt', vStrMon).
 6391exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLPositiveInteger', 'PositiveInteger', 'UniversalVocabularyMt', vStrMon).
 6392exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLPositiveInteger', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrMon).
 6393exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLNonNegativeInteger', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrMon).
 6394exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLNonNegativeInteger', 'Integer', 'UniversalVocabularyMt', vStrMon).
 6395exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'SubLInteger', 'Integer', 'UniversalVocabularyMt', vStrMon).
 6396exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'HLPrototypicalTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6397exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'DocumentationPredicate', tPred, 'CoreCycLMt', vStrMon).
 6398exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6399exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLRepresentedTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6400exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLReifiedDenotationalTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6401exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLReifiableNonAtomicTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6402exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLReifiableDenotationalTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6403exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLNonAtomicTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6404exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLNonAtomicReifiedTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6405exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLIndexedTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6406exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLFormula', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6407exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLExpression', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6408exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLDenotationalTerm-Assertible', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6409exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLDenotationalTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6410exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLConstant', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6411exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLClosedNonAtomicTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6412exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLClosedExpression', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6413exactlyAssertedEL_next('genls-SpecDenotesGenlInstances', 'CycLClosedDenotationalTerm', 'Thing', 'UniversalVocabularyMt', vStrMon).
 6414
 6415exactlyAssertedEL_next(backchainRequired, sentenceTruth, 'UniversalVocabularyMt', vStrMon).
 6416exactlyAssertedEL_next(backchainForbidden, unknownSentence, 'UniversalVocabularyMt', vStrMon).
 6417exactlyAssertedEL_next(backchainForbidden, unknownSentence, 'CoreCycLImplementationMt', vStrMon).
 6418exactlyAssertedEL_next(backchainForbidden, trueSubL, 'BaseKB', vStrMon).
 6419exactlyAssertedEL_next(backchainForbidden, termOfUnit, 'UniversalVocabularyMt', vStrMon).
 6420exactlyAssertedEL_next(backchainForbidden, termOfUnit, 'CoreCycLImplementationMt', vStrMon).
 6421exactlyAssertedEL_next(backchainForbidden, termExternalIDString, 'UniversalVocabularyMt', vStrMon).
 6422exactlyAssertedEL_next(backchainForbidden, termDependsOn, 'UniversalVocabularyMt', vStrDef).
 6423exactlyAssertedEL_next(backchainForbidden, termChosen, 'UniversalVocabularyMt', vStrDef).
 6424exactlyAssertedEL_next(backchainForbidden, termChosen, 'CoreCycLImplementationMt', vStrMon).
 6425exactlyAssertedEL_next(backchainForbidden, sentenceImplies, 'UniversalVocabularyMt', vStrMon).
 6426exactlyAssertedEL_next(backchainForbidden, sentenceEquiv, 'UniversalVocabularyMt', vStrMon).
 6427exactlyAssertedEL_next(backchainForbidden, sentenceEquiv, 'CoreCycLImplementationMt', vStrMon).
 6428exactlyAssertedEL_next(backchainForbidden, salientAssertions, 'BaseKB', vStrDef).
 6429exactlyAssertedEL_next(backchainForbidden, resultIsaArgIsa, 'UniversalVocabularyMt', vStrDef).
 6430exactlyAssertedEL_next(backchainForbidden, quotedArgument, 'UniversalVocabularyMt', vStrDef).
 6431exactlyAssertedEL_next(backchainForbidden, pragmaticRequirement, 'UniversalVocabularyMt', vStrDef).
 6432exactlyAssertedEL_next(backchainForbidden, performSubL, 'UniversalVocabularyMt', vStrDef).
 6433exactlyAssertedEL_next(backchainForbidden, performSubL, 'CoreCycLImplementationMt', vStrMon).
 6434exactlyAssertedEL_next(backchainForbidden, operatorFormulas, 'UniversalVocabularyMt', vStrDef).
 6435exactlyAssertedEL_next(backchainForbidden, omitArgIsa, 'UniversalVocabularyMt', vStrDef).
 6436exactlyAssertedEL_next(backchainForbidden, nthSmallestElement, 'CoreCycLImplementationMt', vStrMon).
 6437exactlyAssertedEL_next(backchainForbidden, nearestIsa, 'CoreCycLImplementationMt', vStrMon).
 6438exactlyAssertedEL_next(backchainForbidden, nearestGenls, 'CoreCycLImplementationMt', vStrMon).
 6439exactlyAssertedEL_next(backchainForbidden, nearestGenlPreds, 'CoreCycLImplementationMt', vStrMon).
 6440exactlyAssertedEL_next(backchainForbidden, nearestGenlMt, 'CoreCycLImplementationMt', vStrMon).
 6441exactlyAssertedEL_next(backchainForbidden, nearestDifferentIsa, 'CoreCycLImplementationMt', vStrMon).
 6442exactlyAssertedEL_next(backchainForbidden, nearestDifferentGenls, 'CoreCycLImplementationMt', vStrMon).
 6443exactlyAssertedEL_next(backchainForbidden, nearestCommonSpecs, 'CoreCycLImplementationMt', vStrMon).
 6444exactlyAssertedEL_next(backchainForbidden, nearestCommonIsa, 'CoreCycLImplementationMt', vStrMon).
 6445exactlyAssertedEL_next(backchainForbidden, nearestCommonGenls, 'CoreCycLImplementationMt', vStrMon).
 6446exactlyAssertedEL_next(backchainForbidden, nearestCommonGenlMt, 'CoreCycLImplementationMt', vStrMon).
 6447exactlyAssertedEL_next(backchainForbidden, natFunction, 'UniversalVocabularyMt', vStrDef).
 6448exactlyAssertedEL_next(backchainForbidden, natFunction, 'CoreCycLImplementationMt', vStrMon).
 6449exactlyAssertedEL_next(backchainForbidden, natArgumentsEqual, 'UniversalVocabularyMt', vStrDef).
 6450exactlyAssertedEL_next(backchainForbidden, natArgumentsEqual, 'CoreCycLImplementationMt', vStrMon).
 6451exactlyAssertedEL_next(backchainForbidden, natArgument, 'UniversalVocabularyMt', vStrDef).
 6452exactlyAssertedEL_next(backchainForbidden, natArgument, 'CoreCycLImplementationMt', vStrMon).
 6453exactlyAssertedEL_next(backchainForbidden, myCreator, 'CoreCycLImplementationMt', vStrMon).
 6454exactlyAssertedEL_next(backchainForbidden, myCreator, 'BookkeepingMt', vStrDef).
 6455exactlyAssertedEL_next(backchainForbidden, myCreationTime, 'CoreCycLImplementationMt', vStrMon).
 6456exactlyAssertedEL_next(backchainForbidden, myCreationTime, 'BookkeepingMt', vStrDef).
 6457exactlyAssertedEL_next(backchainForbidden, myCreationSecond, 'CoreCycLImplementationMt', vStrMon).
 6458exactlyAssertedEL_next(backchainForbidden, myCreationSecond, 'BookkeepingMt', vStrDef).
 6459exactlyAssertedEL_next(backchainForbidden, myCreationPurpose, 'UniversalVocabularyMt', vStrDef).
 6460exactlyAssertedEL_next(backchainForbidden, myCreationPurpose, 'CoreCycLImplementationMt', vStrMon).
 6461exactlyAssertedEL_next(backchainForbidden, mtVisible, 'UniversalVocabularyMt', vStrMon).
 6462exactlyAssertedEL_next(backchainForbidden, knownSentence, 'UniversalVocabularyMt', vStrMon).
 6463exactlyAssertedEL_next(backchainForbidden, knownSentence, 'CoreCycLImplementationMt', vStrMon).
 6464exactlyAssertedEL_next(backchainForbidden, integerBetween, 'UniversalVocabularyMt', vStrMon).
 6465exactlyAssertedEL_next(backchainForbidden, integerBetween, 'CoreCycLImplementationMt', vStrMon).
 6466exactlyAssertedEL_next(backchainForbidden, instanceElementType, 'UniversalVocabularyMt', vStrDef).
 6467exactlyAssertedEL_next(backchainForbidden, indexicalReferent, 'UniversalVocabularyMt', vStrMon).
 6468exactlyAssertedEL_next(backchainForbidden, hypotheticalTerm, 'UniversalVocabularyMt', vStrDef).
 6469exactlyAssertedEL_next(backchainForbidden, formulaArity, 'UniversalVocabularyMt', vStrDef).
 6470exactlyAssertedEL_next(backchainForbidden, formulaArity, 'BaseKB', vStrMon).
 6471exactlyAssertedEL_next(backchainForbidden, extentCardinality, 'UniversalVocabularyMt', vStrMon).
 6472exactlyAssertedEL_next(backchainForbidden, exactlyAssertedEL_next, 'UniversalVocabularyMt', vStrDef).
 6473exactlyAssertedEL_next(backchainForbidden, exactlyAssertedEL_next, 'CoreCycLImplementationMt', vStrMon).
 6474exactlyAssertedEL_next(backchainForbidden, evaluate, 'UniversalVocabularyMt', vStrDef).
 6475exactlyAssertedEL_next(backchainForbidden, evaluate, 'CoreCycLImplementationMt', vStrMon).
 6476exactlyAssertedEL_next(backchainForbidden, equalSymbols, 'UniversalVocabularyMt', vStrDef).
 6477exactlyAssertedEL_next(backchainForbidden, equalSymbols, 'CoreCycLImplementationMt', vStrMon).
 6478exactlyAssertedEL_next(backchainForbidden, elInverse, 'UniversalVocabularyMt', vStrDef).
 6479exactlyAssertedEL_next(backchainForbidden, differentSymbols, 'UniversalVocabularyMt', vStrMon).
 6480exactlyAssertedEL_next(backchainForbidden, differentSymbols, 'CoreCycLImplementationMt', vStrMon).
 6481exactlyAssertedEL_next(backchainForbidden, different, 'CoreCycLImplementationMt', vStrMon).
 6482exactlyAssertedEL_next(backchainForbidden, definingMt, 'UniversalVocabularyMt', vStrDef).
 6483exactlyAssertedEL_next(backchainForbidden, cycTransformationProofRule, 'UniversalVocabularyMt', vStrDef).
 6484exactlyAssertedEL_next(backchainForbidden, cycTransformationProofRule, 'BaseKB', vStrMon).
 6485exactlyAssertedEL_next(backchainForbidden, cycTransformationProofBindings, 'UniversalVocabularyMt', vStrDef).
 6486exactlyAssertedEL_next(backchainForbidden, cycTransformationProofBindings, 'BaseKB', vStrMon).
 6487exactlyAssertedEL_next(backchainForbidden, cycTacticID, 'BaseKB', vStrMon).
 6488exactlyAssertedEL_next(backchainForbidden, cycProofID, 'BaseKB', vStrMon).
 6489exactlyAssertedEL_next(backchainForbidden, cycProblemStoreTerms, 'UniversalVocabularyMt', vStrDef).
 6490exactlyAssertedEL_next(backchainForbidden, cycProblemStoreTerms, 'BaseKB', vStrMon).
 6491exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProofs, 'BaseKB', vStrMon).
 6492exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProofCount, 'UniversalVocabularyMt', vStrDef).
 6493exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProofCount, 'BaseKB', vStrMon).
 6494exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProblems, 'UniversalVocabularyMt', vStrDef).
 6495exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProblems, 'BaseKB', vStrMon).
 6496exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProblemCount, 'UniversalVocabularyMt', vStrDef).
 6497exactlyAssertedEL_next(backchainForbidden, cycProblemStoreProblemCount, 'BaseKB', vStrMon).
 6498exactlyAssertedEL_next(backchainForbidden, cycProblemStoreLinks, 'BaseKB', vStrMon).
 6499exactlyAssertedEL_next(backchainForbidden, cycProblemStoreLinkCount, 'UniversalVocabularyMt', vStrDef).
 6500exactlyAssertedEL_next(backchainForbidden, cycProblemStoreLinkCount, 'BaseKB', vStrMon).
 6501exactlyAssertedEL_next(backchainForbidden, cycProblemStoreInferences, 'BaseKB', vStrMon).
 6502exactlyAssertedEL_next(backchainForbidden, cycProblemStoreInferenceCount, 'UniversalVocabularyMt', vStrDef).
 6503exactlyAssertedEL_next(backchainForbidden, cycProblemStoreInferenceCount, 'BaseKB', vStrMon).
 6504exactlyAssertedEL_next(backchainForbidden, cycProblemStoreID, 'BaseKB', vStrMon).
 6505exactlyAssertedEL_next(backchainForbidden, cycProblemQueryTerms, 'UniversalVocabularyMt', vStrDef).
 6506exactlyAssertedEL_next(backchainForbidden, cycProblemQueryTerms, 'BaseKB', vStrMon).
 6507exactlyAssertedEL_next(backchainForbidden, cycProblemQuerySentence, 'UniversalVocabularyMt', vStrDef).
 6508exactlyAssertedEL_next(backchainForbidden, cycProblemQuerySentence, 'BaseKB', vStrMon).
 6509exactlyAssertedEL_next(backchainForbidden, cycProblemProvabilityStatus, 'UniversalVocabularyMt', vStrDef).
 6510exactlyAssertedEL_next(backchainForbidden, cycProblemProvabilityStatus, 'BaseKB', vStrMon).
 6511exactlyAssertedEL_next(backchainForbidden, cycProblemLinkID, 'BaseKB', vStrMon).
 6512exactlyAssertedEL_next(backchainForbidden, cycProblemID, 'BaseKB', vStrMon).
 6513exactlyAssertedEL_next(backchainForbidden, cycProblemDependentLinks, 'BaseKB', vStrMon).
 6514exactlyAssertedEL_next(backchainForbidden, cycProblemArgumentLinks, 'BaseKB', vStrMon).
 6515exactlyAssertedEL_next(backchainForbidden, cycInferenceRelevantProblems, 'BaseKB', vStrMon).
 6516exactlyAssertedEL_next(backchainForbidden, cycInferenceAnswerLink, 'BaseKB', vStrMon).
 6517exactlyAssertedEL_next(backchainForbidden, constantName, 'UniversalVocabularyMt', vStrDef).
 6518exactlyAssertedEL_next(backchainForbidden, constantName, 'CoreCycLImplementationMt', vStrMon).
 6519exactlyAssertedEL_next(backchainForbidden, constantID, 'UniversalVocabularyMt', vStrDef).
 6520exactlyAssertedEL_next(backchainForbidden, constantID, 'CoreCycLImplementationMt', vStrMon).
 6521exactlyAssertedEL_next(backchainForbidden, constantGUID, 'UniversalVocabularyMt', vStrDef).
 6522exactlyAssertedEL_next(backchainForbidden, constantGUID, 'CoreCycLImplementationMt', vStrMon).
 6523exactlyAssertedEL_next(backchainForbidden, consistent, 'UniversalVocabularyMt', vStrMon).
 6524exactlyAssertedEL_next(backchainForbidden, conceptuallyRelated, 'UniversalVocabularyMt', vStrMon).
 6525exactlyAssertedEL_next(backchainForbidden, comment, 'UniversalVocabularyMt', vStrDef).
 6526exactlyAssertedEL_next(backchainForbidden, collectionIsaBackchainRequired, 'UniversalVocabularyMt', vStrDef).
 6527exactlyAssertedEL_next(backchainForbidden, collectionIsaBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6528exactlyAssertedEL_next(backchainForbidden, collectionGenlsBackchainRequired, 'UniversalVocabularyMt', vStrDef).
 6529exactlyAssertedEL_next(backchainForbidden, collectionGenlsBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6530exactlyAssertedEL_next(backchainForbidden, collectionBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6531exactlyAssertedEL_next(backchainForbidden, backchainRequired, 'UniversalVocabularyMt', vStrDef).
 6532exactlyAssertedEL_next(backchainForbidden, backchainForbiddenWhenUnboundInArg, 'UniversalVocabularyMt', vStrDef).
 6533exactlyAssertedEL_next(backchainForbidden, backchainForbidden, 'UniversalVocabularyMt', vStrDef).
 6534exactlyAssertedEL_next(backchainForbidden, backchainForbidden, 'BaseKB', vStrMon).
 6535exactlyAssertedEL_next(backchainForbidden, assertionDirection, 'UniversalVocabularyMt', vStrDef).
 6536exactlyAssertedEL_next(backchainForbidden, assertionDirection, 'BaseKB', vStrMon).
 6537exactlyAssertedEL_next(backchainForbidden, assertedTermSentences, 'UniversalVocabularyMt', vStrDef).
 6538exactlyAssertedEL_next(backchainForbidden, assertedTermSentences, 'CoreCycLImplementationMt', vStrMon).
 6539exactlyAssertedEL_next(backchainForbidden, knownSentence, 'UniversalVocabularyMt', vStrDef).
 6540exactlyAssertedEL_next(backchainForbidden, knownSentence, 'CoreCycLImplementationMt', vStrMon).
 6541exactlyAssertedEL_next(backchainForbidden, assertedPredicateArg, 'UniversalVocabularyMt', vStrDef).
 6542exactlyAssertedEL_next(backchainForbidden, assertedPredicateArg, 'CoreCycLImplementationMt', vStrMon).
 6543exactlyAssertedEL_next(backchainForbidden, admittedSentence, 'UniversalVocabularyMt', vStrDef).
 6544exactlyAssertedEL_next(backchainForbidden, admittedSentence, 'CoreCycLImplementationMt', vStrMon).
 6545exactlyAssertedEL_next(backchainForbidden, admittedNAT, 'BaseKB', vStrMon).
 6546exactlyAssertedEL_next(backchainForbidden, admittedArgument, 'UniversalVocabularyMt', vStrDef).
 6547exactlyAssertedEL_next(backchainForbidden, admittedArgument, 'CoreCycLImplementationMt', vStrMon).
 6548exactlyAssertedEL_next(backchainForbidden, admittedAllArgument, 'BaseKB', vStrMon).
 6549exactlyAssertedEL_next(backchainForbidden, 'ist-Asserted', 'UniversalVocabularyMt', vStrDef).
 6550exactlyAssertedEL_next(backchainForbidden, 'ist-Asserted', 'CoreCycLImplementationMt', vStrMon).
 6551exactlyAssertedEL_next(backchainForbidden, 'equalStrings-CaseInsensitive', 'UniversalVocabularyMt', vStrMon).
 6552exactlyAssertedEL_next(backchainForbidden, 'equalStrings-CaseInsensitive', 'CoreCycLImplementationMt', vStrMon).
 6553exactlyAssertedEL_next(opaqueArgument, conceptuallyRelated, 2, 'UniversalVocabularyMt', vStrMon).
 6554exactlyAssertedEL_next(opaqueArgument, conceptuallyRelated, 1, 'UniversalVocabularyMt', vStrMon).
 6555exactlyAssertedEL_next(omitArgIsa, thereExists, 2, 'UniversalVocabularyMt', vStrDef).
 6556exactlyAssertedEL_next(omitArgIsa, thereExists, 1, 'UniversalVocabularyMt', vStrDef).
 6557exactlyAssertedEL_next(omitArgIsa, forAll, 2, 'UniversalVocabularyMt', vStrDef).
 6558exactlyAssertedEL_next(omitArgIsa, forAll, 1, 'UniversalVocabularyMt', vStrDef).
 6559exactlyAssertedEL_next(omitArgIsa, 'SubLQuoteFn', 1, 'UniversalVocabularyMt', vStrMon).
 6560
 6561exactlyAssertedEL_next(notAssertibleMt, 'LogicalTruthMt', 'UniversalVocabularyMt', vStrMon).
 6562exactlyAssertedEL_next(notAssertibleMt, 'InferencePSC', 'UniversalVocabularyMt', vStrMon).
 6563exactlyAssertedEL_next(notAssertibleMt, 'EverythingPSC', 'UniversalVocabularyMt', vStrMon).
 6564exactlyAssertedEL_next(notAssertibleCollection, 'ELRelation', 'UniversalVocabularyMt', vStrDef).
 6565exactlyAssertedEL_next(notAssertibleCollection, 'CycLTruthValueSentence', 'UniversalVocabularyMt', vStrMon).
 6566exactlyAssertedEL_next(notAssertibleCollection, 'CanonicalizerDirective', 'BookkeepingMt', vStrMon).
 6567exactlyAssertedEL_next(notAssertible, unknownSentence, 'BaseKB', vStrMon).
 6568exactlyAssertedEL_next(notAssertible, trueSubL, 'BaseKB', vStrMon).
 6569exactlyAssertedEL_next(notAssertible, trueSentence, 'BaseKB', vStrMon).
 6570exactlyAssertedEL_next(notAssertible, termExternalIDString, 'UniversalVocabularyMt', vStrMon).
 6571exactlyAssertedEL_next(notAssertible, termChosen, 'BaseKB', vStrMon).
 6572exactlyAssertedEL_next(notAssertible, sentenceTruth, 'UniversalVocabularyMt', vStrMon).
 6573exactlyAssertedEL_next(notAssertible, sentenceImplies, 'BaseKB', vStrMon).
 6574exactlyAssertedEL_next(notAssertible, sentenceEquiv, 'BaseKB', vStrMon).
 6575exactlyAssertedEL_next(notAssertible, relationExpansion, 'BaseKB', vStrMon).
 6576exactlyAssertedEL_next(notAssertible, querySentence, 'UniversalVocabularyMt', vStrMon).
 6577exactlyAssertedEL_next(notAssertible, operatorFormulas, 'BaseKB', vStrMon).
 6578exactlyAssertedEL_next(notAssertible, nearestIsa, 'BaseKB', vStrMon).
 6579exactlyAssertedEL_next(notAssertible, nearestGenls, 'BaseKB', vStrMon).
 6580exactlyAssertedEL_next(notAssertible, nearestGenlPreds, 'BaseKB', vStrMon).
 6581exactlyAssertedEL_next(notAssertible, nearestGenlMt, 'BaseKB', vStrMon).
 6582exactlyAssertedEL_next(notAssertible, nearestDifferentIsa, 'BaseKB', vStrMon).
 6583exactlyAssertedEL_next(notAssertible, nearestDifferentGenls, 'BaseKB', vStrMon).
 6584exactlyAssertedEL_next(notAssertible, nearestCommonSpecs, 'BaseKB', vStrMon).
 6585exactlyAssertedEL_next(notAssertible, nearestCommonIsa, 'BaseKB', vStrMon).
 6586exactlyAssertedEL_next(notAssertible, nearestCommonGenls, 'BaseKB', vStrMon).
 6587exactlyAssertedEL_next(notAssertible, nearestCommonGenlMt, 'BaseKB', vStrMon).
 6588exactlyAssertedEL_next(notAssertible, natFunction, 'BaseKB', vStrMon).
 6589exactlyAssertedEL_next(notAssertible, natArgumentsEqual, 'BaseKB', vStrMon).
 6590exactlyAssertedEL_next(notAssertible, natArgument, 'BaseKB', vStrMon).
 6591exactlyAssertedEL_next(notAssertible, knownSentence, 'BaseKB', vStrMon).
 6592exactlyAssertedEL_next(notAssertible, integerBetween, 'BaseKB', vStrMon).
 6593exactlyAssertedEL_next(notAssertible, genlCanonicalizerDirectives, 'CoreCycLImplementationMt', vStrMon).
 6594exactlyAssertedEL_next(notAssertible, forwardNonTriggerLiteral, 'UniversalVocabularyMt', vStrMon).
 6595exactlyAssertedEL_next(notAssertible, exactlyAssertedEL_next, 'BaseKB', vStrMon).
 6596exactlyAssertedEL_next(notAssertible, evaluate, 'CoreCycLImplementationMt', vStrMon).
 6597exactlyAssertedEL_next(notAssertible, cycTransformationProofRule, 'BaseKB', vStrMon).
 6598exactlyAssertedEL_next(notAssertible, cycTransformationProofBindings, 'BaseKB', vStrMon).
 6599exactlyAssertedEL_next(notAssertible, constantID, 'BaseKB', vStrMon).
 6600exactlyAssertedEL_next(notAssertible, constantGUID, 'UniversalVocabularyMt', vStrMon).
 6601exactlyAssertedEL_next(notAssertible, consistent, 'BaseKB', vStrMon).
 6602exactlyAssertedEL_next(notAssertible, knownSentence, 'BaseKB', vStrMon).
 6603exactlyAssertedEL_next(notAssertible, assertedPredicateArg, 'BaseKB', vStrMon).
 6604exactlyAssertedEL_next(notAssertible, admittedSentence, 'BaseKB', vStrMon).
 6605exactlyAssertedEL_next(notAssertible, admittedNAT, 'BaseKB', vStrMon).
 6606exactlyAssertedEL_next(notAssertible, admittedArgument, 'BaseKB', vStrMon).
 6607exactlyAssertedEL_next(notAssertible, admittedAllArgument, 'BaseKB', vStrMon).
 6608exactlyAssertedEL_next(notAssertible, 'ist-Asserted', 'BaseKB', vStrMon).
 6609
 6610exactlyAssertedEL_next(predicateConventionMt, termOfUnit, 'BaseKB', 'BaseKB', vStrDef).
 6611exactlyAssertedEL_next(predicateConventionMt, quotedArgument, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 6612exactlyAssertedEL_next(predicateConventionMt, predicateConventionMt, 'BaseKB', 'UniversalVocabularyMt', vStrMon).
 6613exactlyAssertedEL_next(predicateConventionMt, predicateConventionMt, 'BaseKB', 'BaseKB', vStrMon).
 6614exactlyAssertedEL_next(predicateConventionMt, notAssertibleMt, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 6615exactlyAssertedEL_next(predicateConventionMt, nearestGenlMt, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 6616exactlyAssertedEL_next(predicateConventionMt, ist, 'BaseKB', 'BaseKB', vStrMon).
 6617exactlyAssertedEL_next(predicateConventionMt, genlMt, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 6618exactlyAssertedEL_next(predicateConventionMt, definingMt, 'BaseKB', 'BaseKB', vStrMon).
 6619exactlyAssertedEL_next(predicateConventionMt, decontextualizedPredicate, 'BaseKB', 'BaseKB', vStrMon).
 6620exactlyAssertedEL_next(predicateConventionMt, decontextualizedCollection, 'BaseKB', 'BaseKB', vStrDef).
 6621exactlyAssertedEL_next(predicateConventionMt, collectionConventionMt, 'BaseKB', 'BaseKB', vStrMon).
 6622exactlyAssertedEL_next(predicateConventionMt, canonicalizerDirectiveForArgAndRest, 'UniversalVocabularyImplementationMt', 'BaseKB', vStrMon).
 6623exactlyAssertedEL_next(predicateConventionMt, canonicalizerDirectiveForArg, 'UniversalVocabularyImplementationMt', 'BaseKB', vStrMon).
 6624exactlyAssertedEL_next(predicateConventionMt, canonicalizerDirectiveForAllArgs, 'UniversalVocabularyImplementationMt', 'BaseKB', vStrMon).
 6625exactlyAssertedEL_next(predicateConventionMt, assertionDirection, 'BaseKB', 'BaseKB', vStrMon).
 6626exactlyAssertedEL_next(predicateConventionMt, arityMin, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 6627exactlyAssertedEL_next(predicateConventionMt, arityMax, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 6628exactlyAssertedEL_next(predicateConventionMt, arity, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 6629exactlyAssertedEL_next(predicateConventionMt, 'ist-Asserted', 'BaseKB', 'BaseKB', vStrMon).
 6630exactlyAssertedEL_next(openEntryFormatInArgs, rewriteOf, 2, 'UniversalVocabularyMt', vStrDef).
 6631exactlyAssertedEL_next(openEntryFormatInArgs, pointQuantValue, 1, 'UniversalVocabularyMt', vStrDef).
 6632exactlyAssertedEL_next(openEntryFormatInArgs, operatorFormulas, 2, 'UniversalVocabularyMt', vStrMon).
 6633exactlyAssertedEL_next(openEntryFormatInArgs, myCreationPurpose, 1, 'BookkeepingMt', vStrDef).
 6634exactlyAssertedEL_next(openEntryFormatInArgs, minQuantValue, 1, 'UniversalVocabularyMt', vStrDef).
 6635exactlyAssertedEL_next(openEntryFormatInArgs, maxQuantValue, 1, 'UniversalVocabularyMt', vStrDef).
 6636exactlyAssertedEL_next(openEntryFormatInArgs, followingValue, 2, 'UniversalVocabularyMt', vStrDef).
 6637exactlyAssertedEL_next(openEntryFormatInArgs, followingValue, 1, 'UniversalVocabularyMt', vStrDef).
 6638exactlyAssertedEL_next(openEntryFormatInArgs, expresses, 1, 'UniversalVocabularyMt', vStrDef).
 6639exactlyAssertedEL_next(openEntryFormatInArgs, evaluationDefn, 1, 'UniversalVocabularyMt', vStrDef).
 6640exactlyAssertedEL_next(openEntryFormatInArgs, cycTransformationProofBindings, 2, 'UniversalVocabularyMt', vStrDef).
 6641exactlyAssertedEL_next(openEntryFormatInArgs, completelyEnumerableCollection, 1, 'UniversalVocabularyMt', vStrMon).
 6642exactlyAssertedEL_next(openEntryFormatInArgs, completelyDecidableCollection, 1, 'UniversalVocabularyMt', vStrMon).
 6643exactlyAssertedEL_next(openEntryFormatInArgs, completeExtentEnumerable, 1, 'UniversalVocabularyMt', vStrDef).
 6644exactlyAssertedEL_next(openEntryFormatInArgs, completeExtentDecidable, 1, 'UniversalVocabularyMt', vStrDef).
 6645exactlyAssertedEL_next(openEntryFormatInArgs, completeExtentAsserted, 1, 'UniversalVocabularyMt', vStrDef).
 6646exactlyAssertedEL_next(openEntryFormatInArgs, argSometimesIsa, 3, 'UniversalVocabularyMt', vStrMon).
 6647exactlyAssertedEL_next(openEntryFormatInArgs, argSometimesIsa, 2, 'UniversalVocabularyMt', vStrMon).
 6648exactlyAssertedEL_next(openEntryFormatInArgs, argSometimesIsa, 1, 'UniversalVocabularyMt', vStrMon).
 6649exactlyAssertedEL_next(openEntryFormatInArgs, admittedAllArgument, 3, 'UniversalVocabularyMt', vStrMon).
 6650exactlyAssertedEL_next(openEntryFormatInArgs, admittedAllArgument, 2, 'UniversalVocabularyMt', vStrMon).
 6651exactlyAssertedEL_next(openEntryFormatInArgs, admittedAllArgument, 1, 'UniversalVocabularyMt', vStrMon).
 6652
 6653exactlyAssertedEL_next(oldConstantName, unknownSentence, "unknownFormula", 'BookkeepingMt', vStrDef).
 6654exactlyAssertedEL_next(oldConstantName, trueSentence, "trueFormula", 'BookkeepingMt', vStrDef).
 6655exactlyAssertedEL_next(oldConstantName, thereExists, "ThereExists", 'BookkeepingMt', vStrDef).
 6656exactlyAssertedEL_next(oldConstantName, thereExistExactly, "ThereExistExactly", 'BookkeepingMt', vStrDef).
 6657exactlyAssertedEL_next(oldConstantName, thereExistAtMost, "ThereExistAtMost", 'BookkeepingMt', vStrDef).
 6658exactlyAssertedEL_next(oldConstantName, thereExistAtLeast, "ThereExistAtLeast", 'BookkeepingMt', vStrDef).
 6659exactlyAssertedEL_next(oldConstantName, sentenceImplies, "formulaImplies", 'BookkeepingMt', vStrDef).
 6660exactlyAssertedEL_next(oldConstantName, sentenceEquiv, "formulaEquiv", 'BookkeepingMt', vStrDef).
 6661exactlyAssertedEL_next(oldConstantName, sentenceDesignationArgnum, "formulaDesignationArgnum", 'BookkeepingMt', vStrDef).
 6662exactlyAssertedEL_next(oldConstantName, resultIsa, "resultType", 'BookkeepingMt', vStrDef).
 6663exactlyAssertedEL_next(oldConstantName, resultGenl, "usesAreSpecsOf", 'BookkeepingMt', vStrDef).
 6664exactlyAssertedEL_next(oldConstantName, relationAllExistsCount, "relationTypeCount", 'BookkeepingMt', vStrDef).
 6665exactlyAssertedEL_next(oldConstantName, pragmaticRequirement, "pragmaticImplies", 'BookkeepingMt', vStrDef).
 6666exactlyAssertedEL_next(oldConstantName, or, "LogOr", 'BookkeepingMt', vStrDef).
 6667exactlyAssertedEL_next(oldConstantName, numericallyEquals, "numericallyEqual", 'BookkeepingMt', vStrDef).
 6668exactlyAssertedEL_next(oldConstantName, not, "LogNot", 'BookkeepingMt', vStrDef).
 6669exactlyAssertedEL_next(oldConstantName, knownSentence, "knownFormula", 'BookkeepingMt', vStrDef).
 6670exactlyAssertedEL_next(oldConstantName, isa, "instanceOf", 'BookkeepingMt', vStrDef).
 6671exactlyAssertedEL_next(oldConstantName, interArgResultGenl, "interArgResultGenls", 'BookkeepingMt', vStrDef).
 6672exactlyAssertedEL_next(oldConstantName, implies, "LogImplication", 'BookkeepingMt', vStrDef).
 6673exactlyAssertedEL_next(oldConstantName, genlMt, "baseMt", 'BookkeepingMt', vStrDef).
 6674exactlyAssertedEL_next(oldConstantName, forAll, "ForAll", 'BookkeepingMt', vStrDef).
 6675exactlyAssertedEL_next(oldConstantName, except, "exceptedAssertion", 'BookkeepingMt', vStrDef).
 6676exactlyAssertedEL_next(oldConstantName, evaluationDefn, "lispDefun", 'BookkeepingMt', vStrDef).
 6677exactlyAssertedEL_next(oldConstantName, equalSymbols, "equals-Symbols", 'BookkeepingMt', vStrDef).
 6678exactlyAssertedEL_next(oldConstantName, disjointWith, "mutuallyDisjointWith", 'BookkeepingMt', vStrDef).
 6679exactlyAssertedEL_next(oldConstantName, differentSymbols, "different-Symbols", 'BookkeepingMt', vStrDef).
 6680exactlyAssertedEL_next(oldConstantName, defnSufficient, "defn", 'BookkeepingMt', vStrDef).
 6681exactlyAssertedEL_next(oldConstantName, defnIff, "necessaryDefn", 'BookkeepingMt', vStrDef).
 6682exactlyAssertedEL_next(oldConstantName, conceptuallyRelated, "mysteryLink", 'BookkeepingMt', vStrDef).
 6683exactlyAssertedEL_next(oldConstantName, completelyEnumerableCollection, "completeCollectionExtent", 'BookkeepingMt', vStrDef).
 6684exactlyAssertedEL_next(oldConstantName, completeExtentEnumerableForValueInArg, "completeExtentKnownForArg", 'BookkeepingMt', vStrDef).
 6685exactlyAssertedEL_next(oldConstantName, completeExtentEnumerable, "completeExtentKnown", 'BookkeepingMt', vStrDef).
 6686exactlyAssertedEL_next(oldConstantName, commutativeInArgs, "symmetricInArgs", 'BookkeepingMt', vStrMon).
 6687exactlyAssertedEL_next(oldConstantName, comment, "english", 'BookkeepingMt', vStrDef).
 6688exactlyAssertedEL_next(oldConstantName, collectionCompletelyEnumerableViaBackchain, "collectionCompletelyEnumerableViaBackchains", 'BookkeepingMt', vStrDef).
 6689exactlyAssertedEL_next(oldConstantName, assertedTermSentences, "assertedTermFormulas", 'BookkeepingMt', vStrDef).
 6690exactlyAssertedEL_next(oldConstantName, knownSentence, "assertedFormula", 'BookkeepingMt', vStrDef).
 6691exactlyAssertedEL_next(oldConstantName, arity, "expressionArity", 'BookkeepingMt', vStrDef).
 6692exactlyAssertedEL_next(oldConstantName, argsIsa, "argumentTypes", 'BookkeepingMt', vStrDef).
 6693exactlyAssertedEL_next(oldConstantName, arg5Isa, "argumentFiveType", 'BookkeepingMt', vStrDef).
 6694exactlyAssertedEL_next(oldConstantName, arg4Isa, "argumentFourType", 'BookkeepingMt', vStrDef).
 6695exactlyAssertedEL_next(oldConstantName, arg3Isa, "argumentThreeType", 'BookkeepingMt', vStrDef).
 6696exactlyAssertedEL_next(oldConstantName, arg3Genl, "argumentThreeGenls", 'BookkeepingMt', vStrDef).
 6697exactlyAssertedEL_next(oldConstantName, arg2Isa, "argumentTwoType", 'BookkeepingMt', vStrDef).
 6698exactlyAssertedEL_next(oldConstantName, arg2Genl, "argumentTwoGenls", 'BookkeepingMt', vStrDef).
 6699exactlyAssertedEL_next(oldConstantName, arg1Isa, "argumentOneType", 'BookkeepingMt', vStrDef).
 6700exactlyAssertedEL_next(oldConstantName, arg1Genl, "argumentOneGenls", 'BookkeepingMt', vStrDef).
 6701exactlyAssertedEL_next(oldConstantName, and, "LogAnd", 'BookkeepingMt', vStrDef).
 6702exactlyAssertedEL_next(oldConstantName, admittedSentence, "admittedFormula", 'BookkeepingMt', vStrDef).
 6703exactlyAssertedEL_next(oldConstantName, 'Unknown-HLTruthValue', "Unknown-TruthValue", 'BookkeepingMt', vStrDef).
 6704exactlyAssertedEL_next(oldConstantName, 'TransitiveBinaryPredicate', "TransitiveSlot", 'BookkeepingMt', vStrDef).
 6705exactlyAssertedEL_next(oldConstantName, 'TimesFn', "Times", 'BookkeepingMt', vStrDef).
 6706exactlyAssertedEL_next(oldConstantName, 'SubLSymbol', "LispSymbol", 'BookkeepingMt', vStrDef).
 6707exactlyAssertedEL_next(oldConstantName, 'SubLSymbol', "CycSystemSymbol", 'BookkeepingMt', vStrDef).
 6708exactlyAssertedEL_next(oldConstantName, 'SubLString', "CycSystemString", 'BookkeepingMt', vStrDef).
 6709exactlyAssertedEL_next(oldConstantName, 'SubLSExpression', "SubLExpression", 'BookkeepingMt', vStrDef).
 6710exactlyAssertedEL_next(oldConstantName, 'SubLRealNumber', "LispRealNumber", 'BookkeepingMt', vStrDef).
 6711exactlyAssertedEL_next(oldConstantName, 'SubLRealNumber', "CycSystemRealNumber", 'BookkeepingMt', vStrDef).
 6712exactlyAssertedEL_next(oldConstantName, 'SubLList', "CycSystemList", 'BookkeepingMt', vStrDef).
 6713exactlyAssertedEL_next(oldConstantName, 'SubLKeyword', "CycSystemKeyword", 'BookkeepingMt', vStrDef).
 6714exactlyAssertedEL_next(oldConstantName, 'SubLInteger', "CycSystemInteger", 'BookkeepingMt', vStrDef).
 6715exactlyAssertedEL_next(oldConstantName, 'SubLAtom', "LispAtom", 'BookkeepingMt', vStrDef).
 6716exactlyAssertedEL_next(oldConstantName, 'SubLAtom', "CycSystemAtom", 'BookkeepingMt', vStrDef).
 6717exactlyAssertedEL_next(oldConstantName, 'SiblingDisjointAttributeType', "MutuallyDisjointAttributeType", 'BookkeepingMt', vStrDef).
 6718exactlyAssertedEL_next(oldConstantName, 'SententialRelation', "NonPredicateTruthFunction", 'BookkeepingMt', vStrDef).
 6719exactlyAssertedEL_next(oldConstantName, tRelation, "Relationship", 'BookkeepingMt', vStrDef).
 6720exactlyAssertedEL_next(oldConstantName, 'QuotientFn', "Quotient", 'BookkeepingMt', vStrDef).
 6721exactlyAssertedEL_next(oldConstantName, 'PlusFn', "Plus", 'BookkeepingMt', vStrDef).
 6722exactlyAssertedEL_next(oldConstantName, 'MtTimeWithGranularityDimFn', "MtTimeDimWithGranularityFn", 'BookkeepingMt', vStrDef).
 6723exactlyAssertedEL_next(oldConstantName, 'LogicalTruthImplementationMt', "CycInferenceMt", 'BookkeepingMt', vStrDef).
 6724exactlyAssertedEL_next(oldConstantName, 'LogFn', "Log", 'BookkeepingMt', vStrDef).
 6725exactlyAssertedEL_next(oldConstantName, 'List', "List", 'BookkeepingMt', vStrDef).
 6726exactlyAssertedEL_next(oldConstantName, 'LeaveSomeTermsAtELAndAllowKeywordVariables', "CanonicalizeForNL", 'BookkeepingMt', vStrDef).
 6727exactlyAssertedEL_next(oldConstantName, 'IntervalMinFn', "IntervalMin", 'BookkeepingMt', vStrDef).
 6728exactlyAssertedEL_next(oldConstantName, 'IntervalMaxFn', "IntervalMax", 'BookkeepingMt', vStrDef).
 6729exactlyAssertedEL_next(oldConstantName, 'InferencePSC', "ForwardInferencePSC", 'BookkeepingMt', vStrDef).
 6730exactlyAssertedEL_next(oldConstantName, 'HLAssertedArgumentKeywordDatastructure', "HLAssertedArgumentKeyword", 'BookkeepingMt', vStrDef).
 6731exactlyAssertedEL_next(oldConstantName, 'FormulaArityFn', "RelationExpressionArityFn", 'BookkeepingMt', vStrDef).
 6732exactlyAssertedEL_next(oldConstantName, 'FormulaArgSetFn', "RelationArgSetFn", 'BookkeepingMt', vStrDef).
 6733exactlyAssertedEL_next(oldConstantName, 'FormulaArgListFn', "RelationArgsListFn", 'BookkeepingMt', vStrDef).
 6734exactlyAssertedEL_next(oldConstantName, 'FormulaArgFn', "RelationArgFn", 'BookkeepingMt', vStrDef).
 6735exactlyAssertedEL_next(oldConstantName, 'ExpFn', "Exp", 'BookkeepingMt', vStrDef).
 6736exactlyAssertedEL_next(oldConstantName, 'ExceptionPredicate', "ExceptionRelation", 'BookkeepingMt', vStrDef).
 6737exactlyAssertedEL_next(oldConstantName, 'EvaluatableRelation', "EvaluatableRelationship", 'BookkeepingMt', vStrDef).
 6738exactlyAssertedEL_next(oldConstantName, 'equalStrings-CaseInsensitive', "equals-CaseInsensitive", 'BookkeepingMt', vStrDef).
 6739exactlyAssertedEL_next(oldConstantName, 'ELRelation-Reversible', "ELRelation-SemiReversible", 'BookkeepingMt', vStrDef).
 6740exactlyAssertedEL_next(oldConstantName, 'DifferenceFn', "Difference", 'BookkeepingMt', vStrDef).
 6741exactlyAssertedEL_next(oldConstantName, 'CycSupportDatastructure', "CycLSupportDatastructure", 'BookkeepingMt', vStrDef).
 6742exactlyAssertedEL_next(oldConstantName, 'CycLTerm', "CycTerm", 'BookkeepingMt', vStrDef).
 6743exactlyAssertedEL_next(oldConstantName, 'CycLSentence', "CycSyntacticFormula", 'BookkeepingMt', vStrDef).
 6744exactlyAssertedEL_next(oldConstantName, 'CycLSentence', "ConstraintLanguageExpression", 'BookkeepingMt', vStrDef).
 6745exactlyAssertedEL_next(oldConstantName, 'CycLRuleAssertion', "RuleAssertion", 'BookkeepingMt', vStrDef).
 6746exactlyAssertedEL_next(oldConstantName, 'CycLReifiableNonAtomicTerm', "ReifiableNAT", 'BookkeepingMt', vStrDef).
 6747exactlyAssertedEL_next(oldConstantName, 'CycLReifiableDenotationalTerm', "ReifiableTerm", 'BookkeepingMt', vStrDef).
 6748exactlyAssertedEL_next(oldConstantName, 'CycLOpenExpression', "CycOpenTerm", 'BookkeepingMt', vStrDef).
 6749exactlyAssertedEL_next(oldConstantName, 'CycLNonAtomicTerm', "NonAtomicTerm", 'BookkeepingMt', vStrDef).
 6750exactlyAssertedEL_next(oldConstantName, 'CycLIndexedTerm', "CycIndexedTerm", 'BookkeepingMt', vStrDef).
 6751exactlyAssertedEL_next(oldConstantName, 'CycLGAFAssertion', "GAFAssertion", 'BookkeepingMt', vStrDef).
 6752exactlyAssertedEL_next(oldConstantName, 'CycLFormula', "RelationExpression", 'BookkeepingMt', vStrDef).
 6753exactlyAssertedEL_next(oldConstantName, 'CycLDeducedAssertion', "DeducedAssertion", 'BookkeepingMt', vStrDef).
 6754exactlyAssertedEL_next(oldConstantName, 'CycLConstant', "CycConstant", 'BookkeepingMt', vStrDef).
 6755exactlyAssertedEL_next(oldConstantName, 'CycLClosedExpression', "CycClosedTerm", 'BookkeepingMt', vStrDef).
 6756exactlyAssertedEL_next(oldConstantName, 'CycLAtomicSentence', "CycAtomicFormula", 'BookkeepingMt', vStrDef).
 6757exactlyAssertedEL_next(oldConstantName, 'CycLAssertion', "Assertion", 'BookkeepingMt', vStrDef).
 6758exactlyAssertedEL_next(oldConstantName, 'CycLAssertedAssertion', "AssertedAssertion", 'BookkeepingMt', vStrDef).
 6759exactlyAssertedEL_next(oldConstantName, 'CycKBDatastructure', "CycLKBDatastructure", 'BookkeepingMt', vStrDef).
 6760exactlyAssertedEL_next(oldConstantName, 'CycHLTruthValue', "CyclTruthValue", 'BookkeepingMt', vStrDef).
 6761exactlyAssertedEL_next(oldConstantName, 'CycDeductionDatastructure', "CycLDeductionDatastructure", 'BookkeepingMt', vStrDef).
 6762exactlyAssertedEL_next(oldConstantName, 'CycArgumentDatastructure', "CycLArgumentDatastructure", 'BookkeepingMt', vStrDef).
 6763exactlyAssertedEL_next(oldConstantName, 'CurrentWorldDataCollectorMt-NonHomocentric', "CurrentWorldDataCollectorMtt-NonHomocentric", 'BookkeepingMt', vStrDef).
 6764exactlyAssertedEL_next(oldConstantName, 'ArgGenlQuantityBinaryPredicate', "ArgGenlQuanityBinaryPredicate", 'BookkeepingMt', vStrDef).
 6765exactlyAssertedEL_next(oldConstantName, 'AbsoluteValueFn', "AbsoluteValue", 'BookkeepingMt', vStrDef).
 6766
 6767exactlyAssertedEL_next(negationPreds, unknownSentence, trueSentence, 'UniversalVocabularyMt', vStrMon).
 6768exactlyAssertedEL_next(negationPreds, unknownSentence, knownSentence, 'UniversalVocabularyMt', vStrMon).
 6769exactlyAssertedEL_next(negationPreds, unknownSentence, knownSentence, 'BaseKB', vStrMon).
 6770exactlyAssertedEL_next(negationPreds, highlyRelevantPredAssertion, irrelevantPredAssertion, 'UniversalVocabularyMt', vStrMon).
 6771exactlyAssertedEL_next(negationPreds, highlyRelevantMt, irrelevantMt, 'UniversalVocabularyMt', vStrMon).
 6772exactlyAssertedEL_next(negationPreds, highlyRelevantAssertion, irrelevantAssertion, 'UniversalVocabularyMt', vStrMon).
 6773exactlyAssertedEL_next(negationPreds, conceptuallyRelated, genls, 'UniversalVocabularyMt', vStrMon).
 6774exactlyAssertedEL_next(negationInverse, nearestGenlPreds, nearestGenlPreds, 'UniversalVocabularyMt', vStrDef).
 6775exactlyAssertedEL_next(negationInverse, nearestGenlMt, nearestGenlMt, 'UniversalVocabularyMt', vStrDef).
 6776exactlyAssertedEL_next(negationInverse, means, means, 'UniversalVocabularyMt', vStrMon).
 6777exactlyAssertedEL_next(negationInverse, greaterThan, greaterThan, 'UniversalVocabularyMt', vStrMon).
 6778exactlyAssertedEL_next(negationInverse, followingValue, followingValue, 'UniversalVocabularyMt', vStrMon).
 6779exactlyAssertedEL_next(negationInverse, elInverse, elInverse, 'UniversalVocabularyMt', vStrDef).
 6780exactlyAssertedEL_next(negationInverse, denotes, denotes, 'UniversalVocabularyMt', vStrDef).
 6781exactlyAssertedEL_next(negationInverse, conceptuallyRelated, isa, 'UniversalVocabularyMt', vStrMon).
 6782exactlyAssertedEL_next(negationInverse, conceptuallyRelated, genls, 'UniversalVocabularyMt', vStrMon).
 6783exactlyAssertedEL_next(multiplicationUnits, 'Unity', '$VAR'('UNIT'), '$VAR'('UNIT'), 'BaseKB', vStrMon).
 6784exactlyAssertedEL_next(minimizeExtent, termOfUnit, 'UniversalVocabularyMt', vStrDef).
 6785exactlyAssertedEL_next(minimizeExtent, natFunction, 'UniversalVocabularyMt', vStrDef).
 6786exactlyAssertedEL_next(minimizeExtent, isa, 'UniversalVocabularyMt', vStrDef).
 6787exactlyAssertedEL_next(minimizeExtent, genls, 'UniversalVocabularyMt', vStrDef).
 6788exactlyAssertedEL_next(minimizeExtent, genlPreds, 'UniversalVocabularyMt', vStrDef).
 6789exactlyAssertedEL_next(minimizeExtent, genlMt, 'UniversalVocabularyMt', vStrMon).
 6790exactlyAssertedEL_next(minimizeExtent, equals, 'UniversalVocabularyMt', vStrDef).
 6791exactlyAssertedEL_next(minimizeExtent, abnormal, 'UniversalVocabularyMt', vStrDef).
 6792exactlyAssertedEL_next(minimize, disjointWith('$VAR'('COL'), '$VAR'('COL')), 'BaseKB', vStrDef).
 6793exactlyAssertedEL_next(microtheoryDesignationArgnum, ist, 1, 'BaseKB', vStrDef).
 6794exactlyAssertedEL_next(microtheoryDesignationArgnum, 'TLAssertionFn', 1, 'BaseKB', vStrDef).
 6795exactlyAssertedEL_next(microtheoryDesignationArgnum, 'ist-Asserted', 1, 'BaseKB', vStrDef).
 6796
 6797exactlyAssertedEL_next(interArgResultIsa, 'RoundUpFn', 1, 'ScalarPointValue', 'ScalarPointValue', 'BaseKB', vStrMon).
 6798exactlyAssertedEL_next(interArgResultIsa, 'RoundUpFn', 1, 'RealNumber', 'Integer', 'BaseKB', vStrMon).
 6799exactlyAssertedEL_next(interArgResultIsa, 'RoundDownFn', 1, 'ScalarPointValue', 'ScalarPointValue', 'BaseKB', vStrMon).
 6800exactlyAssertedEL_next(interArgResultIsa, 'RoundDownFn', 1, 'RealNumber', 'Integer', 'BaseKB', vStrMon).
 6801exactlyAssertedEL_next(interArgResultIsa, 'RoundClosestFn', 1, 'ScalarPointValue', 'ScalarPointValue', 'BaseKB', vStrMon).
 6802exactlyAssertedEL_next(interArgResultIsa, 'RoundClosestFn', 1, 'RealNumber', 'Integer', 'BaseKB', vStrMon).
 6803exactlyAssertedEL_next(interArgResultIsa, 'ModuloFn', 1, 'Integer', 'NonNegativeInteger', 'BaseKB', vStrMon).
 6804exactlyAssertedEL_next(interArgResultIsa, 'IntervalMinFn', 1, 'NonNegativeScalarInterval', 'NonNegativeScalarInterval', 'BaseKB', vStrMon).
 6805exactlyAssertedEL_next(interArgResultIsa, 'FunctionToArg', 2, 'TernaryPredicate', 'BinaryFunction', 'BaseKB', vStrDef).
 6806exactlyAssertedEL_next(interArgResultIsa, 'FunctionToArg', 2, 'BinaryPredicate', 'UnaryFunction', 'BaseKB', vStrDef).
 6807exactlyAssertedEL_next(interArgDifferent, interArgDifferent, 2, 3, 'UniversalVocabularyMt', vStrMon).
 6808exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 4, 5, 'UniversalVocabularyMt', vStrMon).
 6809exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 3, 5, 'UniversalVocabularyMt', vStrMon).
 6810exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 3, 4, 'UniversalVocabularyMt', vStrMon).
 6811exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 2, 5, 'UniversalVocabularyMt', vStrMon).
 6812exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 2, 4, 'UniversalVocabularyMt', vStrMon).
 6813exactlyAssertedEL_next(interArgDifferent, commutativeInArgs, 2, 3, 'UniversalVocabularyMt', vStrMon).
 6814exactlyAssertedEL_next(instanceElementType, 'Set-Mathematical', 'Thing', 'BaseKB', vStrMon).
 6815exactlyAssertedEL_next(independentArg, 'interArgIsa5-4', 5, 'UniversalVocabularyMt', vStrDef).
 6816exactlyAssertedEL_next(independentArg, 'interArgIsa5-3', 5, 'UniversalVocabularyMt', vStrDef).
 6817exactlyAssertedEL_next(independentArg, 'interArgIsa5-2', 5, 'UniversalVocabularyMt', vStrDef).
 6818exactlyAssertedEL_next(independentArg, 'interArgIsa5-1', 5, 'UniversalVocabularyMt', vStrDef).
 6819exactlyAssertedEL_next(independentArg, 'interArgIsa4-5', 4, 'UniversalVocabularyMt', vStrDef).
 6820exactlyAssertedEL_next(independentArg, 'interArgIsa4-3', 4, 'UniversalVocabularyMt', vStrDef).
 6821exactlyAssertedEL_next(independentArg, 'interArgIsa4-2', 4, 'UniversalVocabularyMt', vStrDef).
 6822exactlyAssertedEL_next(independentArg, 'interArgIsa4-1', 4, 'UniversalVocabularyMt', vStrDef).
 6823exactlyAssertedEL_next(independentArg, 'interArgIsa3-5', 3, 'UniversalVocabularyMt', vStrDef).
 6824exactlyAssertedEL_next(independentArg, 'interArgIsa3-4', 3, 'UniversalVocabularyMt', vStrDef).
 6825exactlyAssertedEL_next(independentArg, 'interArgIsa3-2', 3, 'UniversalVocabularyMt', vStrDef).
 6826exactlyAssertedEL_next(independentArg, 'interArgIsa3-1', 3, 'UniversalVocabularyMt', vStrDef).
 6827exactlyAssertedEL_next(independentArg, 'interArgIsa2-5', 2, 'UniversalVocabularyMt', vStrDef).
 6828exactlyAssertedEL_next(independentArg, 'interArgIsa2-4', 2, 'UniversalVocabularyMt', vStrDef).
 6829exactlyAssertedEL_next(independentArg, 'interArgIsa2-3', 2, 'UniversalVocabularyMt', vStrDef).
 6830exactlyAssertedEL_next(independentArg, 'interArgIsa2-1', 2, 'UniversalVocabularyMt', vStrDef).
 6831exactlyAssertedEL_next(independentArg, 'interArgIsa1-5', 1, 'UniversalVocabularyMt', vStrDef).
 6832exactlyAssertedEL_next(independentArg, 'interArgIsa1-4', 1, 'UniversalVocabularyMt', vStrDef).
 6833exactlyAssertedEL_next(independentArg, 'interArgIsa1-3', 1, 'UniversalVocabularyMt', vStrDef).
 6834exactlyAssertedEL_next(independentArg, 'interArgIsa1-2', 1, 'UniversalVocabularyMt', vStrDef).
 6835exactlyAssertedEL_next(independentArg, 'interArgGenl1-2', 1, 'UniversalVocabularyMt', vStrDef).
 6836exactlyAssertedEL_next(independentArg, 'interArgFormat1-2', 1, 'UniversalVocabularyMt', vStrDef).
 6837exactlyAssertedEL_next(hlPrototypicalInstance, 'ThePrototypicalTransitiveBinaryPredicate', 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6838exactlyAssertedEL_next(hlPrototypicalInstance, 'ThePrototypicalCollection', tCol, 'UniversalVocabularyMt', vStrDef).
 6839exactlyAssertedEL_next(hlPrototypicalInstance, 'ThePrototypicalBinaryPredicate', 'BinaryPredicate', 'UniversalVocabularyMt', vStrDef).
 6840
 6841exactlyAssertedEL_first(genlPreds, trueSentence, consistent, 'UniversalVocabularyMt', vStrDef).
 6842exactlyAssertedEL_first(genlPreds, synonymousExternalConcept, overlappingExternalConcept, 'UniversalVocabularyMt', vStrDef).
 6843exactlyAssertedEL_first(genlPreds, siblingDisjointExceptions, different, 'UniversalVocabularyMt', vStrDef).
 6844exactlyAssertedEL_first(genlPreds, sentenceEquiv, sentenceImplies, 'UniversalVocabularyMt', vStrDef).
 6845exactlyAssertedEL_first(genlPreds, rewriteOf, equals, 'UniversalVocabularyMt', vStrDef).
 6846exactlyAssertedEL_first(genlPreds, relationAllExistsCount, relationAllExistsMin, 'UniversalVocabularyMt', vStrDef).
 6847exactlyAssertedEL_first(genlPreds, relationAllExistsCount, relationAllExistsMax, 'UniversalVocabularyMt', vStrDef).
 6848exactlyAssertedEL_first(genlPreds, reformulatorEquiv, reformulatorRule, 'UniversalVocabularyMt', vStrDef).
 6849exactlyAssertedEL_first(genlPreds, reformulatorEquals, reformulatorRule, 'UniversalVocabularyMt', vStrDef).
 6850exactlyAssertedEL_first(genlPreds, quotedArgument, opaqueArgument, 'UniversalVocabularyMt', vStrDef).
 6851exactlyAssertedEL_first(genlPreds, quantitySubsumes, quantityIntersects, 'UniversalVocabularyMt', vStrDef).
 6852exactlyAssertedEL_first(genlPreds, pointQuantValue, numericallyEquals, 'UniversalVocabularyMt', vStrDef).
 6853exactlyAssertedEL_first(genlPreds, pointQuantValue, minQuantValue, 'UniversalVocabularyMt', vStrDef).
 6854exactlyAssertedEL_first(genlPreds, pointQuantValue, maxQuantValue, 'UniversalVocabularyMt', vStrDef).
 6855exactlyAssertedEL_first(genlPreds, numericallyEquals, quantitySubsumes, 'UniversalVocabularyMt', vStrDef).
 6856exactlyAssertedEL_first(genlPreds, numericallyEquals, greaterThanOrEqualTo, 'UniversalVocabularyMt', vStrDef).
 6857exactlyAssertedEL_first(genlPreds, nearestIsa, isa, 'UniversalVocabularyMt', vStrDef).
 6858exactlyAssertedEL_first(genlPreds, nearestGenls, genls, 'UniversalVocabularyMt', vStrDef).
 6859exactlyAssertedEL_first(genlPreds, nearestGenlPreds, genlPreds, 'UniversalVocabularyMt', vStrDef).
 6860exactlyAssertedEL_first(genlPreds, nearestGenlMt, genlMt, 'UniversalVocabularyMt', vStrDef).
 6861exactlyAssertedEL_first(genlPreds, natFunction, termDependsOn, 'UniversalVocabularyMt', vStrDef).
 6862exactlyAssertedEL_first(genlPreds, minQuantValue, quantitySubsumes, 'UniversalVocabularyMt', vStrDef).
 6863exactlyAssertedEL_first(genlPreds, maxQuantValue, quantitySubsumes, 'UniversalVocabularyMt', vStrDef).
 6864exactlyAssertedEL_first(genlPreds, knownSentence, trueSentence, 'UniversalVocabularyMt', vStrDef).
 6865exactlyAssertedEL_first(genlPreds, knownAntecedentRule, highlyRelevantAssertion, 'UniversalVocabularyMt', vStrDef).
 6866exactlyAssertedEL_first(genlPreds, isa, elementOf, 'UniversalVocabularyMt', vStrDef).
 6867exactlyAssertedEL_first(genlPreds, indexicalReferent, equals, 'UniversalVocabularyMt', vStrDef).
 6868exactlyAssertedEL_first(genlPreds, greaterThan, greaterThanOrEqualTo, 'UniversalVocabularyMt', vStrDef).
 6869exactlyAssertedEL_first(genlPreds, greaterThan, different, 'UniversalVocabularyMt', vStrDef).
 6870exactlyAssertedEL_first(genlPreds, genls, subsetOf, 'UniversalVocabularyMt', vStrDef).
 6871exactlyAssertedEL_first(genlPreds, followingValue, different, 'UniversalVocabularyMt', vStrDef).
 6872exactlyAssertedEL_first(genlPreds, expresses, means, 'UniversalVocabularyMt', vStrDef).
 6873exactlyAssertedEL_first(genlPreds, exactlyAssertedEL_next, knownSentence, 'UniversalVocabularyMt', vStrDef).
 6874exactlyAssertedEL_first(genlPreds, equalSymbols, equals, 'UniversalVocabularyMt', vStrDef).
 6875exactlyAssertedEL_first(genlPreds, elInverse, genlInverse, 'UniversalVocabularyMt', vStrDef).
 6876exactlyAssertedEL_first(genlPreds, different, differentSymbols, 'UniversalVocabularyMt', vStrDef).
 6877exactlyAssertedEL_first(genlPreds, denotes, means, 'UniversalVocabularyMt', vStrDef).
 6878exactlyAssertedEL_first(genlPreds, defnIff, defnSufficient, 'UniversalVocabularyMt', vStrDef).
 6879exactlyAssertedEL_first(genlPreds, defnIff, defnNecessary, 'UniversalVocabularyMt', vStrDef).
 6880exactlyAssertedEL_first(genlPreds, definingMt, termDependsOn, 'UniversalVocabularyMt', vStrDef).
 6881exactlyAssertedEL_first(genlPreds, consistent, admittedSentence, 'UniversalVocabularyMt', vStrDef).
 6882exactlyAssertedEL_first(genlPreds, completelyEnumerableCollection, completelyDecidableCollection, 'UniversalVocabularyMt', vStrDef).
 6883exactlyAssertedEL_first(genlPreds, completelyEnumerableCollection, completelyDecidableCollection, 'CoreCycLMt', vStrDef).
 6884exactlyAssertedEL_first(genlPreds, completeExtentEnumerableViaBackchain, minimizeExtent, 'UniversalVocabularyMt', vStrDef).
 6885exactlyAssertedEL_first(genlPreds, completeExtentEnumerableViaBackchain, minimizeExtent, 'CoreCycLMt', vStrDef).
 6886exactlyAssertedEL_first(genlPreds, completeExtentEnumerableForValueInArg, nonAbducibleWithValueInArg, 'UniversalVocabularyMt', vStrDef).
 6887exactlyAssertedEL_first(genlPreds, completeExtentEnumerableForValueInArg, nonAbducibleWithValueInArg, 'CoreCycLMt', vStrDef).
 6888exactlyAssertedEL_first(genlPreds, completeExtentEnumerableForValueInArg, completeExtentDecidableForValueInArg, 'UniversalVocabularyMt', vStrDef).
 6889exactlyAssertedEL_first(genlPreds, completeExtentEnumerableForValueInArg, completeExtentDecidableForValueInArg, 'CoreCycLMt', vStrDef).
 6890exactlyAssertedEL_first(genlPreds, completeExtentEnumerable, minimizeExtent, 'UniversalVocabularyMt', vStrDef).
 6891exactlyAssertedEL_first(genlPreds, completeExtentEnumerable, minimizeExtent, 'CoreCycLMt', vStrDef).
 6892exactlyAssertedEL_first(genlPreds, completeExtentEnumerable, completeExtentDecidable, 'UniversalVocabularyMt', vStrDef).
 6893exactlyAssertedEL_first(genlPreds, completeExtentEnumerable, completeExtentDecidable, 'CoreCycLMt', vStrDef).
 6894exactlyAssertedEL_first(genlPreds, completeExtentDecidable, backchainForbidden, 'UniversalVocabularyMt', vStrDef).
 6895exactlyAssertedEL_first(genlPreds, completeExtentAssertedForValueInArg, completeExtentEnumerableForValueInArg, 'UniversalVocabularyMt', vStrDef).
 6896exactlyAssertedEL_first(genlPreds, completeExtentAssertedForValueInArg, completeExtentEnumerableForValueInArg, 'CoreCycLMt', vStrDef).
 6897exactlyAssertedEL_first(genlPreds, completeExtentAsserted, completeExtentEnumerable, 'UniversalVocabularyMt', vStrDef).
 6898exactlyAssertedEL_first(genlPreds, completeExtentAsserted, completeExtentEnumerable, 'CoreCycLMt', vStrDef).
 6899exactlyAssertedEL_first(genlPreds, commutativeInArgsAndRest, commutativeInArgs, 'UniversalVocabularyMt', vStrDef).
 6900exactlyAssertedEL_first(genlPreds, collectionIsaBackchainRequired, collectionIsaBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6901exactlyAssertedEL_first(genlPreds, collectionGenlsBackchainRequired, collectionGenlsBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6902exactlyAssertedEL_first(genlPreds, collectionBackchainRequired, collectionIsaBackchainRequired, 'UniversalVocabularyMt', vStrDef).
 6903exactlyAssertedEL_first(genlPreds, collectionBackchainRequired, collectionGenlsBackchainRequired, 'UniversalVocabularyMt', vStrDef).
 6904exactlyAssertedEL_first(genlPreds, collectionBackchainRequired, collectionBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6905exactlyAssertedEL_first(genlPreds, collectionBackchainEncouraged, collectionIsaBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6906exactlyAssertedEL_first(genlPreds, collectionBackchainEncouraged, collectionGenlsBackchainEncouraged, 'UniversalVocabularyMt', vStrDef).
 6907exactlyAssertedEL_first(genlPreds, coExtensional, genls, 'UniversalVocabularyMt', vStrDef).
 6908exactlyAssertedEL_first(genlPreds, canonicalizerDirectiveForArgAndRest, canonicalizerDirectiveForArg, 'UniversalVocabularyMt', vStrDef).
 6909exactlyAssertedEL_first(genlPreds, canonicalizerDirectiveForArgAndRest, canonicalizerDirectiveForArg, 'CoreCycLImplementationMt', vStrDef).
 6910exactlyAssertedEL_first(genlPreds, knownSentence, knownSentence, 'UniversalVocabularyMt', vStrDef).
 6911exactlyAssertedEL_first(genlPreds, assertedPredicateArg, admittedArgument, 'UniversalVocabularyMt', vStrDef).
 6912exactlyAssertedEL_first(genlPreds, argsIsa, arg1Isa, 'UniversalVocabularyMt', vStrDef).
 6913exactlyAssertedEL_first(genlPreds, argIsa, argSometimesIsa, 'UniversalVocabularyMt', vStrDef).
 6914exactlyAssertedEL_first(genlPreds, argAndRestQuotedIsa, argQuotedIsa, 'UniversalVocabularyMt', vStrDef).
 6915exactlyAssertedEL_first(genlPreds, argAndRestIsa, argIsa, 'UniversalVocabularyMt', vStrDef).
 6916exactlyAssertedEL_first(genlPreds, 'ist-Asserted', ist, 'UniversalVocabularyMt', vStrDef).
 6917exactlyAssertedEL_first(genlPreds, 'equalStrings-CaseInsensitive', equals, 'UniversalVocabularyMt', vStrDef).
 6918exactlyAssertedEL_first(genlPreds, 'equalStrings-CaseInsensitive', 'substring-CaseInsensitive', 'UniversalVocabularyMt', vStrDef).
 6919exactlyAssertedEL_first(genlMt, 'UniversalVocabularyMt', 'UniversalVocabularyImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6920exactlyAssertedEL_first(genlMt, 'UniversalVocabularyMt', 'CoreCycLImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6921exactlyAssertedEL_first(genlMt, 'UniversalVocabularyMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6922exactlyAssertedEL_first(genlMt, 'UniversalVocabularyImplementationMt', 'UniversalVocabularyMt', 'UniversalVocabularyMt', vStrDef).
 6923exactlyAssertedEL_first(genlMt, 'UniversalVocabularyImplementationMt', 'CoreCycLImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6924exactlyAssertedEL_first(genlMt, 'UniversalVocabularyImplementationMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6925exactlyAssertedEL_first(genlMt, 'TemporaryEnglishParaphraseMt', 'EnglishParaphraseMt', 'UniversalVocabularyMt', vStrDef).
 6926exactlyAssertedEL_first(genlMt, 'TemporaryEnglishParaphraseMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6927exactlyAssertedEL_first(genlMt, 'QueryMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6928exactlyAssertedEL_first(genlMt, 'LogicalTruthMt', 'LogicalTruthImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6929exactlyAssertedEL_first(genlMt, 'LogicalTruthMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6930exactlyAssertedEL_first(genlMt, 'LogicalTruthImplementationMt', 'LogicalTruthMt', 'UniversalVocabularyMt', vStrDef).
 6931exactlyAssertedEL_first(genlMt, 'LogicalTruthImplementationMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6932exactlyAssertedEL_first(genlMt, 'InferencePSC', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6933exactlyAssertedEL_first(genlMt, 'EverythingPSC', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6934exactlyAssertedEL_first(genlMt, 'EnglishParaphraseMt', 'CurrentWorldDataCollectorMt-NonHomocentric', 'UniversalVocabularyMt', vStrDef).
 6935exactlyAssertedEL_first(genlMt, 'EnglishParaphraseMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6936exactlyAssertedEL_first(genlMt, 'CyclistDefinitionalMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6937exactlyAssertedEL_first(genlMt, 'CurrentWorldDataCollectorMt-NonHomocentric', 'CyclistDefinitionalMt', 'UniversalVocabularyMt', vStrDef).
 6938exactlyAssertedEL_first(genlMt, 'CurrentWorldDataCollectorMt-NonHomocentric', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6939exactlyAssertedEL_first(genlMt, 'CoreCycLMt', 'LogicalTruthMt', 'UniversalVocabularyMt', vStrDef).
 6940exactlyAssertedEL_first(genlMt, 'CoreCycLMt', 'CoreCycLImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6941exactlyAssertedEL_first(genlMt, 'CoreCycLMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6942exactlyAssertedEL_first(genlMt, 'CoreCycLImplementationMt', 'LogicalTruthImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6943exactlyAssertedEL_first(genlMt, 'CoreCycLImplementationMt', 'CoreCycLMt', 'UniversalVocabularyMt', vStrDef).
 6944exactlyAssertedEL_first(genlMt, 'CoreCycLImplementationMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6945exactlyAssertedEL_first(genlMt, 'BookkeepingMt', 'EnglishParaphraseMt', 'UniversalVocabularyMt', vStrDef).
 6946exactlyAssertedEL_first(genlMt, 'BookkeepingMt', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6947exactlyAssertedEL_first(genlMt, 'BaseKB', 'UniversalVocabularyMt', 'UniversalVocabularyMt', vStrDef).
 6948exactlyAssertedEL_first(genlMt, 'BaseKB', 'UniversalVocabularyImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6949exactlyAssertedEL_first(genlMt, 'BaseKB', 'CoreCycLImplementationMt', 'UniversalVocabularyMt', vStrDef).
 6950exactlyAssertedEL_first(genlMt, 'BaseKB', 'BaseKB', 'UniversalVocabularyMt', vStrDef).
 6951exactlyAssertedEL_first(genlMt, '$VAR'('X'), '$VAR'('X'), 'LogicalTruthMt', vStrDef).
 6952exactlyAssertedEL_first(genlInverse, siblingDisjointExceptions, siblingDisjointExceptions, 'UniversalVocabularyMt', vStrDef).
 6953exactlyAssertedEL_first(genlInverse, sentenceEquiv, sentenceImplies, 'UniversalVocabularyMt', vStrDef).
 6954exactlyAssertedEL_first(genlInverse, sentenceEquiv, sentenceEquiv, 'UniversalVocabularyMt', vStrDef).
 6955exactlyAssertedEL_first(genlInverse, reformulatorRuleProperties, isa, 'UniversalVocabularyMt', vStrDef).
 6956exactlyAssertedEL_first(genlInverse, quantitySubsumes, quantityIntersects, 'UniversalVocabularyMt', vStrDef).
 6957exactlyAssertedEL_first(genlInverse, quantityIntersects, quantityIntersects, 'UniversalVocabularyMt', vStrDef).
 6958exactlyAssertedEL_first(genlInverse, numericallyEquals, numericallyEquals, 'UniversalVocabularyMt', vStrDef).
 6959exactlyAssertedEL_first(genlInverse, negationPreds, negationPreds, 'UniversalVocabularyMt', vStrDef).
 6960exactlyAssertedEL_first(genlInverse, negationMt, negationMt, 'UniversalVocabularyMt', vStrDef).
 6961exactlyAssertedEL_first(genlInverse, negationInverse, negationInverse, 'UniversalVocabularyMt', vStrDef).
 6962exactlyAssertedEL_first(genlInverse, natFunction, operatorFormulas, 'UniversalVocabularyMt', vStrDef).
 6963exactlyAssertedEL_first(genlInverse, minQuantValue, quantityIntersects, 'UniversalVocabularyMt', vStrDef).
 6964exactlyAssertedEL_first(genlInverse, maxQuantValue, quantityIntersects, 'UniversalVocabularyMt', vStrDef).
 6965exactlyAssertedEL_first(genlInverse, greaterThan, different, 'UniversalVocabularyMt', vStrDef).
 6966exactlyAssertedEL_first(genlInverse, followingValue, greaterThan, 'UniversalVocabularyMt', vStrDef).
 6967exactlyAssertedEL_first(genlInverse, equalSymbols, equalSymbols, 'UniversalVocabularyMt', vStrDef).
 6968exactlyAssertedEL_first(genlInverse, equals, equals, 'UniversalVocabularyMt', vStrDef).
 6969exactlyAssertedEL_first(genlInverse, elInverse, genlInverse, 'UniversalVocabularyMt', vStrDef).
 6970exactlyAssertedEL_first(genlInverse, disjointWith, disjointWith, 'UniversalVocabularyMt', vStrDef).
 6971exactlyAssertedEL_first(genlInverse, coExtensional, genls, 'UniversalVocabularyMt', vStrDef).
 6972exactlyAssertedEL_first(genlInverse, coExtensional, coExtensional, 'UniversalVocabularyMt', vStrDef).
 6973exactlyAssertedEL_first(genlInverse, 'equalStrings-CaseInsensitive', 'substring-CaseInsensitive', 'UniversalVocabularyMt', vStrDef).
 6974exactlyAssertedEL_first(genlCanonicalizerDirectives, 'LeaveSomeTermsAtELAndAllowKeywordVariables', 'LeaveSomeTermsAtEL', 'CoreCycLImplementationMt', vStrMon).
 6975exactlyAssertedEL_first(genlCanonicalizerDirectives, 'LeaveSomeTermsAtELAndAllowKeywordVariables', 'AllowKeywordVariables', 'CoreCycLImplementationMt', vStrMon).
 6976exactlyAssertedEL_first(genlCanonicalizerDirectives, 'LeaveSomeTermsAtEL', 'LeaveVariablesAtEL', 'CoreCycLImplementationMt', vStrMon).
 6977exactlyAssertedEL_first(genlCanonicalizerDirectives, 'AllowKeywordVariables', 'AllowGenericArgVariables', 'CoreCycLImplementationMt', vStrMon).
 6978exactlyAssertedEL_next(genKeyword, thereExists, ((':THERE_EXISTS')), 'EnglishParaphraseMt', vStrDef).
 6979exactlyAssertedEL_next(genKeyword, thereExistExactly, ((':THERE_EXIST_EXACTLY')), 'EnglishParaphraseMt', vStrDef).
 6980exactlyAssertedEL_next(genKeyword, thereExistAtMost, ((':THERE_EXIST_AT_MOST')), 'EnglishParaphraseMt', vStrDef).
 6981exactlyAssertedEL_next(genKeyword, thereExistAtLeast, ((':THERE_EXIST_AT_LEAST')), 'EnglishParaphraseMt', vStrDef).
 6982exactlyAssertedEL_next(genKeyword, termOfUnit, ((':TERM_OF_UNIT')), 'EnglishParaphraseMt', vStrDef).
 6983exactlyAssertedEL_next(genKeyword, relationExpansion, ((':RELATION_EXPANSION')), 'EnglishParaphraseMt', vStrDef).
 6984exactlyAssertedEL_next(genKeyword, prettyString, ((':PRETTY_NAME')), 'EnglishParaphraseMt', vStrDef).
 6985exactlyAssertedEL_next(genKeyword, or, ((':OR')), 'EnglishParaphraseMt', vStrDef).
 6986exactlyAssertedEL_next(genKeyword, nthSmallestElement, ((':NTH_SMALLEST_ELEMENT')), 'EnglishParaphraseMt', vStrDef).
 6987exactlyAssertedEL_next(genKeyword, nthLargestElement, ((':NTH_LARGEST_ELEMENT')), 'EnglishParaphraseMt', vStrDef).
 6988exactlyAssertedEL_next(genKeyword, not, ((':NOT')), 'EnglishParaphraseMt', vStrDef).
 6989exactlyAssertedEL_next(genKeyword, myCreator, ((':MY_CREATOR')), 'EnglishParaphraseMt', vStrDef).
 6990exactlyAssertedEL_next(genKeyword, myCreationTime, ((':MY_CREATION_TIME')), 'EnglishParaphraseMt', vStrDef).
 6991exactlyAssertedEL_next(genKeyword, isa, ((':ISA')), 'EnglishParaphraseMt', vStrDef).
 6992exactlyAssertedEL_next(genKeyword, implies, ((':IMPLIES')), 'EnglishParaphraseMt', vStrDef).
 6993exactlyAssertedEL_next(genKeyword, genMassNoun, ((':GEN_MASS_NOUN')), 'EnglishParaphraseMt', vStrDef).
 6994exactlyAssertedEL_next(genKeyword, genls, ((':GENLS')), 'EnglishParaphraseMt', vStrDef).
 6995exactlyAssertedEL_next(genKeyword, genFormat, ((':GEN_FORMAT')), 'EnglishParaphraseMt', vStrDef).
 6996exactlyAssertedEL_next(genKeyword, forAll, ((':FOR_ALL')), 'EnglishParaphraseMt', vStrDef).
 6997exactlyAssertedEL_next(genKeyword, exceptWhen, ((':EXCEPT_WHEN')), 'EnglishParaphraseMt', vStrDef).
 6998exactlyAssertedEL_next(genKeyword, exceptFor, ((':EXCEPT_FOR')), 'EnglishParaphraseMt', vStrDef).
 6999exactlyAssertedEL_next(genKeyword, equals, ((':EQUALS')), 'EnglishParaphraseMt', vStrDef).
 7000exactlyAssertedEL_next(genKeyword, different, ((':DIFFERENT')), 'EnglishParaphraseMt', vStrDef).
 7001exactlyAssertedEL_next(genKeyword, and, ((':AND')), 'EnglishParaphraseMt', vStrDef).
 7002exactlyAssertedEL_next(genKeyword, 'VariableArityRelation', ((':VARIABLE_ARITY_RELATION')), 'EnglishParaphraseMt', vStrDef).
 7003exactlyAssertedEL_next(genKeyword, 'UnitOfMeasure', ((':UNIT_OF_MEASURE')), 'EnglishParaphraseMt', vStrDef).
 7004exactlyAssertedEL_next(genKeyword, 'Thing', ((':THING')), 'EnglishParaphraseMt', vStrDef).
 7005exactlyAssertedEL_next(genKeyword, 'TheTerm', ((':THE_TERM')), 'EnglishParaphraseMt', vStrDef).
 7006exactlyAssertedEL_next(genKeyword, 'TemporaryEnglishParaphraseMt', ((':TEMPORARY_ENGLISH_PARAPHRASE_MT')), 'TemporaryEnglishParaphraseMt', vStrDef).
 7007exactlyAssertedEL_next(genKeyword, 'SetOrCollection', ((':SET_OR_COLLECTION')), 'EnglishParaphraseMt', vStrDef).
 7008exactlyAssertedEL_next(genKeyword, 'Set-Mathematical', ((':SET_MATHEMATICAL')), 'EnglishParaphraseMt', vStrDef).
 7009exactlyAssertedEL_next(genKeyword, 'September', ((':SEPTEMBER')), 'EnglishParaphraseMt', vStrDef).
 7010exactlyAssertedEL_next(genKeyword, tRelation, ((':RELATIONSHIP')), 'EnglishParaphraseMt', vStrDef).
 7011exactlyAssertedEL_next(genKeyword, 'Quantifier', ((':QUANTIFIER')), 'EnglishParaphraseMt', vStrDef).
 7012exactlyAssertedEL_next(genKeyword, 'PerFn', ((':PER_FN')), 'EnglishParaphraseMt', vStrDef).
 7013exactlyAssertedEL_next(genKeyword, 'October', ((':OCTOBER')), 'EnglishParaphraseMt', vStrDef).
 7014exactlyAssertedEL_next(genKeyword, 'November', ((':NOVEMBER')), 'EnglishParaphraseMt', vStrDef).
 7015exactlyAssertedEL_next(genKeyword, 'NonNegativeInteger', ((':NON_NEGATIVE_INTEGER')), 'EnglishParaphraseMt', vStrDef).
 7016exactlyAssertedEL_next(genKeyword, 'MeaningInSystemFn', ((':MEANING_IN_SYSTEM_FN')), 'EnglishParaphraseMt', vStrDef).
 7017exactlyAssertedEL_next(genKeyword, 'May', ((':MAY')), 'EnglishParaphraseMt', vStrDef).
 7018exactlyAssertedEL_next(genKeyword, 'March', ((':MARCH')), 'EnglishParaphraseMt', vStrDef).
 7019exactlyAssertedEL_next(genKeyword, 'LogicalConnective', ((':LOGICAL_CONNECTIVE')), 'EnglishParaphraseMt', vStrDef).
 7020exactlyAssertedEL_next(genKeyword, 'Kappa', ((':KAPPA')), 'EnglishParaphraseMt', vStrDef).
 7021exactlyAssertedEL_next(genKeyword, 'June', ((':JUNE')), 'EnglishParaphraseMt', vStrDef).
 7022exactlyAssertedEL_next(genKeyword, 'July', ((':JULY')), 'EnglishParaphraseMt', vStrDef).
 7023exactlyAssertedEL_next(genKeyword, 'January', ((':JANUARY')), 'EnglishParaphraseMt', vStrDef).
 7024exactlyAssertedEL_next(genKeyword, 'Individual', ((':INDIVIDUAL')), 'EnglishParaphraseMt', vStrDef).
 7025exactlyAssertedEL_next(genKeyword, 'FunctionToArg', ((':FUNCTION_TO_ARG')), 'EnglishParaphraseMt', vStrDef).
 7026exactlyAssertedEL_next(genKeyword, tFunction, ((':NON_PREDICATE_FUNCTION')), 'EnglishParaphraseMt', vStrDef).
 7027exactlyAssertedEL_next(genKeyword, 'FixedAritySkolemFunction', ((':SKOLEM_FUNCTION')), 'EnglishParaphraseMt', vStrDef).
 7028exactlyAssertedEL_next(genKeyword, 'February', ((':FEBRUARY')), 'EnglishParaphraseMt', vStrDef).
 7029exactlyAssertedEL_next(genKeyword, 'EnglishParaphraseMt', ((':ENGLISH_PARAPHRASE_MT')), 'EnglishParaphraseMt', vStrDef).
 7030exactlyAssertedEL_next(genKeyword, 'December', ((':DECEMBER')), 'EnglishParaphraseMt', vStrDef).
 7031exactlyAssertedEL_next(genKeyword, tCol, ((':COLLECTION')), 'EnglishParaphraseMt', vStrDef).
 7032exactlyAssertedEL_next(genKeyword, 'BaseKB', ((':BASE_K_B')), 'EnglishParaphraseMt', vStrDef).
 7033exactlyAssertedEL_next(genKeyword, 'August', ((':AUGUST')), 'EnglishParaphraseMt', vStrDef).
 7034exactlyAssertedEL_next(genKeyword, 'April', ((':APRIL')), 'EnglishParaphraseMt', vStrDef).
 7035exactlyAssertedEL_next(genFormat, xor, "either ~a or ~a (but not both)", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7036exactlyAssertedEL_next(genFormat, trueRule, "~a is true, and ~a is an instantiation of the rule template ~a", 'TheList'(2, 2, 1), 'EnglishParaphraseMt', vStrDef).
 7037exactlyAssertedEL_next(genFormat, thereExistAtMost, "there ~a at most ~a ~a such that ~a", 'TheList'('TheList'("is", "are"), 1, 2, 3), 'EnglishParaphraseMt', vStrDef).
 7038exactlyAssertedEL_next(genFormat, thereExistAtLeast, "there ~a at least ~a ~a such that ~a", 'TheList'('TheList'("is", "are"), 1, 2, 3), 'EnglishParaphraseMt', vStrDef).
 7039exactlyAssertedEL_next(genFormat, synonymousExternalConcept, "~s is synonymous with ~s in ~a", 'TheList'('TheList'(1, ((':SINGULAR'))), 3, 2), 'EnglishParaphraseMt', vStrDef).
 7040exactlyAssertedEL_next(genFormat, substring, "~s is a substring of ~s", 'TheList'(1, 2), 'EnglishParaphraseMt', vStrDef).
 7041exactlyAssertedEL_next(genFormat, sentenceEquiv, "the formula ~a is logically equivalent to the formula ~a", 'TheList'('TheList'(1, ((':QUOTE'))), 'TheList'(2, ((':QUOTE')))), 'EnglishParaphraseMt', vStrDef).
 7042exactlyAssertedEL_next(genFormat, requiredArg2Pred, "every ~a is arg 2 of ~a relation", 'TheList'(1, 'TheList'(2, ((':QUOTE')), ((':A_THE_WORD')))), 'EnglishParaphraseMt', vStrDef).
 7043exactlyAssertedEL_next(genFormat, relationExpansion, "one CycL expansion for assertions which have ~a in the operator position is ~a", 'TheList'('TheList'(1, ((':EQUALS'))), 'TheList'(2, ((':EQUALS')))), 'EnglishParaphraseMt', vStrDef).
 7044exactlyAssertedEL_next(genFormat, notAssertibleMt, "Sentences cannot be asserted in ~a", 'TheList'('TheList'(1, ((':EQUALS')))), 'EnglishParaphraseMt', vStrDef).
 7045exactlyAssertedEL_next(genFormat, nearestCommonIsa, "both ~a and ~a are ~a", 'TheList'(1, 2, 'TheList'(3, 'TheList'(((':PN_MASS_NUMBER')), ((':PN_SINGULAR')), ((':MASS_NUMBER'))), ((':GERUND')), ((':AGENTIVE_SG')), ((':SINGULAR')), ((':A_THE_WORD')))), 'EnglishParaphraseMt', vStrDef).
 7046exactlyAssertedEL_next(genFormat, indexicalReferent, "the indexical term ~a refers to ~a", 'TheList'('TheList'(1, ((':QUOTE'))), 2), 'EnglishParaphraseMt', vStrDef).
 7047exactlyAssertedEL_next(genFormat, implies, "if ~a, then ~a", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7048exactlyAssertedEL_next(genFormat, genFormat, "to generate English for assertions formed with ~a, the format string ~a is used with the extra information in this list: ~a", 'TheList'('TheList'(1, ((':EQUALS'))), 2, 3), 'EnglishParaphraseMt', vStrDef).
 7049exactlyAssertedEL_next(genFormat, forAll, "for every ~a, ~a", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7050exactlyAssertedEL_next(genFormat, equiv, "~a if and only if ~a", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7051exactlyAssertedEL_next(genFormat, differentSymbols, "~a are different symbols", 'TheList'('TheList'(1, ((':AND')))), 'EnglishParaphraseMt', vStrDef).
 7052exactlyAssertedEL_next(genFormat, cycTacticID, "the inference tactic ~a contained within the inference problem ~a, has ~a as its ID", 'TheList'('TheList'(1, ((':SINGULAR'))), 'TheList'(2, ((':SINGULAR')))), 'EnglishParaphraseMt', vStrDef).
 7053exactlyAssertedEL_next(genFormat, cycProofID, "the inference proof ~a contained within inference problem store ~a, has ~a as its ID", 'TheList'('TheList'(1, ((':SINGULAR'))), 'TheList'(2, ((':SINGULAR')))), 'EnglishParaphraseMt', vStrDef).
 7054exactlyAssertedEL_next(genFormat, cycProblemStoreProofCount, "the inference problem store ~a has ~a proof~a", 'TheList'(1, 2, 'TheList'("", "s")), 'EnglishParaphraseMt', vStrDef).
 7055exactlyAssertedEL_next(genFormat, cycProblemStoreProblemCount, "the inference problem store ~a has ~a inference problem~a", 'TheList'(1, 2, 'TheList'("", "s")), 'EnglishParaphraseMt', vStrDef).
 7056exactlyAssertedEL_next(genFormat, cycProblemStoreLinkCount, "the inference problem store ~a has ~a inference link~a", 'TheList'(1, 2, 'TheList'("", "s")), 'EnglishParaphraseMt', vStrDef).
 7057exactlyAssertedEL_next(genFormat, cycProblemStoreInferenceCount, "the inference problem store ~a has ~a inference~a", 'TheList'(1, 2, 'TheList'("", "s")), 'EnglishParaphraseMt', vStrDef).
 7058exactlyAssertedEL_next(genFormat, cycProblemLinkID, "the inference problem link ~a contained within inference problem store ~a, has ~a as its ID", 'TheList'('TheList'(1, ((':SINGULAR'))), 'TheList'(2, ((':SINGULAR')))), 'EnglishParaphraseMt', vStrDef).
 7059exactlyAssertedEL_next(genFormat, cycProblemID, "the inference problem ~a contained within inference problem store ~a, has ~a as its ID", 'TheList'('TheList'(1, ((':SINGULAR'))), 'TheList'(2, ((':SINGULAR')))), 'EnglishParaphraseMt', vStrDef).
 7060exactlyAssertedEL_next(genFormat, completeExtentEnumerable, "the complete extent of the predicate ~a is known", 'TheList'('TheList'(1, ((':EQUALS')))), 'EnglishParaphraseMt', vStrDef).
 7061exactlyAssertedEL_next(genFormat, 'UnitProductFn', "~a-~a", 'TheList'('TheList'(1, ((':PLURAL'))), 'TheList'(2, ((':SINGULAR')))), 'EnglishParaphraseMt', vStrDef).
 7062exactlyAssertedEL_next(genFormat, 'TheSet', "the set containing ~a", 'TheList'('TheList'(1, ((':AND')))), 'EnglishParaphraseMt', vStrDef).
 7063exactlyAssertedEL_next(genFormat, 'substring-CaseInsensitive', "~s is a case-insensitive substring of ~s", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7064exactlyAssertedEL_next(genFormat, 'RoundUpFn', "~a, truncated", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7065exactlyAssertedEL_next(genFormat, 'RoundUpFn', "~a, rounded up", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7066exactlyAssertedEL_next(genFormat, 'RoundDownFn', "~a, rounded down", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7067exactlyAssertedEL_next(genFormat, 'PlusFn', "the sum of ~a", 'TheList'('TheList'(1, ((':AND')))), 'EnglishParaphraseMt', vStrDef).
 7068exactlyAssertedEL_next(genFormat, 'PlusAll', "the sum of ~a over ~a", 'TheList'(2, 'TheList'(1, ((':PLURAL')))), 'EnglishParaphraseMt', vStrDef).
 7069exactlyAssertedEL_next(genFormat, 'MinRangeFn', "the minimum range subsumed by ~a and ~a", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7070exactlyAssertedEL_next(genFormat, 'Minimum', "the minimum ~a over ~a", 'TheList'(2, 'TheList'(1, ((':PLURAL')))), 'EnglishParaphraseMt', vStrDef).
 7071exactlyAssertedEL_next(genFormat, 'MaxRangeFn', "the maximum range subsuming ~a and ~a", 'TheEmptyList', 'EnglishParaphraseMt', vStrDef).
 7072exactlyAssertedEL_next(genFormat, 'Maximum', "the maximum ~a over ~a", 'TheList'(2, 'TheList'(1, ((':PLURAL')))), 'EnglishParaphraseMt', vStrDef).
 7073exactlyAssertedEL_next(genFormat, 'FunctionToArg', "'~a'", 'TheList'(2, ((':SINGULAR')), ((':MASS_NUMBER'))), 'EnglishParaphraseMt', vStrDef).
 7074exactlyAssertedEL_next(fanOutArg, substring, 2, 'BaseKB', vStrMon).
 7075exactlyAssertedEL_next(fanOutArg, genls, 1, 'BaseKB', vStrMon).
 7076exactlyAssertedEL_next(fanOutArg, genlPreds, 1, 'BaseKB', vStrMon).
 7077exactlyAssertedEL_next(fanOutArg, genlMt, 1, 'BaseKB', vStrMon).
 7078exactlyAssertedEL_next(expansionDefn, 'TLVariableFn', 'SubLQuoteFn'('TL-VAR-TO-EL'), 'BaseKB', vStrDef).
 7079exactlyAssertedEL_next(expansionDefn, 'TLReifiedNatFn', 'SubLQuoteFn'('TL-FUNCTION-TERM-TO-EL'), 'BaseKB', vStrDef).
 7080exactlyAssertedEL_next(expansionDefn, 'TLAssertionFn', 'SubLQuoteFn'('TL-ASSERTION-TERM-TO-EL'), 'BaseKB', vStrDef).
 7081exactlyAssertedEL_first(evaluationResultQuotedIsa, 'FormulaArgFn', 'CycLTerm', 'UniversalVocabularyMt', vStrMon).
 7082exactlyAssertedEL_first(evaluationResultQuotedIsa, 'DateEncodeStringFn', 'SubLString', 'UniversalVocabularyMt', vStrMon).
 7083exactlyAssertedEL_first(evaluationDefn, trueSubL, 'SubLQuoteFn'('CYC-TRUE-SUBL'), 'BaseKB', vStrMon).
 7084exactlyAssertedEL_first(evaluationDefn, substring, 'SubLQuoteFn'('CYC-SUBSTRING-PREDICATE'), 'BaseKB', vStrMon).
 7085exactlyAssertedEL_first(evaluationDefn, quantitySubsumes, 'SubLQuoteFn'('CYC-QUANTITY-SUBSUMES'), 'BaseKB', vStrMon).
 7086exactlyAssertedEL_first(evaluationDefn, quantityIntersects, 'SubLQuoteFn'('CYC-QUANTITY-INTERSECTS'), 'BaseKB', vStrMon).
 7087exactlyAssertedEL_first(evaluationDefn, numericallyEquals, 'SubLQuoteFn'('CYC-NUMERICALLY-EQUAL'), 'BaseKB', vStrMon).
 7088exactlyAssertedEL_first(evaluationDefn, greaterThanOrEqualTo, 'SubLQuoteFn'('CYC-GREATER-THAN-OR-EQUAL-TO'), 'BaseKB', vStrMon).
 7089exactlyAssertedEL_first(evaluationDefn, greaterThan, 'SubLQuoteFn'('CYC-GREATER-THAN'), 'BaseKB', vStrMon).
 7090exactlyAssertedEL_first(evaluationDefn, differentSymbols, 'SubLQuoteFn'('CYC-DIFFERENT-SYMBOLS'), 'BaseKB', vStrMon).
 7091exactlyAssertedEL_first(evaluationDefn, different, 'SubLQuoteFn'('CYC-DIFFERENT'), 'BaseKB', vStrMon).
 7092exactlyAssertedEL_first(evaluationDefn, 'TimesFn', 'SubLQuoteFn'('CYC-TIMES'), 'BaseKB', vStrMon).
 7093exactlyAssertedEL_first(evaluationDefn, 'substring-CaseInsensitive', 'SubLQuoteFn'('CYC-SUBSTRING-CASE-INSENSITIVE-PREDICATE'), 'BaseKB', vStrMon).
 7094exactlyAssertedEL_first(evaluationDefn, 'RoundUpFn', 'SubLQuoteFn'('CYC-ROUND-UP'), 'BaseKB', vStrMon).
 7095exactlyAssertedEL_first(evaluationDefn, 'RoundDownFn', 'SubLQuoteFn'('CYC-ROUND-DOWN'), 'BaseKB', vStrMon).
 7096exactlyAssertedEL_first(evaluationDefn, 'RoundClosestFn', 'SubLQuoteFn'('CYC-ROUND-CLOSEST'), 'BaseKB', vStrMon).
 7097exactlyAssertedEL_first(evaluationDefn, 'QuotientFn', 'SubLQuoteFn'('CYC-QUOTIENT'), 'BaseKB', vStrMon).
 7098exactlyAssertedEL_first(evaluationDefn, 'QuantityConversionFn', 'SubLQuoteFn'('CYC-QUANTITY-CONVERSION'), 'BaseKB', vStrMon).
 7099exactlyAssertedEL_first(evaluationDefn, 'PlusFn', 'SubLQuoteFn'('CYC-PLUS'), 'BaseKB', vStrMon).
 7100exactlyAssertedEL_first(evaluationDefn, 'PlusAll', 'SubLQuoteFn'('CYC-PLUS-ALL'), 'BaseKB', vStrMon).
 7101exactlyAssertedEL_first(evaluationDefn, 'Percent', 'SubLQuoteFn'('CYC-PERCENT'), 'BaseKB', vStrMon).
 7102exactlyAssertedEL_first(evaluationDefn, 'ModuloFn', 'SubLQuoteFn'('CYC-MODULO'), 'UniversalVocabularyMt', vStrMon).
 7103exactlyAssertedEL_first(evaluationDefn, 'MinRangeFn', 'SubLQuoteFn'('CYC-MIN-RANGE'), 'BaseKB', vStrMon).
 7104exactlyAssertedEL_first(evaluationDefn, 'Minimum', 'SubLQuoteFn'('CYC-MINIMUM'), 'BaseKB', vStrMon).
 7105exactlyAssertedEL_first(evaluationDefn, 'MaxRangeFn', 'SubLQuoteFn'('CYC-MAX-RANGE'), 'BaseKB', vStrMon).
 7106exactlyAssertedEL_first(evaluationDefn, 'Maximum', 'SubLQuoteFn'('CYC-MAXIMUM'), 'BaseKB', vStrMon).
 7107exactlyAssertedEL_first(distributesOutOfArg, and, holdsIn, 2, 'BaseKB', vStrDef).
 7108exactlyAssertedEL_first(disjointWith, 'VariableArityRelation', 'FixedArityRelation', 'LogicalTruthMt', vStrMon).
 7109exactlyAssertedEL_first(disjointWith, 'TruthValue', 'List', 'UniversalVocabularyMt', vStrMon).
 7110exactlyAssertedEL_first(disjointWith, 'SubLString', 'TruthValue', 'UniversalVocabularyMt', vStrMon).
 7111exactlyAssertedEL_first(disjointWith, 'SubLNonVariableNonKeywordSymbol', 'SubLKeyword', 'UniversalVocabularyMt', vStrMon).
 7112exactlyAssertedEL_first(disjointWith, 'SubLNonNegativeInteger', 'SubLSymbol', 'LogicalTruthImplementationMt', vStrMon).
 7113exactlyAssertedEL_first(disjointWith, 'SententialRelation', tPred, 'LogicalTruthMt', vStrMon).
 7114exactlyAssertedEL_first(disjointWith, tRelation, 'TruthValue', 'LogicalTruthMt', vStrMon).
 7115exactlyAssertedEL_first(disjointWith, tRelation, 'NonNegativeInteger', 'LogicalTruthMt', vStrMon).
 7116exactlyAssertedEL_first(disjointWith, tRelation, 'Microtheory', 'LogicalTruthMt', vStrMon).
 7117exactlyAssertedEL_first(disjointWith, 'ReifiableFunction', 'UnreifiableFunction', 'LogicalTruthImplementationMt', vStrMon).
 7118exactlyAssertedEL_first(disjointWith, 'ReflexiveBinaryPredicate', 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', vStrMon).
 7119exactlyAssertedEL_first(disjointWith, 'PartiallyCommutativeRelation', 'UnaryRelation', 'UniversalVocabularyMt', vStrMon).
 7120exactlyAssertedEL_first(disjointWith, 'Microtheory', 'TruthValue', 'LogicalTruthMt', vStrMon).
 7121exactlyAssertedEL_first(disjointWith, 'LogicalConnective', 'Quantifier', 'LogicalTruthMt', vStrMon).
 7122exactlyAssertedEL_first(disjointWith, 'Individual', 'SetOrCollection', 'UniversalVocabularyMt', vStrMon).
 7123exactlyAssertedEL_first(disjointWith, tFunction, 'TruthFunction', 'LogicalTruthMt', vStrMon).
 7124exactlyAssertedEL_first(disjointWith, 'FixedAritySkolemFunction', 'VariableAritySkolemFunction', 'LogicalTruthImplementationMt', vStrMon).
 7125exactlyAssertedEL_first(disjointWith, 'ELRelation-Reversible', 'ELRelation-OneWay', 'UniversalVocabularyMt', vStrDef).
 7126exactlyAssertedEL_first(disjointWith, 'CycLTruthValueSentence', 'CycLFormulaicSentence', 'UniversalVocabularyMt', vStrMon).
 7127exactlyAssertedEL_first(disjointWith, 'CycLSentence-ClosedPredicate', 'CycLNonAtomicTerm-ClosedFunctor', 'UniversalVocabularyMt', vStrMon).
 7128exactlyAssertedEL_first(disjointWith, 'CycLSentence', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 7129exactlyAssertedEL_first(disjointWith, 'CycLSentence', 'CycLGenericRelationFormula', 'UniversalVocabularyMt', vStrDef).
 7130exactlyAssertedEL_first(disjointWith, 'CycLRuleAssertion', 'CycLGAFAssertion', 'UniversalVocabularyMt', vStrMon).
 7131exactlyAssertedEL_first(disjointWith, 'CycLRepresentedAtomicTerm', 'SubLAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 7132exactlyAssertedEL_first(disjointWith, 'CycLOpenSentence', 'CycLOpenDenotationalTerm', 'UniversalVocabularyMt', vStrMon).
 7133% exactlyAssertedEL_first(disjointWith, 'CycLOpenExpression', 'CycLClosedExpression', 'UniversalVocabularyMt', vStrDef).
 7134exactlyAssertedEL_first(disjointWith, 'CycLGenericRelationFormula', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrDef).
 7135exactlyAssertedEL_first(disjointWith, 'CycLClosedSentence', 'CycLNonAtomicTerm', 'UniversalVocabularyMt', vStrMon).
 7136exactlyAssertedEL_first(disjointWith, 'CycLAtomicTerm', 'CycLFormula', 'UniversalVocabularyMt', vStrDef).
 7137exactlyAssertedEL_first(disjointWith, 'CommutativeRelation', 'UnaryRelation', 'UniversalVocabularyMt', vStrMon).
 7138exactlyAssertedEL_first(disjointWith, 'CommutativeRelation', 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrMon).
 7139exactlyAssertedEL_first(disjointWith, tCol, 'Set-Mathematical', 'UniversalVocabularyMt', vStrMon).
 7140exactlyAssertedEL_first(disjointWith, tCol, 'Individual', 'LogicalTruthMt', vStrMon).
 7141exactlyAssertedEL_first(disjointWith, 'BinaryRelation', 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', vStrMon).
 7142exactlyAssertedEL_first(denotes, 'Quote'('Quote'('EscapeQuote'('$VAR'('X')))), 'Quote'('EscapeQuote'('$VAR'('X'))), 'BaseKB', vStrMon).
 7143exactlyAssertedEL_first(defnSufficient, 'Wednesday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7144exactlyAssertedEL_first(defnSufficient, 'Tuesday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7145exactlyAssertedEL_first(defnSufficient, 'Thursday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7146exactlyAssertedEL_first(defnSufficient, 'Sunday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7147exactlyAssertedEL_first(defnSufficient, 'ScalarPointValue', 'SubLQuoteFn'('SCALAR-POINT-VALUE?'), 'UniversalVocabularyMt', vStrDef).
 7148exactlyAssertedEL_first(defnSufficient, 'ScalarInterval', 'SubLQuoteFn'('IBQE?'), 'UniversalVocabularyMt', vStrDef).
 7149exactlyAssertedEL_first(defnSufficient, 'Saturday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7150exactlyAssertedEL_first(defnSufficient, 'Monday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7151exactlyAssertedEL_first(defnSufficient, 'List', 'SubLQuoteFn'('CYC-LIST-OF-TYPE-SUFFICIENT'), 'UniversalVocabularyMt', vStrDef).
 7152exactlyAssertedEL_first(defnSufficient, 'Integer', 'SubLQuoteFn'('INTEGERP'), 'UniversalVocabularyMt', vStrDef).
 7153exactlyAssertedEL_first(defnSufficient, 'Friday', 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN'), 'UniversalVocabularyMt', vStrDef).
 7154exactlyAssertedEL_first(defnSufficient, 'CharacterString', 'SubLQuoteFn'('STRINGP'), 'UniversalVocabularyMt', vStrDef).
 7155exactlyAssertedEL_first(defnSufficient, 'CharacterString', 'SubLQuoteFn'('CYC-LIST-OF-TYPE-SUFFICIENT'), 'UniversalVocabularyMt', vStrDef).
 7156exactlyAssertedEL_first(defnNecessary, 'Set-Mathematical', 'SubLQuoteFn'('CYC-SET-OF-TYPE-NECESSARY'), 'UniversalVocabularyMt', vStrDef).
 7157exactlyAssertedEL_first(defnNecessary, 'List', 'SubLQuoteFn'('CYC-LIST-OF-TYPE-NECESSARY'), 'UniversalVocabularyMt', vStrDef).
 7158exactlyAssertedEL_first(defnNecessary, 'Individual', 'SubLQuoteFn'('CYC-INDIVIDUAL-NECESSARY'), 'UniversalVocabularyMt', vStrDef).
 7159exactlyAssertedEL_first(defnNecessary, 'CharacterString', 'SubLQuoteFn'('CYC-LIST-OF-TYPE-NECESSARY'), 'UniversalVocabularyMt', vStrDef).
 7160exactlyAssertedEL_first(defnIff, 'Thing', 'SubLQuoteFn'('TRUE'), 'UniversalVocabularyMt', vStrDef).
 7161exactlyAssertedEL_first(defnIff, 'Thing', 'SubLQuoteFn'('TRUE'), 'LogicalTruthImplementationMt', vStrDef).
 7162exactlyAssertedEL_first(defnIff, 'RealNumber', 'SubLQuoteFn'('CYC-REAL-NUMBER'), 'UniversalVocabularyMt', vStrDef).
 7163exactlyAssertedEL_first(defnIff, 'PositiveInteger', 'SubLQuoteFn'('CYC-POSITIVE-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 7164exactlyAssertedEL_first(defnIff, 'PositiveInteger', 'SubLQuoteFn'('CYC-POSITIVE-INTEGER'), 'LogicalTruthImplementationMt', vStrDef).
 7165exactlyAssertedEL_first(defnIff, 'NonNegativeScalarInterval', 'SubLQuoteFn'('NON-NEGATIVE-SCALAR-INTERVAL?'), 'UniversalVocabularyMt', vStrDef).
 7166exactlyAssertedEL_first(defnIff, 'NonNegativeInteger', 'SubLQuoteFn'('CYC-NON-NEGATIVE-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 7167exactlyAssertedEL_first(defnIff, 'NonNegativeInteger', 'SubLQuoteFn'('CYC-NON-NEGATIVE-INTEGER'), 'LogicalTruthImplementationMt', vStrDef).
 7168exactlyAssertedEL_first(defnIff, 'Integer', 'SubLQuoteFn'('CYC-INTEGER'), 'UniversalVocabularyMt', vStrDef).
 7169exactlyAssertedEL_first(defnIff, 'HLExternalIDString', 'SubLQuoteFn'('HL-EXTERNAL-ID-STRING-P'), 'UniversalVocabularyMt', vStrDef).
 7170exactlyAssertedEL_first(definingMt, termOfUnit, 'BaseKB', 'BaseKB', vStrDef).
 7171exactlyAssertedEL_first(definingMt, termDependsOn, 'BaseKB', 'BaseKB', vStrDef).
 7172exactlyAssertedEL_first(definingMt, subsetOf, 'CoreCycLMt', 'BaseKB', vStrMon).
 7173exactlyAssertedEL_first(definingMt, skolem, 'BaseKB', 'BaseKB', vStrMon).
 7174exactlyAssertedEL_first(definingMt, ruleAfterRemoving, 'BaseKB', 'BaseKB', vStrMon).
 7175exactlyAssertedEL_first(definingMt, ruleAfterAdding, 'BaseKB', 'BaseKB', vStrMon).
 7176exactlyAssertedEL_first(definingMt, oldConstantName, 'BookkeepingMt', 'BaseKB', vStrMon).
 7177exactlyAssertedEL_first(definingMt, myCreator, 'BookkeepingMt', 'BaseKB', vStrMon).
 7178exactlyAssertedEL_first(definingMt, myCreationTime, 'BookkeepingMt', 'BaseKB', vStrMon).
 7179exactlyAssertedEL_first(definingMt, myCreationPurpose, 'BookkeepingMt', 'BaseKB', vStrDef).
 7180exactlyAssertedEL_first(definingMt, evaluationDefn, 'BaseKB', 'BaseKB', vStrDef).
 7181exactlyAssertedEL_first(definingMt, equals, 'LogicalTruthMt', 'BaseKB', vStrMon).
 7182exactlyAssertedEL_first(definingMt, elementOf, 'CoreCycLMt', 'BaseKB', vStrMon).
 7183exactlyAssertedEL_first(definingMt, defnSufficient, 'BaseKB', 'BaseKB', vStrDef).
 7184exactlyAssertedEL_first(definingMt, defnNecessary, 'BaseKB', 'BaseKB', vStrDef).
 7185exactlyAssertedEL_first(definingMt, defnIff, 'BaseKB', 'BaseKB', vStrDef).
 7186exactlyAssertedEL_first(definingMt, afterRemoving, 'BaseKB', 'BaseKB', vStrDef).
 7187exactlyAssertedEL_first(definingMt, afterAdding, 'BaseKB', 'BaseKB', vStrDef).
 7188exactlyAssertedEL_first(definingMt, 'HumanCyclist', 'BaseKB', 'BaseKB', vStrDef).
 7189exactlyAssertedEL_first(decontextualizedPredicate, termOfUnit, 'BaseKB', vStrMon).
 7190exactlyAssertedEL_first(decontextualizedPredicate, quotedArgument, 'BaseKB', vStrMon).
 7191exactlyAssertedEL_first(decontextualizedPredicate, predicateConventionMt, 'BaseKB', vStrMon).
 7192exactlyAssertedEL_first(decontextualizedPredicate, notAssertibleMt, 'BaseKB', vStrMon).
 7193exactlyAssertedEL_first(decontextualizedPredicate, nearestGenlMt, 'BaseKB', vStrDef).
 7194exactlyAssertedEL_first(decontextualizedPredicate, ist, 'BaseKB', vStrMon).
 7195exactlyAssertedEL_first(decontextualizedPredicate, genlMt, 'BaseKB', vStrMon).
 7196exactlyAssertedEL_first(decontextualizedPredicate, evaluateImmediately, 'BaseKB', vStrDef).
 7197exactlyAssertedEL_first(decontextualizedPredicate, ephemeralTerm, 'BaseKB', vStrMon).
 7198exactlyAssertedEL_first(decontextualizedPredicate, definingMt, 'BaseKB', vStrMon).
 7199exactlyAssertedEL_first(decontextualizedPredicate, decontextualizedPredicate, 'BaseKB', vStrMon).
 7200exactlyAssertedEL_first(decontextualizedPredicate, decontextualizedCollection, 'BaseKB', vStrMon).
 7201exactlyAssertedEL_first(decontextualizedPredicate, collectionConventionMt, 'BaseKB', vStrMon).
 7202exactlyAssertedEL_first(decontextualizedPredicate, canonicalizerDirectiveForArgAndRest, 'BaseKB', vStrDef).
 7203exactlyAssertedEL_first(decontextualizedPredicate, canonicalizerDirectiveForArg, 'BaseKB', vStrMon).
 7204exactlyAssertedEL_first(decontextualizedPredicate, canonicalizerDirectiveForAllArgs, 'BaseKB', vStrMon).
 7205exactlyAssertedEL_first(decontextualizedPredicate, assertionDirection, 'BaseKB', vStrMon).
 7206exactlyAssertedEL_first(decontextualizedPredicate, arityMin, 'BaseKB', vStrMon).
 7207exactlyAssertedEL_first(decontextualizedPredicate, arityMax, 'BaseKB', vStrMon).
 7208exactlyAssertedEL_first(decontextualizedPredicate, arity, 'BaseKB', vStrMon).
 7209exactlyAssertedEL_first(decontextualizedPredicate, 'ist-Asserted', 'BaseKB', vStrDef).
 7210exactlyAssertedEL_first(decontextualizedCollection, 'VariableAritySkolemFunction', 'BaseKB', vStrMon).
 7211exactlyAssertedEL_first(decontextualizedCollection, 'VariableArityRelation', 'BaseKB', vStrDef).
 7212exactlyAssertedEL_first(decontextualizedCollection, 'UnreifiableFunction', 'BaseKB', vStrDef).
 7213exactlyAssertedEL_first(decontextualizedCollection, 'UnitOfMeasure', 'BaseKB', vStrDef).
 7214exactlyAssertedEL_first(decontextualizedCollection, 'UnaryRelation', 'BaseKB', vStrDef).
 7215exactlyAssertedEL_first(decontextualizedCollection, 'UnaryPredicate', 'BaseKB', vStrDef).
 7216exactlyAssertedEL_first(decontextualizedCollection, 'UnaryFunction', 'BaseKB', vStrDef).
 7217exactlyAssertedEL_first(decontextualizedCollection, 'TruthFunction', 'BaseKB', vStrDef).
 7218exactlyAssertedEL_first(decontextualizedCollection, 'TransitiveBinaryPredicate', 'BaseKB', vStrDef).
 7219exactlyAssertedEL_first(decontextualizedCollection, 'Thing', 'BaseKB', vStrMon).
 7220exactlyAssertedEL_first(decontextualizedCollection, 'TheTerm', 'BaseKB', vStrMon).
 7221exactlyAssertedEL_first(decontextualizedCollection, 'TernaryRelation', 'BaseKB', vStrDef).
 7222exactlyAssertedEL_first(decontextualizedCollection, 'TernaryPredicate', 'BaseKB', vStrDef).
 7223exactlyAssertedEL_first(decontextualizedCollection, 'TernaryFunction', 'BaseKB', vStrDef).
 7224exactlyAssertedEL_first(decontextualizedCollection, 'SymmetricBinaryPredicate', 'BaseKB', vStrDef).
 7225exactlyAssertedEL_first(decontextualizedCollection, 'SubLSymbol', 'BaseKB', vStrMon).
 7226exactlyAssertedEL_first(decontextualizedCollection, 'SubLString', 'BaseKB', vStrMon).
 7227exactlyAssertedEL_first(decontextualizedCollection, 'SubLSExpression', 'BaseKB', vStrMon).
 7228exactlyAssertedEL_first(decontextualizedCollection, 'SubLRealNumber', 'BaseKB', vStrMon).
 7229exactlyAssertedEL_first(decontextualizedCollection, 'SubLPositiveInteger', 'BaseKB', vStrDef).
 7230exactlyAssertedEL_first(decontextualizedCollection, 'SubLNonVariableSymbol', 'BaseKB', vStrMon).
 7231exactlyAssertedEL_first(decontextualizedCollection, 'SubLNonVariableNonKeywordSymbol', 'BaseKB', vStrMon).
 7232exactlyAssertedEL_first(decontextualizedCollection, 'SubLNonNegativeInteger', 'BaseKB', vStrDef).
 7233exactlyAssertedEL_first(decontextualizedCollection, 'SubLList', 'BaseKB', vStrMon).
 7234exactlyAssertedEL_first(decontextualizedCollection, 'SubLKeyword', 'BaseKB', vStrMon).
 7235exactlyAssertedEL_first(decontextualizedCollection, 'SubLInteger', 'BaseKB', vStrMon).
 7236exactlyAssertedEL_first(decontextualizedCollection, 'SubLExpressionType', 'BaseKB', vStrMon).
 7237exactlyAssertedEL_first(decontextualizedCollection, 'SubLCharacter', 'BaseKB', vStrMon).
 7238exactlyAssertedEL_first(decontextualizedCollection, 'SubLAtomicTerm', 'BaseKB', vStrMon).
 7239exactlyAssertedEL_first(decontextualizedCollection, 'SubLAtom', 'BaseKB', vStrMon).
 7240exactlyAssertedEL_first(decontextualizedCollection, 'SkolemFunction', 'BaseKB', vStrMon).
 7241exactlyAssertedEL_first(decontextualizedCollection, 'SiblingDisjointCollectionType', 'BaseKB', vStrDef).
 7242exactlyAssertedEL_first(decontextualizedCollection, 'SiblingDisjointAttributeType', 'BaseKB', vStrDef).
 7243exactlyAssertedEL_first(decontextualizedCollection, 'SetOrCollection', 'BaseKB', vStrDef).
 7244exactlyAssertedEL_first(decontextualizedCollection, 'Set-Mathematical', 'BaseKB', vStrDef).
 7245exactlyAssertedEL_first(decontextualizedCollection, 'SententialRelation', 'BaseKB', vStrMon).
 7246exactlyAssertedEL_first(decontextualizedCollection, 'ScopingRelation', 'BaseKB', vStrDef).
 7247exactlyAssertedEL_first(decontextualizedCollection, 'ScalarPointValue', 'BaseKB', vStrDef).
 7248exactlyAssertedEL_first(decontextualizedCollection, 'ScalarInterval', 'BaseKB', vStrDef).
 7249exactlyAssertedEL_first(decontextualizedCollection, 'ScalarIntegralValue', 'BaseKB', vStrDef).
 7250exactlyAssertedEL_first(decontextualizedCollection, tRelation, 'BaseKB', vStrDef).
 7251exactlyAssertedEL_first(decontextualizedCollection, 'ReifiableFunction', 'BaseKB', vStrDef).
 7252exactlyAssertedEL_first(decontextualizedCollection, 'ReformulatorDirectivePredicate', 'BaseKB', vStrDef).
 7253exactlyAssertedEL_first(decontextualizedCollection, 'ReflexiveBinaryPredicate', 'BaseKB', vStrDef).
 7254exactlyAssertedEL_first(decontextualizedCollection, 'RealNumber', 'BaseKB', vStrDef).
 7255exactlyAssertedEL_first(decontextualizedCollection, 'QuintaryRelation', 'BaseKB', vStrDef).
 7256exactlyAssertedEL_first(decontextualizedCollection, 'QuintaryPredicate', 'BaseKB', vStrDef).
 7257exactlyAssertedEL_first(decontextualizedCollection, 'QuintaryFunction', 'BaseKB', vStrDef).
 7258exactlyAssertedEL_first(decontextualizedCollection, 'QuaternaryRelation', 'BaseKB', vStrDef).
 7259exactlyAssertedEL_first(decontextualizedCollection, 'QuaternaryPredicate', 'BaseKB', vStrDef).
 7260exactlyAssertedEL_first(decontextualizedCollection, 'QuaternaryFunction', 'BaseKB', vStrDef).
 7261exactlyAssertedEL_first(decontextualizedCollection, 'Quantifier', 'BaseKB', vStrDef).
 7262exactlyAssertedEL_first(decontextualizedCollection, 'ProblemSolvingCntxt', 'BaseKB', vStrDef).
 7263exactlyAssertedEL_first(decontextualizedCollection, tPred, 'BaseKB', vStrDef).
 7264exactlyAssertedEL_first(decontextualizedCollection, 'PositiveInteger', 'BaseKB', vStrDef).
 7265exactlyAssertedEL_first(decontextualizedCollection, 'PartiallyCommutativeRelation', 'BaseKB', vStrDef).
 7266exactlyAssertedEL_first(decontextualizedCollection, 'NonNegativeScalarInterval', 'BaseKB', vStrDef).
 7267exactlyAssertedEL_first(decontextualizedCollection, 'NonNegativeInteger', 'BaseKB', vStrDef).
 7268exactlyAssertedEL_first(decontextualizedCollection, 'Multigraph', 'BaseKB', vStrDef).
 7269exactlyAssertedEL_first(decontextualizedCollection, 'MonthOfYearType', 'BaseKB', vStrDef).
 7270exactlyAssertedEL_first(decontextualizedCollection, 'MicrotheoryDesignatingRelation', 'BaseKB', vStrDef).
 7271exactlyAssertedEL_first(decontextualizedCollection, 'Microtheory', 'BaseKB', vStrMon).
 7272exactlyAssertedEL_first(decontextualizedCollection, 'LogicalConnective', 'BaseKB', vStrDef).
 7273exactlyAssertedEL_first(decontextualizedCollection, 'List', 'BaseKB', vStrDef).
 7274exactlyAssertedEL_first(decontextualizedCollection, 'IrreflexiveBinaryPredicate', 'BaseKB', vStrDef).
 7275exactlyAssertedEL_first(decontextualizedCollection, 'InterArgIsaPredicate', 'BaseKB', vStrDef).
 7276exactlyAssertedEL_first(decontextualizedCollection, 'InterArgFormatPredicate', 'BaseKB', vStrDef).
 7277exactlyAssertedEL_first(decontextualizedCollection, 'Integer', 'BaseKB', vStrDef).
 7278exactlyAssertedEL_first(decontextualizedCollection, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrMon).
 7279exactlyAssertedEL_first(decontextualizedCollection, 'Individual', 'BaseKB', vStrDef).
 7280exactlyAssertedEL_first(decontextualizedCollection, 'HypotheticalContext', 'BaseKB', vStrDef).
 7281exactlyAssertedEL_first(decontextualizedCollection, 'HLExternalIDString', 'BaseKB', vStrMon).
 7282exactlyAssertedEL_first(decontextualizedCollection, tFunction, 'BaseKB', vStrDef).
 7283exactlyAssertedEL_first(decontextualizedCollection, 'Format', 'BaseKB', vStrDef).
 7284exactlyAssertedEL_first(decontextualizedCollection, 'FixedAritySkolemFunction', 'BaseKB', vStrDef).
 7285exactlyAssertedEL_first(decontextualizedCollection, 'FixedAritySkolemFuncN', 'BaseKB', vStrDef).
 7286exactlyAssertedEL_first(decontextualizedCollection, 'FixedArityRelation', 'BaseKB', vStrDef).
 7287exactlyAssertedEL_first(decontextualizedCollection, 'ExistentialQuantifier-Bounded', 'BaseKB', vStrMon).
 7288exactlyAssertedEL_first(decontextualizedCollection, 'ExistentialQuantifier', 'BaseKB', vStrDef).
 7289exactlyAssertedEL_first(decontextualizedCollection, 'ExceptionPredicate', 'BaseKB', vStrDef).
 7290exactlyAssertedEL_first(decontextualizedCollection, 'EvaluatableRelation', 'BaseKB', vStrDef).
 7291exactlyAssertedEL_first(decontextualizedCollection, 'EvaluatableFunction', 'BaseKB', vStrDef).
 7292exactlyAssertedEL_first(decontextualizedCollection, 'ELRelation-Reversible', 'BaseKB', vStrMon).
 7293exactlyAssertedEL_first(decontextualizedCollection, 'ELRelation-OneWay', 'BaseKB', vStrDef).
 7294exactlyAssertedEL_first(decontextualizedCollection, 'ELRelation', 'BaseKB', vStrMon).
 7295exactlyAssertedEL_first(decontextualizedCollection, 'DistributingMetaKnowledgePredicate', 'BaseKB', vStrDef).
 7296exactlyAssertedEL_first(decontextualizedCollection, 'DisjointCollectionType', 'BaseKB', vStrDef).
 7297exactlyAssertedEL_first(decontextualizedCollection, 'DirectedMultigraph', 'BaseKB', vStrDef).
 7298exactlyAssertedEL_first(decontextualizedCollection, 'DefaultMonotonicPredicate', 'BaseKB', vStrDef).
 7299exactlyAssertedEL_first(decontextualizedCollection, ftVar, 'BaseKB', vStrMon).
 7300exactlyAssertedEL_first(decontextualizedCollection, 'CycLTruthValueSentence', 'BaseKB', vStrMon).
 7301exactlyAssertedEL_first(decontextualizedCollection, 'CycLTerm', 'BaseKB', vStrMon).
 7302exactlyAssertedEL_first(decontextualizedCollection, 'CycLSentence-Assertible', 'BaseKB', vStrMon).
 7303exactlyAssertedEL_first(decontextualizedCollection, 'CycLSentence-Askable', 'BaseKB', vStrMon).
 7304exactlyAssertedEL_first(decontextualizedCollection, 'CycLSentence', 'BaseKB', vStrMon).
 7305exactlyAssertedEL_first(decontextualizedCollection, 'CycLRuleAssertion', 'BaseKB', vStrMon).
 7306exactlyAssertedEL_first(decontextualizedCollection, 'CycLRepresentedTerm', 'BaseKB', vStrMon).
 7307exactlyAssertedEL_first(decontextualizedCollection, 'CycLRepresentedAtomicTerm', 'BaseKB', vStrMon).
 7308exactlyAssertedEL_first(decontextualizedCollection, 'CycLReifiedDenotationalTerm', 'BaseKB', vStrMon).
 7309exactlyAssertedEL_first(decontextualizedCollection, 'CycLReifiableNonAtomicTerm', 'BaseKB', vStrMon).
 7310exactlyAssertedEL_first(decontextualizedCollection, 'CycLReifiableDenotationalTerm', 'BaseKB', vStrMon).
 7311exactlyAssertedEL_first(decontextualizedCollection, 'CycLPropositionalSentence', 'BaseKB', vStrMon).
 7312exactlyAssertedEL_first(decontextualizedCollection, 'CycLOpenSentence', 'BaseKB', vStrMon).
 7313exactlyAssertedEL_first(decontextualizedCollection, 'CycLOpenNonAtomicTerm', 'BaseKB', vStrMon).
 7314exactlyAssertedEL_first(decontextualizedCollection, 'CycLOpenFormula', 'BaseKB', vStrMon).
 7315exactlyAssertedEL_first(decontextualizedCollection, 'CycLOpenExpression', 'BaseKB', vStrMon).
 7316exactlyAssertedEL_first(decontextualizedCollection, 'CycLOpenDenotationalTerm', 'BaseKB', vStrMon).
 7317exactlyAssertedEL_first(decontextualizedCollection, 'CycLNonAtomicTerm-Assertible', 'BaseKB', vStrMon).
 7318exactlyAssertedEL_first(decontextualizedCollection, 'CycLNonAtomicTerm-Askable', 'BaseKB', vStrMon).
 7319exactlyAssertedEL_first(decontextualizedCollection, 'CycLNonAtomicTerm', 'BaseKB', vStrMon).
 7320exactlyAssertedEL_first(decontextualizedCollection, 'CycLNonAtomicReifiedTerm', 'BaseKB', vStrMon).
 7321exactlyAssertedEL_first(decontextualizedCollection, 'CycLIndexedTerm', 'BaseKB', vStrMon).
 7322exactlyAssertedEL_first(decontextualizedCollection, 'CycLGenericRelationFormula', 'BaseKB', vStrMon).
 7323exactlyAssertedEL_first(decontextualizedCollection, 'CycLGAFAssertion', 'BaseKB', vStrMon).
 7324exactlyAssertedEL_first(decontextualizedCollection, 'CycLFormulaicSentence', 'BaseKB', vStrMon).
 7325exactlyAssertedEL_first(decontextualizedCollection, 'CycLFormula', 'BaseKB', vStrMon).
 7326exactlyAssertedEL_first(decontextualizedCollection, ttExpressionType, 'BaseKB', vStrDef).
 7327exactlyAssertedEL_first(decontextualizedCollection, 'CycLExpression-Assertible', 'BaseKB', vStrMon).
 7328exactlyAssertedEL_first(decontextualizedCollection, 'CycLExpression-Askable', 'BaseKB', vStrMon).
 7329exactlyAssertedEL_first(decontextualizedCollection, 'CycLExpression', 'BaseKB', vStrMon).
 7330exactlyAssertedEL_first(decontextualizedCollection, 'CycLDenotationalTerm-Assertible', 'BaseKB', vStrMon).
 7331exactlyAssertedEL_first(decontextualizedCollection, 'CycLDenotationalTerm', 'BaseKB', vStrMon).
 7332exactlyAssertedEL_first(decontextualizedCollection, 'CycLDeducedAssertion', 'BaseKB', vStrMon).
 7333exactlyAssertedEL_first(decontextualizedCollection, 'CycLConstant', 'BaseKB', vStrMon).
 7334exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedSentence', 'BaseKB', vStrMon).
 7335exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedNonAtomicTerm', 'BaseKB', vStrMon).
 7336exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedFormula', 'BaseKB', vStrMon).
 7337exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedExpression', 'BaseKB', vStrMon).
 7338exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedDenotationalTerm', 'BaseKB', vStrMon).
 7339exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedAtomicTerm', 'BaseKB', vStrMon).
 7340exactlyAssertedEL_first(decontextualizedCollection, 'CycLClosedAtomicSentence', 'BaseKB', vStrMon).
 7341exactlyAssertedEL_first(decontextualizedCollection, 'CycLAtomicTerm', 'BaseKB', vStrMon).
 7342exactlyAssertedEL_first(decontextualizedCollection, 'CycLAtomicSentence', 'BaseKB', vStrMon).
 7343exactlyAssertedEL_first(decontextualizedCollection, 'CycLAtomicAssertion', 'BaseKB', vStrMon).
 7344exactlyAssertedEL_first(decontextualizedCollection, 'CycLAssertionDirection', 'BaseKB', vStrDef).
 7345exactlyAssertedEL_first(decontextualizedCollection, 'CycLAssertion', 'BaseKB', vStrMon).
 7346exactlyAssertedEL_first(decontextualizedCollection, 'CycLAssertedAssertion', 'BaseKB', vStrMon).
 7347exactlyAssertedEL_first(decontextualizedCollection, 'CommutativeRelation', 'BaseKB', vStrDef).
 7348exactlyAssertedEL_first(decontextualizedCollection, 'CollectionDenotingFunction', 'BaseKB', vStrDef).
 7349exactlyAssertedEL_first(decontextualizedCollection, tCol, 'BaseKB', vStrDef).
 7350exactlyAssertedEL_first(decontextualizedCollection, 'CanonicalizerDirective', 'BaseKB', vStrMon).
 7351exactlyAssertedEL_first(decontextualizedCollection, 'BroadMicrotheory', 'BaseKB', vStrMon).
 7352exactlyAssertedEL_first(decontextualizedCollection, 'BookkeepingPredicate', 'BaseKB', vStrDef).
 7353exactlyAssertedEL_first(decontextualizedCollection, 'BinaryRelation', 'BaseKB', vStrDef).
 7354exactlyAssertedEL_first(decontextualizedCollection, 'BinaryPredicate', 'BaseKB', vStrDef).
 7355exactlyAssertedEL_first(decontextualizedCollection, 'BinaryFunction', 'BaseKB', vStrDef).
 7356exactlyAssertedEL_first(decontextualizedCollection, 'AtemporalNecessarilyEssentialCollectionType', 'BaseKB', vStrMon).
 7357exactlyAssertedEL_first(decontextualizedCollection, 'AsymmetricBinaryPredicate', 'BaseKB', vStrDef).
 7358exactlyAssertedEL_first(decontextualizedCollection, 'AssociativeRelation', 'BaseKB', vStrDef).
 7359exactlyAssertedEL_first(decontextualizedCollection, 'ArgTypeTernaryPredicate', 'BaseKB', vStrDef).
 7360exactlyAssertedEL_first(decontextualizedCollection, 'ArgTypePredicate', 'BaseKB', vStrDef).
 7361exactlyAssertedEL_first(decontextualizedCollection, 'ArgTypeBinaryPredicate', 'BaseKB', vStrDef).
 7362exactlyAssertedEL_first(decontextualizedCollection, 'ArgQuotedIsaTernaryPredicate', 'BaseKB', vStrMon).
 7363exactlyAssertedEL_first(decontextualizedCollection, 'ArgIsaTernaryPredicate', 'BaseKB', vStrDef).
 7364exactlyAssertedEL_first(decontextualizedCollection, 'ArgIsaBinaryPredicate', 'BaseKB', vStrDef).
 7365exactlyAssertedEL_first(decontextualizedCollection, 'ArgGenlTernaryPredicate', 'BaseKB', vStrDef).
 7366exactlyAssertedEL_first(decontextualizedCollection, 'ArgGenlQuantityTernaryPredicate', 'BaseKB', vStrDef).
 7367exactlyAssertedEL_first(decontextualizedCollection, 'ArgGenlQuantityBinaryPredicate', 'BaseKB', vStrDef).
 7368exactlyAssertedEL_first(decontextualizedCollection, 'ArgGenlBinaryPredicate', 'BaseKB', vStrDef).
 7369exactlyAssertedEL_first(decontextualizedCollection, 'ArgConstraintPredicate', 'BaseKB', vStrDef).
 7370exactlyAssertedEL_first(decontextualizedCollection, 'AntiTransitiveBinaryPredicate', 'BaseKB', vStrDef).
 7371exactlyAssertedEL_first(decontextualizedCollection, 'AntiSymmetricBinaryPredicate', 'BaseKB', vStrDef).
 7372exactlyAssertedEL_next(constrainsArg, argsIsa, 0, 'CoreCycLMt', vStrDef).
 7373exactlyAssertedEL_next(constrainsArg, argsGenl, 0, 'CoreCycLMt', vStrDef).
 7374exactlyAssertedEL_next(constrainsArg, arg6SometimesIsa, 6, 'CoreCycLMt', vStrMon).
 7375exactlyAssertedEL_next(constrainsArg, arg6QuotedIsa, 6, 'CoreCycLMt', vStrMon).
 7376exactlyAssertedEL_next(constrainsArg, arg6Isa, 6, 'CoreCycLMt', vStrDef).
 7377exactlyAssertedEL_next(constrainsArg, arg6Genl, 6, 'CoreCycLMt', vStrDef).
 7378exactlyAssertedEL_next(constrainsArg, arg5SometimesIsa, 5, 'CoreCycLMt', vStrMon).
 7379exactlyAssertedEL_next(constrainsArg, arg5QuotedIsa, 5, 'CoreCycLMt', vStrMon).
 7380exactlyAssertedEL_next(constrainsArg, arg5Isa, 5, 'CoreCycLMt', vStrDef).
 7381exactlyAssertedEL_next(constrainsArg, arg5Genl, 5, 'CoreCycLMt', vStrDef).
 7382exactlyAssertedEL_next(constrainsArg, arg5Format, 5, 'CoreCycLMt', vStrDef).
 7383exactlyAssertedEL_next(constrainsArg, arg4SometimesIsa, 4, 'CoreCycLMt', vStrMon).
 7384exactlyAssertedEL_next(constrainsArg, arg4QuotedIsa, 4, 'CoreCycLMt', vStrMon).
 7385exactlyAssertedEL_next(constrainsArg, arg4Isa, 4, 'CoreCycLMt', vStrDef).
 7386exactlyAssertedEL_next(constrainsArg, arg4Genl, 4, 'CoreCycLMt', vStrDef).
 7387exactlyAssertedEL_next(constrainsArg, arg4Format, 4, 'CoreCycLMt', vStrDef).
 7388exactlyAssertedEL_next(constrainsArg, arg3SometimesIsa, 3, 'CoreCycLMt', vStrMon).
 7389exactlyAssertedEL_next(constrainsArg, arg3QuotedIsa, 3, 'CoreCycLMt', vStrMon).
 7390exactlyAssertedEL_next(constrainsArg, arg3Isa, 3, 'CoreCycLMt', vStrDef).
 7391exactlyAssertedEL_next(constrainsArg, arg3Genl, 3, 'CoreCycLMt', vStrDef).
 7392exactlyAssertedEL_next(constrainsArg, arg3Format, 3, 'CoreCycLMt', vStrDef).
 7393exactlyAssertedEL_next(constrainsArg, arg2SometimesIsa, 2, 'CoreCycLMt', vStrMon).
 7394exactlyAssertedEL_next(constrainsArg, arg2QuotedIsa, 2, 'CoreCycLMt', vStrMon).
 7395exactlyAssertedEL_next(constrainsArg, arg2Isa, 2, 'UniversalVocabularyMt', vStrMon).
 7396exactlyAssertedEL_next(constrainsArg, arg2Isa, 2, 'CoreCycLMt', vStrDef).
 7397exactlyAssertedEL_next(constrainsArg, arg2Genl, 2, 'UniversalVocabularyMt', vStrDef).
 7398exactlyAssertedEL_next(constrainsArg, arg2Genl, 2, 'CoreCycLMt', vStrDef).
 7399exactlyAssertedEL_next(constrainsArg, arg2Format, 2, 'CoreCycLMt', vStrDef).
 7400exactlyAssertedEL_next(constrainsArg, arg1SometimesIsa, 1, 'CoreCycLMt', vStrMon).
 7401exactlyAssertedEL_next(constrainsArg, arg1QuotedIsa, 1, 'CoreCycLMt', vStrMon).
 7402exactlyAssertedEL_next(constrainsArg, arg1Isa, 1, 'UniversalVocabularyMt', vStrMon).
 7403exactlyAssertedEL_next(constrainsArg, arg1Isa, 1, 'CoreCycLMt', vStrDef).
 7404exactlyAssertedEL_next(constrainsArg, arg1Genl, 1, 'UniversalVocabularyMt', vStrDef).
 7405exactlyAssertedEL_next(constrainsArg, arg1Genl, 1, 'CoreCycLMt', vStrDef).
 7406exactlyAssertedEL_next(constrainsArg, arg1Format, 1, 'CoreCycLMt', vStrDef).
 7407exactlyAssertedEL_next(constrainsArg, 'interArgIsa5-4', 4, 'CoreCycLMt', vStrDef).
 7408exactlyAssertedEL_next(constrainsArg, 'interArgIsa5-3', 3, 'CoreCycLMt', vStrDef).
 7409exactlyAssertedEL_next(constrainsArg, 'interArgIsa5-2', 2, 'CoreCycLMt', vStrDef).
 7410exactlyAssertedEL_next(constrainsArg, 'interArgIsa5-1', 1, 'CoreCycLMt', vStrDef).
 7411exactlyAssertedEL_next(constrainsArg, 'interArgIsa4-5', 5, 'CoreCycLMt', vStrDef).
 7412exactlyAssertedEL_next(constrainsArg, 'interArgIsa4-3', 3, 'CoreCycLMt', vStrDef).
 7413exactlyAssertedEL_next(constrainsArg, 'interArgIsa4-2', 2, 'CoreCycLMt', vStrDef).
 7414exactlyAssertedEL_next(constrainsArg, 'interArgIsa4-1', 1, 'CoreCycLMt', vStrDef).
 7415exactlyAssertedEL_next(constrainsArg, 'interArgIsa3-5', 5, 'CoreCycLMt', vStrDef).
 7416exactlyAssertedEL_next(constrainsArg, 'interArgIsa3-4', 4, 'CoreCycLMt', vStrDef).
 7417exactlyAssertedEL_next(constrainsArg, 'interArgIsa3-2', 2, 'CoreCycLMt', vStrDef).
 7418exactlyAssertedEL_next(constrainsArg, 'interArgIsa3-1', 1, 'CoreCycLMt', vStrDef).
 7419exactlyAssertedEL_next(constrainsArg, 'interArgIsa2-5', 5, 'CoreCycLMt', vStrDef).
 7420exactlyAssertedEL_next(constrainsArg, 'interArgIsa2-4', 4, 'CoreCycLMt', vStrDef).
 7421exactlyAssertedEL_next(constrainsArg, 'interArgIsa2-3', 3, 'CoreCycLMt', vStrDef).
 7422exactlyAssertedEL_next(constrainsArg, 'interArgIsa2-1', 1, 'CoreCycLMt', vStrDef).
 7423exactlyAssertedEL_next(constrainsArg, 'interArgIsa1-5', 5, 'CoreCycLMt', vStrDef).
 7424exactlyAssertedEL_next(constrainsArg, 'interArgIsa1-4', 4, 'CoreCycLMt', vStrDef).
 7425exactlyAssertedEL_next(constrainsArg, 'interArgIsa1-3', 3, 'CoreCycLMt', vStrDef).
 7426exactlyAssertedEL_next(constrainsArg, 'interArgIsa1-2', 2, 'CoreCycLMt', vStrDef).
 7427exactlyAssertedEL_next(constrainsArg, 'interArgGenl1-2', 2, 'CoreCycLMt', vStrDef).
 7428exactlyAssertedEL_next(constrainsArg, 'interArgFormat1-2', 2, 'CoreCycLMt', vStrDef).
 7429exactlyAssertedEL_next(conceptuallyRelated, querySentence, pragmaticRequirement, 'UniversalVocabularyMt', vStrDef).
 7430exactlyAssertedEL_next(conceptuallyRelated, querySentence, meetsPragmaticRequirement, 'UniversalVocabularyMt', vStrDef).
 7431exactlyAssertedEL_next(conceptuallyRelated, pragmaticRequirement, pragmaticallyNormal, 'BaseKB', vStrMon).
 7432exactlyAssertedEL_next(conceptuallyRelated, pragmaticRequirement, meetsPragmaticRequirement, 'BaseKB', vStrMon).
 7433exactlyAssertedEL_next(conceptuallyRelated, knownAntecedentRule, knownSentence, 'UniversalVocabularyMt', vStrMon).
 7434exactlyAssertedEL_next(conceptuallyRelated, knownAntecedentRule, backchainRequired, 'UniversalVocabularyMt', vStrMon).
 7435exactlyAssertedEL_next(conceptuallyRelated, exceptWhen, abnormal, 'BaseKB', vStrMon).
 7436exactlyAssertedEL_next(conceptuallyRelated, exceptFor, abnormal, 'BaseKB', vStrMon).
 7437exactlyAssertedEL_next(conceptuallyRelated, exactlyAssertedEL_next, knownSentence, 'UniversalVocabularyMt', vStrDef).
 7438exactlyAssertedEL_next(conceptuallyRelated, commutativeInArgs, 'CommutativeRelation', 'BaseKB', vStrMon).
 7439exactlyAssertedEL_next(conceptuallyRelated, collectionIsaBackchainEncouraged, isa, 'BaseKB', vStrMon).
 7440exactlyAssertedEL_next(conceptuallyRelated, collectionIsaBackchainEncouraged, tCol, 'BaseKB', vStrMon).
 7441exactlyAssertedEL_next(conceptuallyRelated, collectionGenlsBackchainEncouraged, isa, 'BaseKB', vStrMon).
 7442exactlyAssertedEL_next(conceptuallyRelated, collectionGenlsBackchainEncouraged, tCol, 'BaseKB', vStrMon).
 7443exactlyAssertedEL_next(conceptuallyRelated, collectionBackchainRequired, isa, 'BaseKB', vStrMon).
 7444exactlyAssertedEL_next(conceptuallyRelated, collectionBackchainRequired, tCol, 'BaseKB', vStrMon).
 7445exactlyAssertedEL_next(conceptuallyRelated, collectionBackchainEncouraged, isa, 'BaseKB', vStrMon).
 7446exactlyAssertedEL_next(conceptuallyRelated, collectionBackchainEncouraged, tCol, 'BaseKB', vStrMon).
 7447exactlyAssertedEL_next(conceptuallyRelated, abnormal, pragmaticallyNormal, 'BaseKB', vStrMon).
 7448exactlyAssertedEL_next(conceptuallyRelated, abnormal, meetsPragmaticRequirement, 'BaseKB', vStrMon).
 7449exactlyAssertedEL_next(conceptuallyRelated, 'SubLQuoteFn', trueSubL, 'UniversalVocabularyMt', vStrDef).
 7450exactlyAssertedEL_next(conceptuallyRelated, 'SubLQuoteFn', performSubL, 'UniversalVocabularyMt', vStrDef).
 7451exactlyAssertedEL_next(conceptuallyRelated, 'SubLQuoteFn', 'ExpandSubLFn', 'UniversalVocabularyMt', vStrDef).
 7452exactlyAssertedEL_next(conceptuallyRelated, 'SubLQuoteFn', 'EvaluateSubLFn', 'UniversalVocabularyMt', vStrDef).
 7453exactlyAssertedEL_next(conceptuallyRelated, 'MonotonicallyFalse', 'False', 'BaseKB', vStrMon).
 7454exactlyAssertedEL_next(conceptuallyRelated, 'IrreflexiveBinaryPredicate', interArgDifferent, 'BaseKB', vStrMon).
 7455exactlyAssertedEL_next(conceptuallyRelated, 'DefaultFalse', 'False', 'BaseKB', vStrMon).
 7456exactlyAssertedEL_next(conceptuallyRelated, 'CycHLTruthValue', 'TruthValue', 'BaseKB', vStrDef).
 7457exactlyAssertedEL_next(completelyEnumerableCollection, 'TruthValue', 'BaseKB', vStrMon).
 7458exactlyAssertedEL_next(completelyEnumerableCollection, 'TheTerm', 'BaseKB', vStrDef).
 7459exactlyAssertedEL_next(completelyEnumerableCollection, 'SkolemFunction', 'BaseKB', vStrMon).
 7460exactlyAssertedEL_next(completelyEnumerableCollection, 'SententialRelation', 'UniversalVocabularyMt', vStrDef).
 7461exactlyAssertedEL_next(completelyEnumerableCollection, 'Quantifier', 'UniversalVocabularyMt', vStrDef).
 7462exactlyAssertedEL_next(completelyEnumerableCollection, 'ProblemSolvingCntxt', 'BaseKB', vStrMon).
 7463exactlyAssertedEL_next(completelyEnumerableCollection, 'LogicalConnective', 'UniversalVocabularyMt', vStrDef).
 7464exactlyAssertedEL_next(completelyEnumerableCollection, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', vStrMon).
 7465exactlyAssertedEL_next(completelyEnumerableCollection, 'HumanCyclist', 'UniversalVocabularyMt', vStrDef).
 7466exactlyAssertedEL_next(completelyEnumerableCollection, 'ExistentialQuantifier-Bounded', 'UniversalVocabularyMt', vStrDef).
 7467exactlyAssertedEL_next(completelyEnumerableCollection, 'ExceptionPredicate', 'BaseKB', vStrMon).
 7468exactlyAssertedEL_next(completelyEnumerableCollection, 'DayOfWeekType', 'UniversalVocabularyMt', vStrDef).
 7469exactlyAssertedEL_next(completelyEnumerableCollection, 'CycProvabilityStatus', 'UniversalVocabularyMt', vStrDef).
 7470exactlyAssertedEL_next(completelyEnumerableCollection, 'CycLRuleAssertion', 'BaseKB', vStrMon).
 7471exactlyAssertedEL_next(completelyEnumerableCollection, 'CycLGAFAssertion', 'BaseKB', vStrMon).
 7472exactlyAssertedEL_next(completelyEnumerableCollection, 'CycLDeducedAssertion', 'BaseKB', vStrMon).
 7473exactlyAssertedEL_next(completelyEnumerableCollection, 'CycLAssertionDirection', 'BaseKB', vStrMon).
 7474exactlyAssertedEL_next(completelyEnumerableCollection, 'CycLAssertedAssertion', 'BaseKB', vStrMon).
 7475exactlyAssertedEL_next(completelyEnumerableCollection, 'CycInferenceProblemLinkStatus', 'UniversalVocabularyMt', vStrDef).
 7476exactlyAssertedEL_next(completelyEnumerableCollection, 'CanonicalizerDirective', 'CoreCycLImplementationMt', vStrMon).
 7477exactlyAssertedEL_next(completelyEnumerableCollection, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrDef).
 7478exactlyAssertedEL_next(completelyEnumerableCollection, 'ArgIsaBinaryPredicate', 'BaseKB', vStrMon).
 7479exactlyAssertedEL_next(completelyEnumerableCollection, 'ArgGenlQuantityTernaryPredicate', 'BaseKB', vStrDef).
 7480exactlyAssertedEL_next(completelyEnumerableCollection, 'ArgGenlQuantityBinaryPredicate', 'BaseKB', vStrDef).
 7481exactlyAssertedEL_next(completelyEnumerableCollection, 'ArgGenlBinaryPredicate', 'BaseKB', vStrMon).
 7482exactlyAssertedEL_next(completelyDecidableCollection, 'Microtheory', 'UniversalVocabularyMt', vStrMon).
 7483exactlyAssertedEL_next(completelyDecidableCollection, 'IndeterminateTerm', 'BaseKB', vStrMon).
 7484exactlyAssertedEL_next(completelyDecidableCollection, 'HLPrototypicalTerm', 'BaseKB', vStrMon).
 7485exactlyAssertedEL_next(completeExtentEnumerableForValueInArg, indexicalReferent, 'TheUser', 1, 'UniversalVocabularyMt', vStrMon).
 7486exactlyAssertedEL_next(completeExtentEnumerableForValueInArg, indexicalReferent, 'QueryMt', 1, 'UniversalVocabularyMt', vStrMon).
 7487exactlyAssertedEL_next(completeExtentEnumerableForArg, termOfUnit, 2, 'UniversalVocabularyMt', vStrMon).
 7488exactlyAssertedEL_next(completeExtentEnumerableForArg, termOfUnit, 1, 'UniversalVocabularyMt', vStrMon).
 7489exactlyAssertedEL_next(completeExtentEnumerableForArg, conceptuallyRelated, 1, 'UniversalVocabularyMt', vStrMon).
 7490exactlyAssertedEL_next(completeExtentEnumerable, termDependsOn, 'UniversalVocabularyMt', vStrDef).
 7491exactlyAssertedEL_next(completeExtentEnumerable, termChosen, 'UniversalVocabularyMt', vStrMon).
 7492exactlyAssertedEL_next(completeExtentEnumerable, quotedArgument, 'UniversalVocabularyMt', vStrMon).
 7493exactlyAssertedEL_next(completeExtentEnumerable, pragmaticRequirement, 'UniversalVocabularyMt', vStrMon).
 7494exactlyAssertedEL_next(completeExtentEnumerable, performSubL, 'UniversalVocabularyMt', vStrMon).
 7495exactlyAssertedEL_next(completeExtentEnumerable, operatorFormulas, 'UniversalVocabularyMt', vStrMon).
 7496exactlyAssertedEL_next(completeExtentEnumerable, natFunction, 'UniversalVocabularyMt', vStrMon).
 7497exactlyAssertedEL_next(completeExtentEnumerable, natArgumentsEqual, 'UniversalVocabularyMt', vStrMon).
 7498exactlyAssertedEL_next(completeExtentEnumerable, natArgument, 'UniversalVocabularyMt', vStrMon).
 7499exactlyAssertedEL_next(completeExtentEnumerable, myCreator, 'BookkeepingMt', vStrMon).
 7500exactlyAssertedEL_next(completeExtentEnumerable, myCreationTime, 'BookkeepingMt', vStrMon).
 7501exactlyAssertedEL_next(completeExtentEnumerable, myCreationSecond, 'BookkeepingMt', vStrMon).
 7502exactlyAssertedEL_next(completeExtentEnumerable, myCreationPurpose, 'UniversalVocabularyMt', vStrMon).
 7503exactlyAssertedEL_next(completeExtentEnumerable, formulaArity, 'UniversalVocabularyMt', vStrMon).
 7504exactlyAssertedEL_next(completeExtentEnumerable, exactlyAssertedEL_next, 'UniversalVocabularyMt', vStrMon).
 7505exactlyAssertedEL_next(completeExtentEnumerable, evaluate, 'UniversalVocabularyMt', vStrMon).
 7506exactlyAssertedEL_next(completeExtentEnumerable, equalSymbols, 'UniversalVocabularyMt', vStrMon).
 7507exactlyAssertedEL_next(completeExtentEnumerable, definingMt, 'UniversalVocabularyMt', vStrMon).
 7508exactlyAssertedEL_next(completeExtentEnumerable, cycTransformationProofRule, 'UniversalVocabularyMt', vStrMon).
 7509exactlyAssertedEL_next(completeExtentEnumerable, cycTransformationProofBindings, 'UniversalVocabularyMt', vStrMon).
 7510exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreTerms, 'UniversalVocabularyMt', vStrMon).
 7511exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreProofCount, 'UniversalVocabularyMt', vStrMon).
 7512exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreProblems, 'UniversalVocabularyMt', vStrMon).
 7513exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreProblemCount, 'UniversalVocabularyMt', vStrMon).
 7514exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreLinkCount, 'UniversalVocabularyMt', vStrMon).
 7515exactlyAssertedEL_next(completeExtentEnumerable, cycProblemStoreInferenceCount, 'UniversalVocabularyMt', vStrMon).
 7516exactlyAssertedEL_next(completeExtentEnumerable, cycProblemQueryTerms, 'UniversalVocabularyMt', vStrMon).
 7517exactlyAssertedEL_next(completeExtentEnumerable, cycProblemQuerySentence, 'UniversalVocabularyMt', vStrMon).
 7518exactlyAssertedEL_next(completeExtentEnumerable, cycProblemProvabilityStatus, 'UniversalVocabularyMt', vStrMon).
 7519exactlyAssertedEL_next(completeExtentEnumerable, constantName, 'UniversalVocabularyMt', vStrMon).
 7520exactlyAssertedEL_next(completeExtentEnumerable, constantID, 'UniversalVocabularyMt', vStrMon).
 7521exactlyAssertedEL_next(completeExtentEnumerable, constantGUID, 'UniversalVocabularyMt', vStrMon).
 7522exactlyAssertedEL_next(completeExtentEnumerable, comment, 'UniversalVocabularyMt', vStrMon).
 7523exactlyAssertedEL_next(completeExtentEnumerable, collectionIsaBackchainRequired, 'UniversalVocabularyMt', vStrMon).
 7524exactlyAssertedEL_next(completeExtentEnumerable, collectionIsaBackchainEncouraged, 'UniversalVocabularyMt', vStrMon).
 7525exactlyAssertedEL_next(completeExtentEnumerable, collectionGenlsBackchainRequired, 'UniversalVocabularyMt', vStrMon).
 7526exactlyAssertedEL_next(completeExtentEnumerable, collectionGenlsBackchainEncouraged, 'UniversalVocabularyMt', vStrMon).
 7527exactlyAssertedEL_next(completeExtentEnumerable, collectionBackchainEncouraged, 'UniversalVocabularyMt', vStrMon).
 7528exactlyAssertedEL_next(completeExtentEnumerable, backchainRequired, 'UniversalVocabularyMt', vStrMon).
 7529exactlyAssertedEL_next(completeExtentEnumerable, backchainForbiddenWhenUnboundInArg, 'UniversalVocabularyMt', vStrMon).
 7530exactlyAssertedEL_next(completeExtentEnumerable, backchainForbidden, 'UniversalVocabularyMt', vStrMon).
 7531exactlyAssertedEL_next(completeExtentEnumerable, assertionDirection, 'UniversalVocabularyMt', vStrMon).
 7532exactlyAssertedEL_next(completeExtentEnumerable, assertedTermSentences, 'UniversalVocabularyMt', vStrMon).
 7533exactlyAssertedEL_next(completeExtentEnumerable, knownSentence, 'UniversalVocabularyMt', vStrMon).
 7534exactlyAssertedEL_next(completeExtentEnumerable, assertedPredicateArg, 'UniversalVocabularyMt', vStrMon).
 7535exactlyAssertedEL_next(completeExtentEnumerable, admittedSentence, 'UniversalVocabularyMt', vStrMon).
 7536exactlyAssertedEL_next(completeExtentEnumerable, admittedArgument, 'UniversalVocabularyMt', vStrMon).
 7537exactlyAssertedEL_next(completeExtentEnumerable, 'ist-Asserted', 'UniversalVocabularyMt', vStrMon).
 7538exactlyAssertedEL_next(completeExtentDecidable, unknownSentence, 'UniversalVocabularyMt', vStrMon).
 7539exactlyAssertedEL_next(completeExtentDecidable, termOfUnit, 'UniversalVocabularyMt', vStrMon).
 7540exactlyAssertedEL_next(completeExtentDecidable, sentenceImplies, 'UniversalVocabularyMt', vStrMon).
 7541exactlyAssertedEL_next(completeExtentDecidable, sentenceEquiv, 'UniversalVocabularyMt', vStrMon).
 7542exactlyAssertedEL_next(completeExtentDecidable, mtVisible, 'UniversalVocabularyMt', vStrMon).
 7543exactlyAssertedEL_next(completeExtentDecidable, knownSentence, 'UniversalVocabularyMt', vStrMon).
 7544exactlyAssertedEL_next(completeExtentDecidable, integerBetween, 'UniversalVocabularyMt', vStrMon).
 7545exactlyAssertedEL_next(completeExtentDecidable, indexicalReferent, 'UniversalVocabularyMt', vStrMon).
 7546exactlyAssertedEL_next(completeExtentDecidable, differentSymbols, 'UniversalVocabularyMt', vStrMon).
 7547exactlyAssertedEL_next(completeExtentDecidable, consistent, 'UniversalVocabularyMt', vStrMon).
 7548exactlyAssertedEL_next(completeExtentDecidable, conceptuallyRelated, 'UniversalVocabularyMt', vStrMon).
 7549exactlyAssertedEL_next(completeExtentDecidable, 'equalStrings-CaseInsensitive', 'UniversalVocabularyMt', vStrMon).
 7550exactlyAssertedEL_next(completeExtentAsserted, salientAssertions, 'BaseKB', vStrDef).
 7551exactlyAssertedEL_next(completeExtentAsserted, resultIsaArgIsa, 'UniversalVocabularyMt', vStrMon).
 7552exactlyAssertedEL_next(completeExtentAsserted, omitArgIsa, 'UniversalVocabularyMt', vStrDef).
 7553exactlyAssertedEL_next(completeExtentAsserted, instanceElementType, 'UniversalVocabularyMt', vStrMon).
 7554exactlyAssertedEL_next(completeExtentAsserted, hypotheticalTerm, 'UniversalVocabularyMt', vStrMon).
 7555exactlyAssertedEL_next(completeExtentAsserted, elInverse, 'UniversalVocabularyMt', vStrDef).
 7556exactlyAssertedEL_next(commutativeInArgsAndRest, commutativeInArgsAndRest, 2, 'BaseKB', vStrDef).
 7557exactlyAssertedEL_next(commutativeInArgsAndRest, commutativeInArgs, 2, 'BaseKB', vStrDef).
 7558exactlyAssertedEL_next(commutativeInArgs, multiplicationUnits, 1, 2, 'BaseKB', vStrMon).
 7559exactlyAssertedEL_next(commutativeInArgs, interArgDifferent, 2, 3, 'BaseKB', vStrMon).
 7560exactlyAssertedEL_next(comment, xor, "The LogicalConnective that represents exclusive-or in CycL. Unlike or, which is a VariableArityRelation, xor takes two arguments, which must be instances of ELSentence-Assertible. (xor P Q) means  one but not both of P and Q is true. (An EL formula that mentions \n  xor is translated during canonicalization into an equivalent, less compact, formula that mentions or, and, and not).", 'UniversalVocabularyMt', vStrDef).
 7561exactlyAssertedEL_next(comment, unknownSentence, "A unary KBDependentRelation (q.v.) that takes instances of CycLSentence as arguments.  <code>(unknownSentence SENTENCE)</code> means that <code>SENTENCE</code> is not currently  \"known\" by the Cyc system to be true.  More precisely, the inference engine cannot prove <code>SENTENCE</code> <i>using only removal</i> (see CycRemovalModule) from the current state of the knowledge base.  <code>SENTENCE</code> might actually be known to be false (see the specialization contradictorySentence), or its truth-value might be simply unknown in the present sense.  \n<p>\nNote that, as a KB dependent relation, unknownSentence is notAssertible (q.v.).", 'UniversalVocabularyMt', vStrMon).
 7562exactlyAssertedEL_next(comment, unitMultiplicationFactor, "A ternary MetaFunction predicate that relates two interconvertible UnitOfMeasures (q.v.) to the real number by which the larger unit is a multiple of the smaller.  <code>(unitMultiplicationFactor SMALLUNIT BIGUNIT N)</code> means that there are <code>N SMALLUNIT</code>s in one <code>BIGUNIT</code>.  In other words, to convert from a measure <code>BIGUNIT</code>s to a measure in <code>SMALLUNIT</code>s, multiply by <code>N</code>.\n<p>\nFor example, (unitMultiplicationFactor Inch Foot-UnitOfMeasure 12) entails that, when converting from feet to inches, one multiplies the number of feet by twelve.\n<p>\nNote that <code>SMALLUNIT</code> and <code>BIGUNIT</code> must be instances of the same InterconvertibleUnitType (q.v.), and that <code>N</code> must be greater than or equal to 1.\n<p>\nSee also QuantityConversionFn.", 'UniversalVocabularyMt', vStrDef).
 7563exactlyAssertedEL_next(comment, trueSubL, "<code>(trueSubL SUBL)</code> states that the SubL expression <code>SUBL</code> evaluates to a value other than NIL.  This predicate allows for a procedural test for programmatic 'truth' in the implementation language to be reflected as a CycL test for logical truth in the logical language.  For example, <code>(trueSubL (ExpandSubLFn () (integerp 42)))</code> states that the SubL expression <code>(integerp 42)</code> evaluates to something other than NIL.  See ExpandSubLFn for a way to denote SubL within CycL.  See also evaluate and EvaluateSubLFn, and performSubL.", 'UniversalVocabularyMt', vStrMon).
 7564exactlyAssertedEL_next(comment, trueSentence, "A KBDependentRelation (q.v.) and specialization of consistent (q.v.) that is used to state that a given CycL sentence is true.  <code>(trueSentence SENT)</code> means that <code>SENT</code> is true.\n<p>\ntrueSentence is a non-assertible predicate (see  notAssertible).  But this puts no real limitation on the expressive power of the Cyc system since one can assert that <code>SENT</code> is true by simply asserting <code>SENT</code> itself.  \n<p>\nMost occurrences of the expression 'trueSentence' in CycL assertions have been added by the canonicalizer, so that certain nested sentences (or variables occurring in argument-positions intended for sentences) can receive special handling during canonicalization or inference. See the accompanying cyclistNotes for details.", 'UniversalVocabularyMt', vStrDef).
 7565exactlyAssertedEL_next(comment, trueRule, "(trueRule TEMPLATE FORMULA) states that FORMULA is both true and an instantiation of the rule template TEMPLATE.", 'UniversalVocabularyMt', vStrMon).
 7566exactlyAssertedEL_next(comment, transitiveViaArgInverse, "A MetaPredicate used for stating that a given predicate behaves transitively, in a specified argument-place, with respect to the inverse of a given binary predicate.  <code>(transitiveViaArgInverse PRED BINPRED N)</code> means that the <code>N</code>th argument position of <code>PRED</code> is \"transitive\" with respect to the inverse of <code>BINPRED</code>.  That is, if <code>(PRED</code> ... <code>ARGN</code> ...) and <code>(BINPRED ARGN-PRIME ARGN)</code> hold, then so does <code>(PRED</code> ... <code>ARGN-PRIME</code> ...).  For example,(transitiveViaArgInverse relationAllExists genls 2) holds; thus from (relationAllExists anatomicalParts Mammal Head-AnimalBodyPart) and (genls Horse Mammal) it follows that (relationAllExists anatomicalParts Horse Head-AnimalBodyPart).  See also transitiveViaArg.", 'UniversalVocabularyMt', vStrDef).
 7567exactlyAssertedEL_next(comment, transitiveViaArg, "A MetaPredicate used for stating that a given predicate behaves transitively, in a specified argument-place, with respect to a given binary predicate. <code>(transitiveViaArg PRED BINPRED N)</code> means that the <code>N</code>th argument position of <code>PRED</code> is \"transitive\" with respect to <code>BINPRED</code>.  That is, if <code>(PRED ... ARG-N ...)</code> and <code>(BINPRED ARG-N ARG-N-PRIME)</code> hold, then so does <code>(PRED ... ARG-N-PRIME ...)</code>.  For example, (transitiveViaArg relationAllExists genlPreds 1) holds; thus from (relationAllExists anatomicalParts Mammal Head-AnimalBodyPart) and (genlPreds anatomicalParts physicalParts) it follows that (relationAllExists physicalParts Mammal Head-AnimalBodyPart). See also transitiveViaArgInverse.", 'UniversalVocabularyMt', vStrDef).
 7568exactlyAssertedEL_next(comment, thereExists, "An ExistentialQuantifier (q.v.) that corresponds to the standard existential quantifier of predicate calculus.  thereExists takes as its arguments an ELVariable and an ELSentence-Assertible (such that, typically, the former occurs free in the latter).  (thereExists VAR SENT) means that there is at least one thing THING such that SENT is true of it.  That is, if some given CycL term that denotes THING were substituted for each free occurrence of VAR in SENT, the result would be a true sentence.  For example, `(thereExists ?X (mother ?X GeorgeWBush))' means that George W. Bush has a (i.e. at least one) mother; and\n<p>\n(forAll ?PER\n(implies\n(isa ?PER Person)\n(thereExists ?MOM\n(mother ?MOM ?PER))))\n<p>\nmeans that every person has a mother.  Note that some existential statements can be represented more tersely in CycL using other instances of ExistentialQuantifier, such as thereExistAtMost or thereExistExactly.  Also see the cyclistNotes for thereExists.", 'UniversalVocabularyMt', vStrDef).
 7569exactlyAssertedEL_next(comment, thereExistExactly, "An ExistentialQuantifier (q.v.) and a specialization of both thereExistAtLeast and  thereExistAtMost (qq.v.).  Compared to the standard existential quantifier thereExists, thereExistExactly has an extra argument-place for specifying exactly how many things satisfy a given condition (specified by an CycLSentence-Assertible, in which the also-specified CycLVariable will typically occur free).  A closed sentence of the form <code>(thereExistExactly NUM VAR SENT)</code> means that there are exactly<code> NUM</code> distinct things that satisfy <code>SENT</code>, i.e. that render <code>SENT</code> true when taken as the value of <code>VAR</code>.  For example, the sentence\n<p>\n<pre>\n  (thereExistExactly 7 ?X (isa ?X Sea))\n</pre>\n<p>\nmeans that there are exactly seven seas.\n<p>\nIn the degenerate case where <code>VAR</code> does not appear free in <code>SENT</code>, then <code>(thereExistExactly NUM VAR SENT)</code> is equivalent to <code>SENT</code>.", 'UniversalVocabularyMt', vStrDef).
 7570exactlyAssertedEL_next(comment, thereExistAtMost, "An ExistentialQuantifier (q.v.) and a specialized (albeit higher arity) version of thereExists (q.v.).  Compared to the latter, standard existential quantifier, thereExistAtLeast has an extra argument-place for specifying how many things (at the most) satisfy a given condition (specified by an ELSentence-Assertible, in which the also-specified ELVariable will typically occur free).  A closed sentence of the form (thereExistAtMost NUM VAR SENT) means that there are at most NUM distinct things that satisfy SENT, i.e. that render SENT true when taken as the value of VAR.  For example, the sentence\n<p>\n<pre>\n  (thereExistAtMost 7 ?X (isa ?X Sea))\n</pre>\n<p>\nmeans that there are at most seven seas.\n<p>\nIn the degenerate case where VAR does not appear free in SENT, then (thereExistAtMost NUM VAR SENT) is equivalent to SENT.\n<p>\nSee also thereExistAtLeast, thereExistExactly.", 'UniversalVocabularyMt', vStrDef).
 7571exactlyAssertedEL_next(comment, thereExistAtLeast, "An ExistentialQuantifier (q.v.) and a specialized (albeit higher arity) version of thereExists (q.v.).  Compared to the latter, standard existential quantifier, thereExistAtLeast has an extra argument-place for specifying how many things (at the least) satisfy a given condition (specified by an ELSentence-Assertible, in which the also-specified ELVariable will typically occur free).  A closed sentence of the form (thereExistAtLeast NUM VAR SENT) means that there are at least NUM distinct things that satisfy SENT, i.e. that render SENT true when taken as the value of VAR.  For example, the sentence\n<p>\n<pre>\n  (thereExistAtLeast 7 ?X (isa ?X Sea))\n</pre>\n<p>\nmeans that there are at least seven seas.\n<p>\nIn the degenerate case where VAR does not appear free in SENT, then (thereExistAtLeast NUM VAR SENT) is equivalent to SENT.\n<p>\nSee also thereExistAtMost, thereExistExactly.", 'UniversalVocabularyMt', vStrDef).
 7572exactlyAssertedEL_next(comment, termOfUnit, "An InferenceRelatedBookkeepingPredicate (q.v.) that appears in system-generated assertions.  termOfUnit relates unreified reifiable non-atomic terms (\"NATs\") to indexed data structures reified by the system.  termOfUnit GAF (see CycLClosedAtomicSentence) assertions\nare added by the system when an unreified reifiable NAT first appears in a CycL sentence that is added to the knowledge base.  When such a NAT is first used in a sentence, the Cyc system automatically creates an indexed data structure to reify the NAT.  A name is automatically assigned to the new data structure by the Cyc system.  (Typically, this name is character-for-character identical to the unreified reifiable NAT itself; but one should not be misled by this into thinking that termOfUnit is a specialization of equals.)  The predicate termOfUnit relates the system-generated data structure to the original NAT.  <code>(termOfUnit DATA-STRUCTURE NAT)</code> means that the data structure <code>DATA-STRUCTURE</code> was created to reify the value of the non-atomic term <code>NAT</code>, and that <code>NAT</code> refers to <code>DATA-STRUCTURE</code>, which in turn denotes something in the range of the function in the 0th (or \"arg 0\") position of <code>NAT</code>.\n<p>\nFor example, if an assertion such as (isa (RepairingFn Automobile) ProductType) introduced the unreified reifiable NAT (RepairingFn Automobile) in the Cyc knowledge base, the system would create a data structure to reify the value of (RepairingFn Automobile).  The system would assign the name `(RepairingFn Automobile)' to the newly-created data structure.  The system would also associate the newly-reified data structure with the unreified refiable NAT by means of the termOfUnit assertion (termOfUnit (RepairingFn Automobile) (RepairingFn Automobile)).\n<p>\nNote that termOfUnit assertions are made in the BaseKB because the relation between a NAT and the data structure reified for it is meant to hold in all contexts.  \n<p>\nOne should view termOfUnit assertions as bits of bookkeeping knowledge that are very rarely, if ever, entered into the Cyc knowledge base by hand. See retainTerm -- the predicate to use to create a NART that one wishes to remain in the Cyc KB even if no substantive additional assertions are made about it. NARTs that have only termOfUnit assertions made about them are removed from the KB at build time.", 'UniversalVocabularyMt', vStrDef).
 7573exactlyAssertedEL_next(comment, termExternalIDString, "A predicate which relates any CycLExpression to an external\nidentification string which is guaranteed to uniquely identify the\nexpression in both time and space. (termExternalIDString EXPRESSION\nID-STRING) states that the HLExternalIDString ID-STRING is the string\nrepresentation of the unique external id for the CycLExpression\nEXPRESSION. For obvious reasons, this predicate is notAssertible.\nAlso, note that this predicate is *not* a generalization of\nconstantGUID, since the latter relates a CycLConstant to an\nentirely different string.  That is to say, the termExternalIDString\nof a CycLConstant is not the same string as its constantGUID.", 'UniversalVocabularyMt', vStrMon).
 7574exactlyAssertedEL_next(comment, termDependsOn, "(termDependsOn DEP-TERM INDEP-TERM) states that the reason for the existence of the term DEP-TERM in the Cyc knowledge base is completely dependent on the continued existence of the term INDEP-TERM.  Thus, if INDEP-TERM should ever be removed from the knowledge base, then DEP-TERM should also be immediately removed.  This relationship is automatically maintained between reified non-atomic terms (NATs) and the terms from which they are constructed.", 'UniversalVocabularyMt', vStrDef).
 7575exactlyAssertedEL_next(comment, termChosen, "(termChosen TERM) is true for any closed Cyc TERM, and indicates that TERM has been chosen from the set of terms in the universe of discourse.  This predicate is primarily used on a variable so that the moment of choice of a particular term as the binding for that variable can be identified.  There should never be methods for generating bindings for non-closed termChosen literals.", 'UniversalVocabularyMt', vStrMon).
 7576exactlyAssertedEL_next(comment, synonymousExternalConcept, "<code>(synonymousExternalConcept THING SOURCE STRING)</code> means that as it occurs in the external data source <code>SOURCE</code>, the string <code>STRING</code> denotes <code>THING</code>.", 'UniversalVocabularyMt', vStrMon).
 7577exactlyAssertedEL_next(comment, substring, "A binary predicate that relates an instance of CharacterString to another intance of CharacterString. <code>(substring SUBSTRING STRING)</code> means that <code>SUBSTRING</code> is a substring of <code>STRING</code>.", 'UniversalVocabularyMt', vStrMon).
 7578exactlyAssertedEL_next(comment, subsetOf, "This predicate relates a set or collection <code>SUB</code> to a set or collection <code>SUPER</code> whenever the extent (see extent) of <code>SUB</code> is a  subset of the extent of <code>SUPER</code>.  That is, <code>(subsetOf SUB SUPER)</code> means that  every element of (see elementOf) <code>SUB</code> is an element of <code>SUPER</code>.  subsetOf is thus a generalization both of the subset relation in set theory and of genls (q.v.); and (unlike either of those other relations) subsetOf can hold between a set and a collection, or between a collection and a set.", 'UniversalVocabularyMt', vStrDef).
 7579exactlyAssertedEL_next(comment, skolemizeForward, "(skolemizeForward FUNC) tells the inference engine that terms should be generated for fully-bound uses of FUNC during forward inference.", 'UniversalVocabularyMt', vStrDef).
 7580exactlyAssertedEL_next(comment, skolem, "An InferenceRelatedBookkeepingPredicate (q.v.) that appears in system-generated assertions.  skolem holds of all instances of SkolemFunction, and exists solely for internal bookkeeping purposes.  The set of supports for a skolem assertion of the form (skolem FUNCTOR) is the set of defining assertions of FUNCTOR.", 'UniversalVocabularyMt', vStrDef).
 7581exactlyAssertedEL_next(comment, singleEntryFormatInArgs, "An instance of SpecificEntryFormatPredicate (q.v.).  <code>(singleEntryFormatInArgs PRED N)</code> means that, for any particular way of fixing the other arguments to <code>PRED</code> besides the <code>N</code>th, there is at most one thing such that, if taken as the <code>N</code>th argument, <code>PRED</code> holds of those arguments.  That is, if the sequences <code><... ARGN ...></code> and <code><... ARGN-PRIME ...></code> differ at most in their <code>N</code>th items and both <code>(PRED ... ARGN ...)</code> and <code>(PRED ... ARGN-PRIME ...)</code> hold, then <code>ARGN = ARGN-PRIME</code> (see equals).  For example, singleEntryFormatInArgs holds of biologicalMother with respect to its second argument-place, since an animal can only have one biological mother.  A predicate with a single-entry format argument-place is thus a StrictlyFunctionalPredicate (q.v.) that is \"functional\" with respect to that argument-place (see strictlyFunctionalInArgs).  Contrast with openEntryFormatInArgs.", 'UniversalVocabularyMt', vStrDef).
 7582exactlyAssertedEL_next(comment, siblingDisjointExceptions, "A predicate that is  used to make exceptions to constraints normally imposed by some instance of SiblingDisjointCollectionType or SiblingDisjointSetOrCollectionType (qq.v.).  <code>(siblingDisjointExceptions SETORCOL1 SETORCOL2)</code> means that the pair consisting of <code>SETORCOL1</code> and <code>SETORCOL2</code> is exempt from the disjointness constraint that would otherwise be imposed because those set-or-collections are both elements of some instance of SiblingDisjointCollectionType or SiblingDisjointSetOrCollectionType.  (See these collections' comments for a full explanation of the constraints.)   \n<p>\nFor example, SensoryNerve and CranialNerve are both instances of OrganismPartType, which in turn is an instance of SiblingDisjointCollectionType.  Consequently, since SensoryNerve is not a specialization of CranialNerve (or vice versa), the two collections have a default disjointness constraint placed between them.  However, such a disjointness constraint should be blocked, since any instance of OpticNerve is an instance of both SensoryNerve and CranialNerve.  By asserting <code>(siblingDisjointExceptions SensoryNerve CranialNerve)</code>, we block the disjointness constraint between those two collections, without disturbing the constraints between each of those collections and all their other (sibling) instances of the parent collection OrganismPartType.", 'UniversalVocabularyMt', vStrDef).
 7583exactlyAssertedEL_next(comment, sharedNotes, "A predicate-denoting constant that is an instance of DocumentationPredicate.  It is sometimes useful to include the same piece of text in the documentation of two or more constants or other CycLIndexedTerms. Rather than actually duplicating text in the Knowledge Base, one can create a SharedNote (q.v.): a piece of text that is to serve as this shared documentation, and which is itself the comment (see comment) on the SharedNote's constant.  (Thus the constants for shared-notes actually denote their own comments.)  (sharedNotes TERM NOTE) means that NOTE is a string of text (see TextString) serving as shared documentation partly about TERM.  Since SharedNotes are typically _shared_, there are likely to be one or more other indexed terms having NOTE as their shared-note as well.", 'UniversalVocabularyMt', vStrDef).
 7584exactlyAssertedEL_next(comment, sentenceTruth, "A KBDependentRelation (q.v.) that is used to state the truth of a given CycL sentence. (sentenceTruth SENT TRUTH) means that the CycL sentence SENT has the truth value TRUTH, which is either True or False.", 'UniversalVocabularyMt', vStrMon).
 7585exactlyAssertedEL_next(comment, sentenceImplies, "A binary predicate that represents logical entailment in CycL.  <code>(sentenceImplies ANTECEDENT CONSEQUENT)</code> means that <code>CONSEQUENT</code> can be derived from <code>ANTECEDENT</code> using purely logical transformations.  For example, this holds by double negation:\n<pre>\n  (sentenceImplies\n    (isa Muffet Poodle)\n    (not (not (isa Muffet Poodle))) .\n</pre>\nNote that there are cases in which <code>(implies ANTECEDENT CONSEQUENT)</code> is analytically true, or necessarily true in some sense of necessity weaker than logical necessity, such that <code>(sentenceImplies ANTECEDENT CONSEQUENT)</code> is false.  For example, whereas:\n<pre>\n  (implies (isa Muffet Poodle) (isa Muffet Dog))\n</pre>\nis analytically true or in some sense necessarily true,\n<pre>\n  (sentenceImplies (isa Muffet Poodle) (isa Muffet Dog))\n</pre>\nis not true, since the material conditional is not logically valid.\n<p>\nsentenceImplies also differs from implies in that whereas implies is a LogicalConnective (q.v.), sentenceImplies is merely a predicate that holds between sentences.  sentenceImplies is primarily intended to be used for rules that quantify over CycL sentences.", 'UniversalVocabularyMt', vStrMon).
 7586exactlyAssertedEL_next(comment, sentenceEquiv, "(sentenceEquiv FORMULA-1 FORMULA-2) means that  the ELSentence-Assertible FORMULA-1 is logically equivalent to the ELSentence-Assertible FORMULA-2.  This predicate is very similar to equiv, but equiv is an instance of LogicalConnective, while sentenceEquiv is an instance of Predicate.  sentenceEquiv is primarily intended to be used for rules that quantify over CycL formulas.", 'UniversalVocabularyMt', vStrDef).
 7587exactlyAssertedEL_next(comment, sentenceDesignationArgnum, "Used to specify which argument of a given MicrotheoryDesignatingRelation\ndesignates the CycL sentence to be interpreted in a specific microtheory.", 'UniversalVocabularyMt', vStrDef).
 7588exactlyAssertedEL_next(comment, scopingArg, "A binary MetaRelation that relates a ScopingRelation (q.v.) to an integer indicating the argument-place of the former that takes a variable or list of variables.  (scopingArg RELN N) means that RELN's Nth argument is a variable or variable-list (see CycLVariable and CycLVariableList) such that it (they) and any other occurrences of the same variable(s) that occur free in the CycL formula serving as the \"scoped\" argument (see scopedFormulaArg) to RELN is (are) bound with respect to the entire RELN-based formula.  For example, (scopingArg thereExists 1) entails that in the sentence\n<p>\n<pre>\n  (thereExists ?KIT\n    (and\n      (isa ?KIT Cat)\n      (isa ?KIT BlackColor)))\n</pre>\n<p>\neach occurrence of the variable '?KIT' is bound by the quantifier thereExists.", 'UniversalVocabularyMt', vStrDef).
 7589exactlyAssertedEL_next(comment, salientAssertions, "(salientAssertions TERM ASSERTION) means that ASSERTION has been deemed one of the assertions most useful to examine when one is trying to figure out the intended meaning of TERM.  Thus, ASSERTION will normally contain TERM, and should be something that has been asserted on its own in the KB as well.  Statements using salientAssertions are primarily intended for human consumption, and are not normally used by the Cyc inference engine.", 'UniversalVocabularyMt', vStrDef).
 7590exactlyAssertedEL_next(comment, ruleTemplateDirection, "A MetaKnowledgePredicate. (ruleTemplateDirection TEMPLATE DIRECTION) states that all assertions which are instantiations of TEMPLATE should  have a direction of DIRECTION.", 'UniversalVocabularyMt', vStrMon).
 7591exactlyAssertedEL_next(comment, ruleAfterRemoving, "Whenever a new rule is unasserted, ruleAfterRemovings are called on each literal of the rule.  The particular ruleAfterRemovings called depend on the predicate of the literal.  (ruleAfterRemoving PRED HOOK) means that HOOK will be called on each of the rule's literals whose predicate is PRED.  If the rule has multiple literals containing predicate with ruleAfterRemoving the order of execution is not guaranteed.  Also, ruleAfterRemovings are retriggered on the removal of the each argument to a rule.", 'UniversalVocabularyMt', vStrMon).
 7592exactlyAssertedEL_next(comment, ruleAfterAdding, "Whenever a new rule is asserted, ruleAfterAddings are called on each literal of the rule.  The particular ruleAfterAddings called depend on the predicate of the literal.  (ruleAfterAdding PRED HOOK) means that HOOK will be called on each of the rule's literals whose predicate is PRED.  If the rule has multiple literals containing predicate with ruleAfterAdding, the order of execution is not guaranteed.  Also, ruleAfterAddings are retriggered on the addition of new arguments to an existing rule.", 'UniversalVocabularyMt', vStrMon).
 7593exactlyAssertedEL_next(comment, rewriteOf, "A specialization of equals and a CycLReformulatorConstant that relates pairs of CycLClosedDenotationalTerms.   rewriteOf is, in a sense, a \"directional\" version of equals.  <code>(rewriteOf FAVORED-TERM DISFAVORED-TERM)</code> means that (1) <code>FAVORED-TERM</code> and <code>DISFAVORED-TERM</code> denote the same thing, and (2) <code>FAVORED-TERM</code> is deemed worthy of being privileged over <code>DISFAVORED-TERM</code> in the following senses: assertions made on <code>DISFAVORED-TERM</code> will be propagated to <code>FAVORED-TERM</code>, and whenever possible attempts to reason about  <code>DISFAVORED-TERM</code> will be transformed into attempts to reason about <code>FAVORED-TERM</code>.  The propagated assertions will differ from the original assertions only in that the propagated assertions will be the result of substituting <code>FAVORED-TERM</code> for <code>DISFAVORED-TERM</code> wherever <code>DISFAVORED-TERM</code> occurs in the original assertions.  Note that substitution does not happen in the opposite direction.  That is, assertions containing <code>FAVORED-TERM</code> will not propagate to <code>DISFAVORED-TERM</code>.\n<p>\nOne common use of rewriteOf is that in which <code>FAVORED-TERM</code> is a syntactically simpler term than <code>DISFAVORED-TERM</code>.  For example, <code>FAVORED-TERM</code> may contain fewer nested terms that denote Function-Denotationals than does <code>DISFAVORED-TERM</code>.  (rewriteOf UnitedStatesNavy (NavyFn UnitedStatesOfAmerica)) is a good example of this common sort of use.\n<p>\nNote that rewriteOf expresses a strictly conventional notion of \"directional\" equality. Pragmatic considerations, not ontology, will dictate which term is chosen to occur as the privileged (left-hand side) term in a rewriteOf assertion.  Thus, in the example the fact that simpler terms are generally easier to use (remember, manipulate, etc.) dictates that UnitedStatesNavy should be a rewrite of (NavyFn UnitedStatesOfAmerica), and not vice versa.", 'UniversalVocabularyMt', vStrDef).
 7594exactlyAssertedEL_next(comment, resultQuotedIsa, "A binary MetaRelation predicate that holds between functions and expression-types. resultQuotedIsa indicates that any value returned by a given Function-Denotational is a \"quoted instance\" of a given expression-type.   More correctly, <code>(resultQuotedIsa FUNC TYPE)</code> means that, for any term-sequence <code>ARGS</code>, if the expression <code>(FUNC . ARGS)</code> is an admittedNAT (q.v.), then it is an instance of the SubLExpressionType <code>TYPE</code>.  That is, the following holds:\n<pre>\n  (quotedIsa (FUNC . ARGS) TYPE)\n</pre>\nAnd, equivalently, so does:\n<pre>\n  (isa (Quote (FUNC . ARGS)) TYPE)\n</pre>\n\nTo contrast this predicate with resultIsa: <code>(resultIsa FUNC COL)</code> holds just in case each defined term of the form <code>(FUNC . ARGS)</code> <i>denotes</i> an instance of <code>COL</code>, whereas <code>(resultQuotedIsa FUNC COL)</code> holds just in case each admitted (i.e. syntactically and semantically well-formed) term of the form <code>(FUNC . ARGS)</code> <i>is itself</i> an instance of <code>COL</code>.", 'UniversalVocabularyMt', vStrMon).
 7595exactlyAssertedEL_next(comment, resultIsaArgIsa, "(resultIsaArgIsa FUNC INT) means that the NAT resulting from a use of FUNC is a member of the same collections that the term\nin arg position INT is a member of.", 'UniversalVocabularyMt', vStrMon).
 7596exactlyAssertedEL_next(comment, resultIsaArg, "A MetaRelation predicate.  <code>(resultIsaArg FUNC N)</code>  means that the value returned by <code>FUNC</code> for any given sequence of arguments  is an instance of the <code>N</code>th argument in that sequence.  That is, if  <code>(FUNC ARG1 ... ARGN ...) = VALUE</code>, then <code>(isa VALUE ARGN)</code> holds.  Obviously, <code>ARGN</code> must be a collection; so <code>FUNC</code>'s <code>N</code>th argument-place is likely to be constrained (via argIsa) to be an instance of Collection or some specialization thereof.\n<p>\nFor example, (resultIsaArg The 1) entails that (The Dog) is an instance of Dog.\n<p>\nSee also resultGenlArg and resultIsa.", 'UniversalVocabularyMt', vStrDef).
 7597exactlyAssertedEL_next(comment, resultIsa, "A binary MetaFunction that is used to indicate that any value returned by a given function (see Function-Denotational) is an instance of a given collection.  <code>(resultIsa FUNC COL)</code> means that <code>FUNC</code> returns an instance of <code>COL</code> for any sequence of arguments for which <code>FUNC</code> is defined.  That is, <code>(isa (FUNC . ARGS) COL)</code> holds for any sequence <code>ARGS</code> for which <code>FUNC</code> has a value (see valueOfFunctionForArgs and relationDomain).  \n<p>\nFor example, <code>(resultIsa PlusFn ScalarInterval)</code> holds, and it entails (e.g.) <code>(isa (PlusFn 2 2) ScalarInterval)</code>.  \n<p>\nSee also resultGenl.", 'UniversalVocabularyMt', vStrDef).
 7598exactlyAssertedEL_next(comment, resultGenlArg, "A MetaFunction predicate that holds of certain CollectionRelatingFunctions with respect to certain argument-places.  (resultGenlArg FUNC N) means that FUNC always returns a subcollection of its own corresponding Nth-place argument, and that FUNC is \"genls preserving\" in that argument-place.  More precisely: (i) the value of FUNC for any sequence of arguments for which it is defined is a subcollection of the Nth item in that sequence (i.e. (genls (FUNC ARG1..ARGN..) ARGN)) and (ii) (preservesGenlsInArg FUNC N) holds.  For example, (resultGenlArg JuvenileFn 1) entails (genls (JuvenileFn Dog) Dog) and -- given that (genls Dog Mammal) --   (genls (JuvenileFn Dog) (JuvenileFn Mammal)).  See also resultIsaArg and resultGenl.", 'UniversalVocabularyMt', vStrDef).
 7599exactlyAssertedEL_next(comment, resultGenl, "A MetaFunction that is used to specify that a \ngiven collection is a supercollection of any value returned by a given CollectionDenotingFunction (q.v.).  <code>(resultGenl COLFUNC COL)</code> means that when <code>COLFUNC</code> is applied to any sequence of arguments <code>ARGS</code> for which it is defined, the resulting value will be a subcollection of <code>COL</code>.  That is, <code>(genls (COLFUNC . ARGS) COL)</code> holds.  \n<p>\nFor example, <code>(resultGenl UsingAFn Action)</code> implies that the collection of acts done using any given type of object is a type of action, <code>(resultGenl AttemptingFn PurposefulAction)</code> implies that the attempts at a given type of action constitute a type of purposeful act, and <code>(resultGenl JointTypeBetweenFn Joint-Physical)</code> means that the collection of joints between two given types of things is a type of physical joint.  \n<p>\nSee also resultIsa.", 'UniversalVocabularyMt', vStrDef).
 7600exactlyAssertedEL_next(comment, requiredArg3Pred, "A MetaPredicate for stating that every instance of a given collection is related (as the \"arg3\") to some things by a given predicate.  <code>(requiredArg3Pred COL PRED)</code>  means that for every instance <code>INST</code> of <code>COL</code>, there exists some sequence  <<code>X1</code>, <code>X2</code>,..., <code>Xn</code>> such that <code>(PRED X1 X2 INST</code> ... <code>Xn)</code> holds.  For  example, (requiredArg3Pred ConflictEvent opponentsInConflict) means that every conflict involves (at least) two opponents.  See also requiredArg1Pred and requiredArg2Pred.", 'UniversalVocabularyMt', vStrDef).
 7601exactlyAssertedEL_next(comment, requiredArg2Pred, "A MetaPredicate for stating that every  instance of a given collection is related (as the \"arg2\") to some  thing or things by a given predicate.  (requiredArg2Pred COL PRED)  means that for every instance INST of COL, there exists some sequence  <X1, X3, ..., Xn> of such that (PRED X1 INST X3 ... Xn) holds.  For  example, (requiredArg2Pred Side objectSides) means that every  side is the side of at least one object.  See also requiredArg1Pred.", 'UniversalVocabularyMt', vStrDef).
 7602exactlyAssertedEL_next(comment, requiredArg1Pred, "A MetaPredicate for stating that every instance of a given collection is related to some thing or things by a given predicate.  <code>(requiredArg1Pred COL PRED)</code> means that for every  instance <code>INST</code> of <code>COL</code>, there exists some sequence <code>ARGS</code> such that <code>(PRED INST . ARGS)</code> holds.  For example, (requiredArg1Pred Organization hasMembers) means that every organization has at least one member.  \n<p>\nSee also requiredArg2Pred and requiredArg3Pred.", 'UniversalVocabularyMt', vStrDef).
 7603exactlyAssertedEL_next(comment, relationMemberInstance, "(relationMemberInstance PRED GROUP INST) states that for every MEMBER of GROUP the following is true: (PRED MEMBER INST).  This predicate enables one to make claims about the members of a group by referencing only the group itself.", 'UniversalVocabularyMt', vStrMon).
 7604exactlyAssertedEL_next(comment, relationInstanceMember, "(relationInstanceMember PRED INST GROUP) states that for every MEMBER of GROUP the following is true: (PRED INST MEMBER).  This predicate enables one to make claims about the members of a group by referencing only the group itself.", 'UniversalVocabularyMt', vStrMon).
 7605exactlyAssertedEL_next(comment, relationInstanceExists, "A ternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate holds between a specified thing and some instance of a given collection.  <code>(relationInstanceExists PRED THING COL)</code> means that there exists an instance <code>INST</code> of <code>COL</code> such that <code>(PRED THING INST)</code> holds.  It is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n<pre>\n     (thereExists ?INST\n          (and\n               (isa ?INST COL)\n               (PRED THING ?INST))) .\n</pre>\n<p>\nFor example, '(relationInstanceExists geographicalSubRegions Iran OilField)' means that there exists an oilfield in Iran.  Cf. relationExistsInstance, and see the shared NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrMon).
 7606exactlyAssertedEL_next(comment, relationInstanceAll, "A ternary RuleMacroPredicate that is used to state that a given binary predicate holds between a given thing and all instances of a given collection. (relationInstanceAll BINPRED THING COL) means that THING bears the relation PRED to every instance INST of COL such that (BINPRED THING INST) holds.  It is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n(implies\n(isa ?INST COL)\n(BINPRED THING ?INST)) .\n<p>\nFor example, `(relationInstanceAll geopoliticalSubdivision UnitedStatesOfAmerica State-UnitedStates)' means that each State in the Union is a subdivision of the United States.  Cf. relationAllInstance, and see NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7607exactlyAssertedEL_next(comment, relationExpansion, "ARG2 is a CycL expression which indicates the meaning of expressions in which the relation ARG1 is the operator (i.e., in which ARG1 is in the 0th argument position).  In ARG2, the variables ?arg1, ?arg2, ?arg3, ?arg4, and ?arg5 correspond to the objects in the argument positions 1, 2, 3, 4, and 5, respectively, in expressions which have ARG1 as the operator.", 'UniversalVocabularyMt', vStrDef).
 7608exactlyAssertedEL_next(comment, relationExistsMinAll, "A quaternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate stands in a certain numerical relation with respect to two collections.  (relationExistsMinAll BINPRED COL1 COL2 N) means that for any instance INST of COL2, there are at least N instances of (INST(1), ..., INST(N)) of COL1 such that (BINPRED INST(i) INST) holds (for 1 <= i <= N).  This is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n(implies\n(isa INST COL2)\n(thereExistAtLeast N ?INST-I\n(and\n(isa ?INST-I COL1)\n(BINPRED ?INST-I INST)))) .\n<p>\nFor example, `(relationExistsMinAll physicalParts Hand Finger 1)' means that every finger is part of at least one hand.  Cf. relationAllExistsMin, and see the shared NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7609exactlyAssertedEL_next(comment, relationExistsMaxAll, "A quaternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate stands in a certain numerical relation with respect to two collections.  <code>(relationExistsMaxAll BINPRED COL1 COL2 N)</code> means that for any instance <code>INST</code> of <code>COL2</code>, there are at most <code>N</code> instances of <code>(INST(1), ..., INST(N))</code> of <code>COL1</code> such that <code>(BINPRED INST(i) INST)</code> holds (for 1 <= <code>i</code> <= <code>N</code>).  This is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<pre>\n  (implies\n    (isa INST COL2)\n    (thereExistAtMost N ?INST-I\n      (and\n        (isa ?INST-I COL1)\n        (BINPRED ?INST-I INST)))).\n</pre>\nFor example, <code>(relationExistsMaxAll physicalParts Hand Finger 1)</code> means that every finger is part of at most one hand.  Cf. relationAllExistsMax, and see the shared NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7610exactlyAssertedEL_next(comment, relationExistsInstance, "A ternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate holds between some instance of a given collection and a given thing.  <code>(relationExistsInstance BINPRED COL THING)</code> means that there exists an instance <code>INST</code> of <code>COL</code> such that <code>(BINPRED INST THING)</code> holds.  This is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n<pre>\n(thereExists ?INST\n  (and\n     (isa ?INST COL)\n     (PRED ?INST THING))) .\n</pre>\n<p>\nFor example, (relationExistsInstance eventOccursAt IllegalDrugActivity Sweden) means that there exists illegal drug activity in Sweden.  See also the shared  NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7611exactlyAssertedEL_next(comment, relationExistsCountAll, "A quaternary RuleMacroPredicate (q.v.) that is used to state that a given binary predicate stands in a certain numerical relationship with respect to two collections.  (relationExistsCountAll BINPRED COL1 COL2 N) means that for every instance INST of COL2 there are exactly N instances of COL1 (INST(1), ..., INST(N)) such that (BINPRED INST(i) INST) holds (for 1 <= i <= N).  It is equivalent to (and so can be used in effect as shorthand for) the more complex form:\n<p>\n<pre>\n  (implies\n    (isa ?INST COL2)\n    (thereExistExactly N ?INST-I\n      (and\n             (isa ?INST COL1)\n             (BINPRED ?INST-I ?INST)))) .\n</pre>\n<p>\nFor example, (relationExistsCountAll anatomicalParts Animal Head-AnimalBodyPart 1) means that every animal head is a part of exactly one animal.  See also relationAllExistsCount and NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7612exactlyAssertedEL_next(comment, relationExistsAll, "A ternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate stands in a certain relation to two collections.  <code>(relationExistsAll BINPRED COL1 COL2)</code> means that for any instance <code>INST2</code> of <code>COL2</code>, there exists some instance <code>INST1</code> of <code>COL1</code> such that <code>(BINPRED INST1 INST2)</code> holds.  It is equivalent to (and can thus be used in effect as shorthand for) the more complex form\n<pre>\n  (implies\n    (isa ?INST2 COL2)\n    (thereExists ?INST1\n      (and\n        (isa ?INST1 COL1)\n        (BINPRED ?INST1 ?INST2)))).\n</pre>\nFor example, <code>(relationExistsAll adjacentTo Harbor PortCity)</code> means that for every port city there exists a harbor to which the city is adjacent.  See also relationAllExists and NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7613exactlyAssertedEL_next(comment, relationAllInstance, "A ternary RuleMacroPredicate that is used to state that a given binary predicate holds between all instances of a given collection and a given thing. <code>(relationAllInstance PRED COL THING)</code> means that every instance <code>INST</code> of <code>COL</code> bears the relation <code>PRED</code> to <code>THING</code> such that <code>(PRED INST THING)</code> holds.  It is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n<pre>\n     (implies\n          (isa ?INST COL)\n          (PRED ?INST THING)) .\n</pre>\n<p>\nFor example, '(relationAllInstance maxSpeed GolfCart (MilesPerHour 15))' means that the maximum speed of every golf cart is 15 miles per hour. Cf. relationInstanceAll, and see NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrMon).
 7614exactlyAssertedEL_next(comment, relationAllExistsMin, "A quaternary RuleMacroPredicate that can be used to state that a given binary predicate stands in a certain numerical relationship with respect to two collections.  (relationAllExistsMin BINPRED COL1 COL2 N) means that for any instance INST of COL1 there are at least N instances (INST(1), ..., INST(N)) of COL2 such that (BINPRED INST INST(i)) holds (for 1 <= i <= N).  This is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n(implies\n(isa ?INST COL1)\n(thereExistAtLeast N ?INST-I\n(and\n(isa ?INST-I COL2)\n(BINPRED ?INST ?INST-I)))) .\n<p>\nFor example, `(relationAllExistsMin subEvents EatingEvent Swallowing 1)' means that every act of eating includes at least one swallowing. Cf. relationExistsMinAll, and see NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7615exactlyAssertedEL_next(comment, relationAllExistsMax, "A quaternary RuleMacroPredicate that can be used to state that a given binary predicate stands in a certain numerical relationship with respect to two collections.  (relationAllExistsMax BINPRED COL1 COL2 N) means that for any instance INST of COL1 there are at most N instances (INST(1), ..., INST(N)) of COL2 such that (BINPRED INST INST(i)) holds (for 1 <= i <= N).  This is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n(implies\n(isa ?INST COL1)\n(thereExistAtMost N ?INST-I\n(and\n(isa ?INST-I COL2)\n(BINPRED ?INST INST-I)))) .\n<p>\nFor example, `(relationAllExistsMax anatomicalParts Dog Leg 4)' means that all dogs have at most four legs.\n<p>\nCf. relationExistsMaxAll; also see NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7616exactlyAssertedEL_next(comment, relationAllExistsCount, "A quaternary RuleMacroPredicate that is a specialization of both relationAllExistsMin and relationAllExistsMax (qq.v.).  <code>(relationAllExistsCount BINPRED COL1 COL2 N)</code> means that for any instance <code>INST</code> of <code>COL1</code> there are exactly <code>N</code> instances <code>INST1</code>, ..., <code>INSTn</code> of <code>COL2</code> such that <code>(BINPRED INST INSTi)</code> holds (for 1 <code><= i <= N)</code>. It is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<pre>\n  (implies\n    (isa ?INST COL1)\n    (thereExistExactly N ?INST-I\n      (and\n        (isa ?INST-I COL2)\n        (BINPRED ?INST ?INST-I))))\n</pre>\n<p>\n(wherein the variable <code>?INST</code> is interpreted as if it were bound by an initial universal quantifier).\n<p>\nFor example, <code>(relationAllExistsCount anatomicalParts Dog Leg 4)</code> means that all dogs have four legs.\n<p>\nCf. relationExistsCountAll, and see the NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7617exactlyAssertedEL_next(comment, relationAllExists, "A ternary RuleMacroPredicate (q.v.) that can be used to state that a given binary predicate stands in a certain relation to two collections. <code>(relationAllExists BINPRED COL1 COL2)</code> means that for any instance <code>INST1</code> of <code>COL1</code>, there exists some instance <code>INST2</code> of <code>COL2</code> such that <code>(BINPRED INST1 INST2)</code> holds.  It is equivalent to (and can thus be used in effect as shorthand for) the more complex form:\n<p>\n<pre>\n  (implies\n    (isa ?INST1 COL1)\n    (thereExists ?INST2\n      (and\n        (isa ?INST2 COL2)\n        (BINPRED ?INST1 ?INST2)))).\n</pre>\n<p>\nFor example, <code>(relationAllExists temporalBoundsContain CalendarWeek Wednesday)</code> means that every calendar week contains a Wednesday.  See also relationExistsAll and NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrDef).
 7618exactlyAssertedEL_next(comment, relationAll, "A binary RuleMacroPredicate that relates a given unary predicate to a collection of things that the predicate holds of.  <code>(relationAll PRED COL)</code> means that, for every instance <code>INST</code> of <code>COL</code>, <code>(PRED INST)</code> holds.  Thus <code>(relationAll PRED COL)</code> is equivalent to -- and so can be used in effect as shorthand for -- (the unversal closure of) the more complex form:\n<pre>\n  (implies \n    (isa <b>?INST</b> COL) \n    (PRED <b>?INST</b>)) .\n</pre>\nFor example, <code>(relationAll knownSentence CycLAssertion)</code> means that all CycLAssertions are asserted sentences.  \n<p>\nSee also relationOnly and the shared NoteAboutUseOfRuleMacroPredicates.", 'UniversalVocabularyMt', vStrMon).
 7619exactlyAssertedEL_next(comment, reformulatorRuleProperties, "(reformulatorRuleProperties PROP RULE) means that RULE has\nthe property PROP.  Most reformulator directives express an assertion\nof the form 'The reformulator should do X', for some X.  In contrast,\nreformulatorRuleProperties assertions are stronger, in that they\nexpress intrinsic properties of reformulator rules, and it is a\nconsequence that the reformulator should do X in order to be\ncorrect.  For example, a reformulator directive could say 'For this\nreformulator rule, if in tersification mode, the reformulator should reformulate\nthe second argument into the first argument.', whereas a reformulator\nrule property could say 'This reformulator rule's first argument is\nmore terse than its second argument.'  The latter implies the former.", 'UniversalVocabularyMt', vStrMon).
 7620exactlyAssertedEL_next(comment, reformulatorRule, "(reformulatorRule EXPR-1 EXPR-2), asserted in the\nmicrotheory MT, means that EXPR-1 may be reformulated into EXPR-2 (or\nvice versa, based on meta-properties of this rule and what mode the\nreformulator is in) in MT\nor a specMt thereof.  Free variables in EXPR-1 and EXPR-2 are shared,\nand may bind with CycL expressions which match the template. Truth\nand semantics are not necessarily preserved (see TruthPreservingReformulation).\nUse the more specific predicates reformulatorEquiv and reformulatorEquals\nwhen applicable.", 'UniversalVocabularyMt', vStrMon).
 7621exactlyAssertedEL_next(comment, reformulatorEquiv, "A CycLReformulationRulePredicate that relates two CycL sentences.  When asserted in a Microtheory MT, (reformulatorEquiv SENTENCE-1 SENTENCE-2) means that the CycLSentence SENTENCE-1 may be reformulated into the CycLSentence SENTENCE-2, or vice versa (based on meta-properties of this rule and what mode the reformulator is in), in any Microtheory SPEC-MT such that (genlMt SPEC-MT MT) holds.  Free variables in SENTENCE-1 and SENTENCE-2 are shared, and may bind with CycL sentences which match the template.  Note that (reformulatorEquiv SENTENCE-1 SENTENCE-2) does _not_ necessarily imply (equiv SENTENCE-1 SENTENCE-2), although this implication would hold if the reformulation is a TruthPreservingReformulation (q.v.).", 'UniversalVocabularyMt', vStrMon).
 7622exactlyAssertedEL_next(comment, reformulatorEquals, "A CycLReformulationRulePredicate that relates two CycL denotational terms.  When asserted in a Microtheory MT, (reformulatorEquals TERM-1 TERM-2) means that the CycLDenotationalTerm TERM-1 may be reformulated into the CycLDenotationalTerm TERM-2, or vice-versa (based on meta-properties of this rule and what mode the reformulator is in), in any Microtheory SPEC-MT such that (genlMt SPEC-MT MT) holds.  Free variables in TERM-1 and TERM-2 are shared, and may bind with CycL terms which match the template.  Note that (reformulatorEquals TERM-1 TERM-2) does _not_ necessarily imply (equals TERM-1 TERM-2), although this implication would hold if the reformualtion is a TruthPreservingReformulation (q.v.).", 'UniversalVocabularyMt', vStrMon).
 7623exactlyAssertedEL_next(comment, reformulationPrecondition, "(reformulationPrecondition DIRECTION PRECONDITION RULE), asserted in\nthe microtheory MT, means that the CycLReformulator may only use\nRULE in MT in the DIRECTION direction (reformulating the 'from' arg\ninto the 'to' arg) if PRECONDITION holds.  PRECONDITION must be a closed CycL query, which will be asked during reformulation, and either proven true or fail to be proven.", 'UniversalVocabularyMt', vStrMon).
 7624exactlyAssertedEL_next(comment, reformulationDirectionInMode, "(reformulationDirectionInMode DIRECTION MODE RULE), when\nasserted in the microtheory MT, tells the CycLReformulator whether to use RULE\nin the forward (ReformulationForwardDirection) or backward\n(ReformulationBackwardDirection) direction when reformulating\nCycLExpressions in MT or a specMt thereof, and when operating in the mode MODE.\nIt will reformulate the 'from' arg into the 'to' arg,\nbased on DIRECTION.  ReformulationNeitherDirection\nindicates the rule is not to be used at all in this mt.\nThis concept of direction has nothing to do with the forward vs. backward rule\ndistinction in inference.", 'UniversalVocabularyMt', vStrMon).
 7625exactlyAssertedEL_next(comment, ratioOfTo, "The predicate corresponding to QuotientFn.  (ratioOfTo NUM-1 NUM-2 NUM-3) holds just in case the ratio of NUM-1 to NUM-2 is NUM-3; that is, just in case  (QuotientFn NUM-1 NUM-2) = NUM-3.  For example, (ratioOfTo 1 2 0.5) is true because 1 divided by 2 is 0.5.", 'UniversalVocabularyMt', vStrMon).
 7626exactlyAssertedEL_next(comment, quotedIsa, "A binary MetaLanguagePredicate (q.v.) that relates CycL expressions to the SubLExpressionTypes (q.v.) of which they are instances.  quotedIsa is thus like a restricted version of isa (q.v.), but with one important difference: the first argument-place of quotedIsa is \"implicitly quoted\" (see quotedArgument).  So a ground atomic sentence of the form <code>(quotedIsa THING EXPR-TYPE)</code> does <i>not</i> mean that <code>THING</code> itself is an instance of <code>EXPR-TYPE</code>.  Rather, such a sentence is partly self-referential, and means that the particular <i>CycL expression</i> appearing in the sentence's own first argument-position is an instance of <code>EXPR-TYPE</code>.  Thus, quotedIsa provides a convenient shorthand for stating certain things that would otherwise require explicit quotation (or some other device for naming expressions).\n<p>\nThis is better illustrated with a specific example.  Suppose we wish to state that the CycL constant <code>IndianOcean</code> is an instance of the CycL expression type PublicConstant.  We cannot express this with the straightforward isa sentence <code>(isa IndianOcean PublicConstant)</code>, as that states the falsehood that the IndianOcean itself -- which is <i>not</i> a constant but a body of water -- is a public constant.  But we can express precisely what we want like this:\n<pre>\n  (quotedIsa IndianOcean PublicConstant) .\n</pre>  \nNow quotedIsa is a MacroRelation (q.v.), and by its expansion any given quotedIsa sentence is equivalent to some isa sentence with an <i>explicitly</i> quoted first argument.  The sentence displayed above turns out to be equivalent to: \n<pre>\n  (isa (Quote IndianOcean) PublicConstant).\n</pre> \nBut the quotedIsa version has two related practical advantages over the isa version.  First, the former is syntactically simpler than the latter.  Second, the simpler syntax of the former makes it easier to browse in the Knowedge Base: while the quotedIsa version is conveniently indexed under the KB Browser page for the constant <code>IndianOcean</code>, the isa version would apparently be indexed under a separate, brand new page for the term <code>(Quote IndianOcean)</code>. Generalizing the point, quotedIsa lets us avoid having potentially to double the number of pages currently in the browser.\n<p>\nFor the semantically more complicated (but rarely encountered) case in which quotedIsa's first argument-place is filled with an <i>open</i> expression, see the accompanying cyclistNotes.", 'UniversalVocabularyMt', vStrDef).
 7627exactlyAssertedEL_next(comment, quotedDefnSufficient, "A CycInferenceDescriptorPredicate. (quotedDefnSufficient COL TEST) means that TEST is the name of a piece of code in the SubL implementation of Cyc that specifies, and tests for, a sufficient condition for a CycL term's denoting a quoted instance of (see quotedIsa) the collection COL. If TEST returns `T' (for `True') when applied to a particular term, then that term's denotatum is considered to be a quoted instance of COL. Note that TEST isn't necessarily a necessary test for quoted membership in COL; that is, not all quoted instances of COL must pass the test, unless TEST is also a defnNecessary for COL, or the term is asserted to be a quoted instance of COL using quotedIsa. See the related predicates quotedDefnNecessary and quotedDefnIff.", 'UniversalVocabularyMt', vStrMon).
 7628exactlyAssertedEL_next(comment, quotedDefnNecessary, "A CycInferenceDescriptorPredicate. (quotedDefnNecessary COL TEST) means that TEST is the name of a piece of code in the SubL implementation of Cyc that specifies, and tests for, a necessary condition for a CycL term's denoting a quoted instance of (see quotedIsa) the collection COL. Only if TEST returns `T' (for `True') when applied to a particular term can that term's denotatum be considered a quoted instance of COL; all terms that denote quoted instances of COL must fulfill TEST's requirements, although there may be additional requirements for denoting an instance of COL as well. However, terms asserted to be quoted instances of the collection COL using quotedIsa are exempt from fulfilling TEST's requirements. See also quotedDefnSufficient and quotedDefnIff.", 'UniversalVocabularyMt', vStrMon).
 7629exactlyAssertedEL_next(comment, quotedDefnIff, "A CycInferenceDescriptorPredicate. (quotedDefnIff COL TEST) means that TEST is the name of a piece of code in the SubL implementation of Cyc that specifies, and tests for, a necessary and sufficient condition for a CycL term's denoting a quoted instance of (see quotedIsa) the collection COL. If and only if TEST returns `T' (for `True') when applied to a particular term can that term's denotatum be considered a quoted instance of COL; all and only terms that denote quoted instances of COL must fulfill TEST's requirements.  However, terms asserted to be quoted instances of the collection COL using quotedIsa are exempt from fulfilling TEST's requirements. See also quotedDefnNecessary and quotedDefnSufficient.", 'UniversalVocabularyMt', vStrMon).
 7630exactlyAssertedEL_next(comment, quotedArgument, "The main (longer) comment on this predicate was written to explain the role of quotedArgument in an earlier approach for referring to CycL expressions in the CycL language that is currently (April 2002) being phased out in favor of a new approach.  Whereas the earlier approach enabled self-reference only by means of a sort of \"implicit quotation\", the new approach involves a mechanism for explicitly quoting CycL expressions (by putting them inside something analogous to quotation marks).  quotedArgument, unlike quotedCollection (q.v.), still has a role to play with respect to the new approach, and its main comment will soon revised to better explain that role.  For an explanation of the new approach to quoting, see the shared NoteAboutQuotingInCycL and the constants that share that note.", 'UniversalVocabularyMt', vStrDef).
 7631exactlyAssertedEL_next(comment, quotedArgument, "A specialization of opaqueArgument (q.v.).  quotedArgument is a binary MetaLanguagePredicate used to state that a given argument-place of a given CycL relation-denoting expression is an <i>implicitly quoted</i> context, in the sense that a symbol appearing in that context denotes <i>itself</i> (as opposed to whatever that symbol might denote, if anything, in ordinary non-quoted contexts).  \n<p>\n<code>(quotedArgument REL N)</code> means that in a closed compound expression built from <code>REL</code> -- i.e. a ground atomic sentence (or <i>gaf</i>) if <code>REL</code> is a predicate or a closed non-atomic term (or <i>nat</i>) if <code>REL</code> is a function -- the term (i.e. the CycL expression) <code>EXPR</code> appearing in <code>REL</code>'s <code>N</code>th argument-place is taken to denote <i>itself</i> (i.e. that very expression <code>EXPR</code>).  \n<p>\nquotedArgument thus makes possible a kind of a self-reference in CycL. Relations with quoted argument-places can be used to make statements about particular CycL expressions, without quoting those expressions explicitly (cf. Quote).\n<p>\nFor example, the first argument-place of the predicate myCreator is quoted and its second argument-place is not.  Thus in the sentence <code>(myCreator PlanetEarth Maeda)</code>, the CycL constant <code>PlanetEarth</code> denotes that constant itself (and not the actual planet Earth), while the constant <code>Maeda</code> simply denotes the person Maeda (and not a CycL expression).  Hence the above sentence correctly states that Maeda created (i.e. reified) the CycL constant <code>PlanetEarth</code>; it does <i>not</i> state the absurdity that he created the planet Earth.  In ordinary non-quoted contexts, of course, <code>PlanetEarth</code> denotes the planet and not the constant.\n<p>\nSee also quotedCollection and NoteAboutUseVersusMention.", 'UniversalVocabularyMt', vStrDef).
 7632exactlyAssertedEL_next(comment, querySentence, "querySentence is an HL level predicate that allows for special handling of a sentence (especially nested sentences) as a top level query during the process of canonicalization.  querySentence is not-assertible.  It should not be used in any assertions.", 'UniversalVocabularyMt', vStrMon).
 7633exactlyAssertedEL_next(comment, quantitySubsumes, "A specialization of both quantityIntersects and intangibleParts, this predicate relates a given numerically measurable ScalarInterval to those scalar intervals that it subsumes or that \"fall completely inside\" it.    <code>(quantitySubsumes SUPER SUB)</code> means that both (i) the maximum (see maxQuantValue) of <code>SUPER</code> is greaterThanOrEqualTo the maximum of <code>SUB</code> and (ii) the minimum (see minQuantValue) of <code>SUPER</code> is lessThanOrEqualTo the minimum of <code>SUB</code>.\n<p>\nFor example, (Meter 2 5) -- the Distance of between 2 and 5 meters inclusive -- subsumes both (Meter 3 4) and (Meter 3 5), but not (Meter 3 6).", 'UniversalVocabularyMt', vStrMon).
 7634exactlyAssertedEL_next(comment, quantityIntersects, "A binary predicate that relates numerically measurable ScalarIntervals (q.v.) that intersect or overlap.  <code>(quantityIntersects SCALAR1 SCALAR2)</code> means that  <code>SCALAR1</code> and <code>SCALAR2</code> intersect. More precisely: there is  some scalar interval (which might even be as small as an  instance of ScalarPointValue) that is subsumed by (see quantitySubsumes) both <code>SCALAR1</code> and <code>SCALAR2</code>.\n<p>\nFor example, (Meter 2 5) -- the Distance of between 2 and 5 meters inclusive -- intersects both (Meter 3 4) and (Meter 3 7), but does not intersect (Meter 6 7).", 'UniversalVocabularyMt', vStrDef).
 7635exactlyAssertedEL_next(comment, prettyString, "(prettyString TERM STRING) means that STRING is the English word or expression (sequence of words) commonly used to refer to TERM.  The predicate prettyString is used by the code which generates CycL to English paraphrases, but its applicability is not restricted to this use.", 'UniversalVocabularyMt', vStrDef).
 7636exactlyAssertedEL_next(comment, preservesGenlsInArg, "<code>(preservesGenlsInArg FUNCTION N)</code> means that the CollectionDenotingFunction <code>FUNCTION</code> has the following properties: \n<p>\n(1) argument place <code>N</code> of <code>FUNCTION</code> is constrained to instances of Collection, and <br>\n(2) if <code>COLLECTION1</code> and <code>COLLECTION2</code> can both serve as the <code>N</code>th argument of <code>FUNCTION</code>, and <code>COLLECTION2</code> is a specialization of <code>COLLECTION1</code> (so that <code>(genls COLLECTION2 COLLECTION1)</code> holds), then <code>(genls (FUNCTION ARG_1 ARG_2 ... ARG_N-1 COLLECTION2   ... ARG-M) (FUNCTION ARG_1 ARG_2 .. ARG_N-1 COLLECTION1 ... ARG-M))</code> also holds, where <code>ARG_1</code>, <code>ARG_2</code>, ..., <code>ARG_M</code> (where <code>M</code> is the arity of <code>FUNCTION</code>) are admitted arguments for <code>FUNCTION</code> (see admittedArgument).  \n<p>\nFor example, (preservesGenlsInArg GroupFn 1) holds because <code>(genls COL-2 COL-1)</code> implies <code>(genls (GroupFn COL-2) (GroupFn COL-1))</code>, for all collections <code>COL-1</code> and <code>COL-2</code> that satisfy the argument constraints for GroupFn.  \n<p>\nSimilarly, (preservesGenlsInArg SubcollectionOfByTypeFn 2) holds because <code>(genls COL-2 COL-1)</code> implies <code>(genls (SubcollectionOfByTypeFn FIXED-ARG COL-2) (SubcollectionOfByTypeFn FIXED-ARG COL-1))</code> for all collections <code>COL-1</code> and <code>COL-2</code>, and all arguments <code>FIXED-ARG</code>, that satisfy the appropriate argument constraints for SubcollectionOfByTypeFn.  See also the collection GenlsPreservingFunction.", 'UniversalVocabularyMt', vStrDef).
 7637exactlyAssertedEL_next(comment, predicateConventionMt, "(predicateConventionMt PRED MT) means that the predicate extent of the predicate PRED, by convention, is asserted in MT.", 'UniversalVocabularyMt', vStrMon).
 7638exactlyAssertedEL_next(comment, pragmaticRequirement, "A MetaKnowledgePredicate that is used to place a certain kind of pragmatic precondition on the use of a given asserted rule (see CycLRuleAssertion). (pragmaticRequirement SENTENCE RULE) means that SENTENCE expresses a necessary condition on RULE's being used in any proof carried out by the Cyc inference engine. The effect of asserting this is virtually the same as that of asserting (exceptWhen (unknownSentence SENTENCE) RULE): it blocks the use of RULE when SENTENCE is not currently \"known\" by the Cyc system to be true. SENTENCE should not contain disjuncts (or canonicalize into disjuncts). Upon assertion to the knowledge base, a pragmaticRequirement sentence is transformed by the canonicalizer into a rule involving pragmaticallyNormal (q.v.).", 'UniversalVocabularyMt', vStrMon).
 7639exactlyAssertedEL_next(comment, pragmaticallyNormal, "A MetaKnowledgePredicate that is used to express that certain pragmatic preconditions on a given rule are satisfied.  The predicate takes as arguments a list of CycL variables and an asserted rule (see CycLRuleAssertion) in which those variables occur \"free\".  At the EL (\"epistemological level\"), pragmaticallyNormal sentences are not asserted as GAFs, but appear instead as the antecedents of system-generated implies rules.  For a given sequence of values for the respective variables VAR1, ..., VARn,    (pragmaticallyNormal (TheList VAR1 ... VARn) RULE) means that any pragmatic preconditions placed on RULE's being used by the Cyc inference engine (see pragmaticRequirement) are satisfied with respect to those values.\n<p>\nLet's make this more precise and explicit.  A pragmatic precondition for a rule is written like so:\n<p>\n(pragmaticRequirement CONDITION RULE)\n<p>\nand gets canonicalized into a rule involving pragmaticallyNormal like so:\n<p>\n(implies\n(pragmaticallyNormal (TheList VAR1 ... VARn) RULE)\nCONDITION),\n<p>\nwhere VAR1, ..., VARn are all and only the variables that occur free in RULE and thus include all (and possibly only) the variables that occur free in CONDITION (i.e. as RULE and CONDITION explicitly appear in the KB browser, without consideration of their having \"implicit\" initial universal quantifiers).\n<p>\nThe above pragmaticallyNormal rule is used in inference as though it were a constraint rule.  If CONDITION does not hold for a given sequence of values <VAL1, ..., VALn> for its variables <VAR1, ..., VARn>, then those values are not \"pragmatically normal\" for RULE; and hence inference will not proceed using <VAL1, ..., VALn> with RULE.\n<p>\nThe effect of the foregoing is that any asserted rule RULE is implicitly treated by the Cyc inference engine as if it had the form\n<p>\n(implies\n(pragmaticallyNormal (TheList VAR1 ... VARn) RULE)\nRULE)\n<p>\n(with VAR1, ..., VARn as described above).\n<p>\nThis convention allows the logical content of a rule to be expressed independently of any pragmatic preconditions for its being used in inference.\n<p>\nAlso see abnormal, which is syntactically similar and has a related  interpretation that makes it roughly the complement of pragmaticallyNormal.", 'UniversalVocabularyMt', vStrDef).
 7640exactlyAssertedEL_next(comment, pointQuantValue, "A NumericComparisonPredicate and a specialization of numericallyEquals, minQuantValue, and maxQuantValue (qq.v.).  pointQuantValue is essentially the relation numericallyEquals restricted to scalar point-values, with the additional proviso that its first argument must be given using a reifiable CycL term.  Thus a sentence of the form\n<p>\n\t<code>(pointQuantValue REIFIABLE-TERM OTHER-TERM)</code>\n<p>\nis true if and only if <code>REIFIABLE-TERM</code> is a CycLReifiableDenotationalTerm (q.v.), and <code>REIFIABLE-TERM</code> and <code>OTHER-TERM</code> denote the same ScalarPointValue (q.v.).\n<p>\nThis predicate is primarily used to state the equivalence of a reified scalar-denoting term (e.g. 'Zero', 'AvogadrosNumber', 'SpeedOfLight') with an appropriate unreifiable term.  For example, both of the following sentences hold:\n<p>\n<pre>\n  (pointQuantValue Zero 0)\n</pre>\n<p>\n<pre>\n  (pointQuantValue\n    SpeedOfLight\n    (PerFn (Mile 186000) (HoursDuration 1))'  .\n</pre>", 'UniversalVocabularyMt', vStrDef).
 7641exactlyAssertedEL_next(comment, performSubL, "<code>(performSubL SUBL)</code> states that the SubL expression <code>SUBL</code> has been successfully evaluated for side-effect.  performSubL is evaluated as late in an inference proof as possible.  See also trueSubL which evaluates usually as soon as possible in an inference.  For example, <code>(performSubL (ExpandSubLFn () (print \"Done\")))</code> will print out the string \"Done\" as a given proof path completes.  See ExpandSubLFn for a way to denote SubL within CycL.  See also EvaluateSubLFn.", 'UniversalVocabularyMt', vStrMon).
 7642exactlyAssertedEL_next(comment, overlappingExternalConcept, "A predicate for mapping terms from an external data source to closely related concepts represented in Cyc.  <code>(overlappingExternalConcept THING SOURCE STRING)</code> means that in the external data source <code>SOURCE</code>, the meaning of <code>STRING</code> has significant semantic overlap with THING.", 'UniversalVocabularyMt', vStrMon).
 7643exactlyAssertedEL_next(comment, or, "A LogicalConnective that represents disjunction in CycL. It is a VariableArityRelation, taking an arbitrary number of instances of CycLSentence-Assertible as arguments.  (or P Q ... Z) is true if and only if at least one of the sentences P, Q, ..., or Z is true.", 'UniversalVocabularyMt', vStrDef).
 7644exactlyAssertedEL_next(comment, operatorFormulas, "A non-assertible MetaLanguagePredicate and specialization of termFormulas (q.v.) that relates CycL operators to CycL formulas in which they occur as the main operator.  <code>(operatorFormulas OPERATOR FORMULA)</code> means that <code>OPERATOR</code> occurs as the main operator (i.e. in the \"arg0\" position) of <code>FORMULA</code>.  \n<p>\nNote that both argument-places of operatorFormulas are implicitly \"quoted\" (see quotedArgument). So if the above operatorFormulas sentence is closed (see CycLClosedAtomicSentence), the two CycL expressions it mentions, <code>OPERATOR</code> and <code>FORMULA</code>, actually <i>appear in</i> that sentence -- as names of themselves.  Thus, the sentence \n\n<pre>  (operatorFormulas bordersOn (bordersOn France Germany))</pre> \n\nis true, due to the manifest fact that the <i>term</i> <code>bordersOn</code> occurs as the main operator in the sentence <code>(bordersOn France Germany)</code>. \n<p>\nNote that <code>FORMULA</code> in the above need not be true (if it's a sentence) or even semantically well-formed.", 'UniversalVocabularyMt', vStrMon).
 7645exactlyAssertedEL_next(comment, openEntryFormatInArgs, "An instance of SpecificEntryFormatPredicate (q.v.).  <code>(openEntryFormatInArgs PRED N)</code> means that, for any particular way of fixing the other arguments to <code>PRED</code> besides the <code>N</code>th, there might be any number (including zero) of things such that, if taken as the <code>N</code>th argument, <code>PRED</code> holds of those arguments.  For example, openEntryFormatInArgs holds of biologicalMother with respect to its first argument-place, since a given female animal might have any number of offspring.  \n<p>\nUnlike the other reified instances of SpecificEntryFormatPredicate, openEntryFormatInArgs actually places no restriction at all on what <code>PRED</code> might or might not hold of with respect to the specified argument-place.  But one should not infer from this that openEntryFormatInArgs assertions are pointless; for they forestall duplication of effort by serving notice that the entry-format of a given argument-place has previously been considered and openEntryFormatInArgs was deemed appropriate.  \n<p>\nopenEntryFormatInArgs is the most commonly-encountered specific entry-format in the Cyc Knowledge Base.  Contrast with singleEntryFormatInArgs.", 'UniversalVocabularyMt', vStrDef).
 7646exactlyAssertedEL_next(comment, opaqueArgument, "A binary MetaLanguagePredicate that can be used to state that a given argument-place of a given CycL relation-denoting expression is <i>denotationally opaque</i>.  \n<p>\n<code>(opaqueArgument REL N)</code> means that if in a closed compound expression built from the CycL expression for <code>REL</code> -- i.e. a ground atomic formula (or <i>gaf</i>) if <code>REL</code> is a predicate or a closed non-atomic term (or <i>nat</i>) if <code>REL</code> is a function -- the term appearing in <code>REL</code>'s <code>N</code>th argument-place is replaced with another term having the same denotatum (or truth-value, if the term is a sentence), there is no guarantee that the resulting gaf (or nat) will itself have the same truth-value (or denotatum) as the original.  \n<p>\nMost argument-places of most relation-denoting expressions do  allow such substitutions to be made freely, and are thus <i>denotationally transparent</i>.  For example, given that (equals Cicero Tully), the truth of <code>(residesInRegion Cicero CityOfRomeItaly)</code> entails the truth of  <code>(residesInRegion Tully CityOfRomeItaly)</code>.  This shows that residesInRegion's first argument-place is denotationally transparent. On the other hand, if Caesar were seeking Cicero and found him then (<code>objectFound-Definite CaesarsSearchForCicero Caesar Cicero)</code> would be true; but <code>(objectFound-Definite CaesarsSearchForCicero Caesar Tully)</code> might nevertheless be false, because Caesar might not know that Tully is Cicero and thus might not realize that in finding Cicero he had found Tully.  Having such a realization is a necessary condition for objectFound-Definite's holding, which shows that this relation's third argument-place is denotationally opaque.  \n<p>\nAccording to one well-known semantics for denotational opacity (viz. GottlobFrege's), a term appearing in an opaque context (in most cases) denotes (not its ordinary denotatum, but) what is ordinarily its <i>intensional meaning</i> or <i>sense</i> (or <i>Sinn</i>, in Frege's native German).  \n<p>\nquotedArgument (q.v.) is a specialization of opaqueArgument, and a term appearing in a <i>quoted</i> context is interpreted as denoting <i>itself</i> (rather than its usual denotatum).", 'UniversalVocabularyMt', vStrDef).
 7647exactlyAssertedEL_next(comment, omitArgIsa, "<code>(omitArgIsa RELN N)</code> means that the relation <code>RELN</code> is not asserted to have a non-quoted argument constraint in its <code>N</code>th argument position, due to limitations of the Cyc system.  Since every relation relates things to other things, in principle every argument position for every relation should have an argIsa constraint; however, asserting some argIsa constraints will cause certain Cyc tests to fail.", 'UniversalVocabularyMt', vStrMon).
 7648exactlyAssertedEL_next(comment, oldConstantName, "This bookkeeping predicate relates a CycL constant to a former \"name\" of that constant.  More accurately, (oldConstantName CONSTANT STRING) means that the underlying data structure currently associated with the CycL expression CONSTANT was formerly associated instead with the SubL string STRING.  If CONSTANT has undergone multiple \"renames\", STRING will \nnormally be its most recent former \"name\".  While oldConstantName sentences \ncan be asserted and edited by hand, they are asserted automatically when a Rename is done in the Knowledge Base.", 'BookkeepingMt', vStrMon).
 7649exactlyAssertedEL_next(comment, numericallyEquals, "A NumericComparisonPredicate that is applicable to ScalarIntervals (<i>q.v.</i>) of all sorts, including quantitative intervals (see NumericInterval and Quantity) as well as point values (see ScalarPointValue).  <code>(numericallyEquals VALUE1 VALUE2)</code> means that <code>VALUE1</code> is equal to <code>VALUE2</code> with respect to some scale that they are both on.  More precisely, there is some TotallyOrderedScalarIntervalType <code>SCALE</code> that <code>VALUE1</code> and <code>VALUE2</code> are instances of and the minimum (see minQuantValue) of <code>VALUE1</code> is equal to the minimum of <code>VALUE2</code> and the maximum (see maxQuantValue) of <code>VALUE1</code> is equal to the maximum of <code>VALUE2</code>.\n<p>\nNote that numericallyEquals is <i>not</i> a specialization of equals (<i>q.v.</i>), as numeric values of different sorts can be \"numerically  equivalent\" without being considered identical (e.g. the Integer 1 and the RealNumber 1.0).", 'UniversalVocabularyMt', vStrDef).
 7650exactlyAssertedEL_next(comment, nthSmallestElement, "(nthSmallestElement X N SET FUNCTION) means that X is an element of SET that has precisely N-1 other elements with a smaller value for FUNCTION. For example, (nthSmallestElement RhodeIsland-State 1 State-UnitedStates (FunctionToArg 2 areaOfRegion)). Yet there may be more nthSmallestElements. For example, (nthSmallestElement ?X 3 (TheSet 1 2 3 -3) AbsoluteValueFn) is true for both 3 and -3 - when the elements in the set are ordered according to their absolute value both 3 and -3 are 3rd smallest elements. ", 'UniversalVocabularyMt', vStrMon).
 7651exactlyAssertedEL_next(comment, nthLargestElement, "(nthLargestElement X N SET FUNCTION) means that X is an element of SET that has precisely N-1 other elements with a larger value for FUNCTION. For example, (nthLargestElement Alaska-State 1 State-UnitedStates (FunctionToArg 2 areaOfRegion)) means that Alaska is the largest state (no elements have a larger areaOfRegion). Yet there may be more nthLargestElements. For example, (nthLargestElement ?X 1 (TheSet 1 2 3 -3) AbsoluteValueFn) is true for both 3 and -3 ; when the elements in the set are ordered according to their absolute value both 3 and -3 are largest elements. See also nthSmallestElement.", 'UniversalVocabularyMt', vStrMon).
 7652exactlyAssertedEL_next(comment, notAssertibleMt, "(notAssertibleMt MT) states that the Microtheory MT cannot be used as the microtheory of an assertion made to the KB; i.e., MT might be a microtheory used as scaffolding or one whose assertions are known to be complete.  See also notAssertibleCollection, and notAssertible.", 'UniversalVocabularyMt', vStrMon).
 7653exactlyAssertedEL_next(comment, notAssertibleCollection, "A UnaryPredicate used for stating a certain restriction regarding the use of a given Collection in assertions to the Cyc Knowledge Base.  (notAssertibleCollection COL) means that no ground atomic formula (or \"GAF\"; see CycLClosedAtomicSentence) whose initial (or \"0th\" argument-place) term is `isa', and whose 2nd argument-place term denotes COL, can be asserted to the KB.  See also notAssertible, which constrains predicates in a similar fashion.", 'UniversalVocabularyMt', vStrMon).
 7654exactlyAssertedEL_next(comment, notAssertible, "A MetaPredicate for stating a certain restriction regarding the use of a given Predicate in assertions to the Cyc Knowledge Base.  (notAssertible PRED) means that no ground atomic formula (or \"GAF\"; see CycLClosedAtomicSentence) whose initial (or \"0th\" argument-place) term denotes PRED can be asserted to the KB.  In many cases, PRED will be an EvaluatablePredicate whose extent is (re)computed as necessary and never cached in the KB.  \n<p>\nSee also notAssertibleCollection, which constrains collections \nin a similar fashion.", 'UniversalVocabularyMt', vStrMon).
 7655exactlyAssertedEL_next(comment, not, "An instance of both LogicalConnective and UnaryRelation.  which takes an instance of #CycLSentence-Assertible as its argument. (not SENT) is true if and only if SENT is false (and false if and only if SENT is true).", 'UniversalVocabularyMt', vStrDef).
 7656exactlyAssertedEL_next(comment, nonAbducibleWithValueInArg, "A ternary predicate that is an instance of AbductionConstraintConstant (q.v.) and that can apply to a predicate and a specified value for a specified argument-place. \n<p>\n(nonAbducibleWithValueInArg PRED VALUE N) means that, if asked a query of the form (PRED ... VALUE ...), where VALUE appears in the Nth argument-position and all of the other positions (>= 1) are filled with variables, the Inference Engine cannot use abduction to hypothesize that any non-abduced terms are legitimate bindings for those variables.\n<p>\nFor example, (nonAbducibleWithValueInArg hasMembers InternationalMonetaryFund 1) holds, so Cyc cannot use abduction to hypothesize that Sealand is a member of the IMF.  (Note that this does not mean that Cyc cannot prove that some abduced term is a member of the IMF.)", 'CoreCycLMt', vStrMon).
 7657exactlyAssertedEL_next(comment, negationPreds, "A MetaPredicate for stating that two predicates are logical \"contraries\" of one another.  <code>(negationPreds PRED1 PRED2)</code> means that if <code>PRED1</code> holds among a given sequence of things, then <code>PRED2</code> does <i>not</i> hold among that sequence (and vice versa).  Thus it is equivalent to \n\n<pre>  (not (and (PRED1 . ARGS) (PRED2 . ARGS))) .</pre>  \n\nFor example, (negationPreds owns rents) holds, as one cannot both own and rent a given thing at the same time.   \n<p>\nNote that the argument types of <code>PRED1</code> and <code>PRED2</code> need not be the same, they merely must not be disjoint.  Note also that <code>PRED1</code> and <code>PRED2</code> are constrained (see e.g. interArgIsa) either to both having the same fixed-arity (see FixedArityRelation) or to both having variable-arity (see VariableArityRelations).     \n<p>\nSee also genlPreds and negationInverse.", 'UniversalVocabularyMt', vStrDef).
 7658exactlyAssertedEL_next(comment, negationMt, "(negationMt MT-1 MT-2) means that the domain assumptions of the Microtheory MT-1 are inconsistent with those of the Microtheory MT-2, and no lifting can occur between MT-1 and MT-2 (i.e. assertions made in one microtheory should not be made visible to the other microtheory). For cases where two microtheories differ not in domain assumptions but purely in content (assertions made within those microtheories), see the less specialized contradictoryMt.", 'UniversalVocabularyMt', vStrDef).
 7659exactlyAssertedEL_next(comment, negationInverse, "A MetaPredicate for stating that each of two binary predicates is a logical \"contrary\" of the other's inverse. <code>(negationInverse BINPRED1 BINPRED2)</code> means that if <code>BINPRED1</code> holds between a pair <code><THING1, THING2></code>, then <code>BINPRED2</code> does <i>not</i> hold between the inverse pair <code><THING2, THING1></code> (and vice versa).  In other words, <code>(negationInverse BINPRED1 BINPRED2)</code> is equivalent to <code>(not (and (BINPRED1 ARG1 ARG2) (BINPRED2 ARG2 ARG1)))</code>.\n<p>\nNote that any AsymmetricBinaryPredicate is related to itself by negationInverse.  For example, (negationInverse subordinates subordinates) holds, since if one person is a subordinate of another, the latter person cannot at the same time also be a subordinate of the former.  See also negationPreds and genlInverse.", 'UniversalVocabularyMt', vStrDef).
 7660exactlyAssertedEL_next(comment, nearestIsa, "A TaxonomicSlotForAnyThing, and a specialization of isa (q.v.).  (nearestIsa OBJ COL) means that COL is a \"nearest\" collection of which OBJ is an instance.  That is, (isa OBJ COL) holds, OBJ is not identical to COL, and there is no reified Collection NEARER-COL distinct from OBJ and COL such that both (isa OBJ NEARER-COL) and (genls NEARER-COL COL) hold.  Note that nearestIsa is non-assertible (see notAssertible), since its extension at any given time depends upon (and so must be recomputed from) the current state of the isa and genls hierarchy in the Cyc Knowledge Base.", 'UniversalVocabularyMt', vStrMon).
 7661exactlyAssertedEL_next(comment, nearestGenls, "A TaxonomicSlotForCollections and a KBDependentRelation (qq.v.) that is a specialization of genls. \n<code>(nearestGenls COL NEAR-COL)</code> means that <code>NEAR-COL</code> is a \"nearest\" generalization of <code>COL</code>.  More precisely:\n<p>\n(i) <code>(genls COL NEAR-COL)</code> holds, <br>\n(ii) <code>COL</code> is not identical to <code>NEAR-COL</code>, <br>\n(iii) both <code>COL</code> and <code>NEAR-COL</code> are reified, and <br>\n(iv) there is no reified Collection <code>NEARER-COL</code> distinct from <code>COL</code> and <code>NEAR-COL</code> such that both <code>(genls COL NEARER-COL)</code> and <code>(genls NEARER-COL NEAR-COL)</code> hold.\n<p>\nNote that nearestGenls is non-assertible (see notAssertible), since its extension at any given time depends upon (and so must be recomputed from) the current state of the genls hierarchy in the Cyc Knowledge Base.", 'UniversalVocabularyMt', vStrMon).
 7662exactlyAssertedEL_next(comment, nearestGenlPreds, "A TaxonomicSlotForPredicates and a specialization of genlPreds (q.v.).  (nearestGenlPreds PRED NEAR-PRED) means that NEAR-PRED  is a \"nearest\" generalization of PRED.  That is, (genlPreds PRED NEAR-PRED)  holds, PRED is not identical to NEAR-PRED, and there is no reified Predicate  OTHER-PRED distinct from PRED and NEAR-PRED such that both  (genlPreds PRED OTHER-PRED) and (genlPreds OTHER-PRED NEAR-PRED) hold.  Note   that nearestGenlPreds is non-assertible (see notAssertible), since its  extension at any given time depends upon (and so must be recomputed from) the  current state of the genlPreds hierarchy in the Cyc Knowledge Base.", 'UniversalVocabularyMt', vStrDef).
 7663exactlyAssertedEL_next(comment, nearestGenlMt, "A specialization of genlMt.  (nearestGenlMt MT NEAR-MT) means that NEAR-MT is a \"nearest\" microtheory of which MT is a specialization.  That is, (genlMt MT NEAR-MT) holds, MT is not identical to NEAR-MT, and there is no reified Microtheory NEARER-MT distinct from MT and NEAR-MT such that both (genlMt MT NEARER-MT) and (genlMt NEARER-MT NEAR-MT) hold.  Note that nearestGenlMt is non-assertible (see notAssertible), since its extension at any given time depends upon (and so must be recomputed from) the current state of the genlMt hierarchy in the Cyc Knowledge Base.", 'UniversalVocabularyMt', vStrDef).
 7664exactlyAssertedEL_next(comment, nearestDifferentIsa, "(nearestDifferentIsa OBJ-1 OBJ-2 NEAR-DIFF) means that NEAR-DIFF is a \"nearest\" collection of which OBJ-1 is an instance, but OBJ-2 is not. That is, (isa OBJ-1 NEAR-DIFF) holds, but (isa OBJ-2 NEAR-DIFF) does not, and there is no reified Collection OTHER-COL distinct from NEAR-DIFF such that (isa OBJ-1 OTHER-COL) holds, (isa OBJ-2 OTHER-COL) does not hold, and (genls OTHER-COL NEAR-DIFF) holds. Note that this predicate is notAssertible, since it must always be recomputed from the current state of the isa and genls hierarchy. For comparison, see nearestDifferentGenls.", 'UniversalVocabularyMt', vStrMon).
 7665exactlyAssertedEL_next(comment, nearestDifferentGenls, "(nearestDifferentGenls COL-1 COL-2 NEAR-DIFF) relates collections COL-1 and COL-2 to the nearest unsubsumed collections NEAR-DIFF of which COL-1 is a subset but COL-2 is not. This predicate is notAssertible, since it  must always be recomputed from the current state of the genls heirarchy.  For comparison, see nearestDifferentIsa.", 'UniversalVocabularyMt', vStrMon).
 7666exactlyAssertedEL_next(comment, nearestCommonSpecs, "(nearestCommonSpecs COL-1 COL-2 NEAR-SPEC) relates collections COL-1 and COL-2 to the nearest unsubsumed collections NEAR-SPEC of which are subsets of both COL-1 and COL-2. This predicate is notAssertible, since it  must always be recomputed from the current state of the genls heirarchy.  For comparison, see also nearestCommonIsa and nearestCommonGenls.", 'UniversalVocabularyMt', vStrMon).
 7667exactlyAssertedEL_next(comment, nearestCommonIsa, "(nearestCommonIsa THING1 THING2 NEAR-COL) means that NEAR-COL is a \"nearest\" collection of which both THING1 and THING2 are instances.  That is, both (isa THING1 NEAR-COL) and (isa THING2 NEAR-COL) hold, and there is no reified Collection NEARER-COL distinct from NEAR-COL such that (isa THING1 NEARER-COL), (isa THING2 NEARER-COL) and (genls NEARER-COL NEAR-COL) all hold.  Note that this predicate is non-assertible (see notAssertible), since its extension at any given time depends upon (and so must be computed from) the current state of the isa and genls hierarchies in the Cyc Knowledge Base. See also nearestCommonGenls and nearestCommonSpecs.", 'UniversalVocabularyMt', vStrMon).
 7668exactlyAssertedEL_next(comment, nearestCommonGenls, "A TaxonomicPredicateForCollections that relates two collections to their nearest common generalizations represented in the Cyc Knowledge Base.  <code>(nearestCommonGenls COL1 COL2 NEAREST-GENL)</code> means that (i) <code>NEAREST-GENL</code> in known in the Cyc Knowledge Base to subsume (via genls) both <code>COL1</code> and <code>COL2</code> and (ii) there is no proper specialization of <code>NEAREST-GENL</code> that is known to subsume both <code>COL1</code> and <code>COL2</code>.\n<p>\nNote that nearestCommonGenls is <i>not</i> functional with respect to its third argument, as a pair of collections might have several nearest common generalizations, all orthogonal to each other.  Note also that this predicate is notAssertible, since it must always be recomputed from the current state of the represented genls heirarchy.  \n<p>\nSee also nearestCommonIsa and nearestCommonSpecs.", 'UniversalVocabularyMt', vStrMon).
 7669exactlyAssertedEL_next(comment, nearestCommonGenlMt, "(nearestCommonGenlMt MT-1 MT-2 NEAR-MT) relates microtheories MT-1 and MT-2 to the nearest unsubsumed microtheories NEAR-MT of which both are spec microtheories.  This predicate is notAssertible, since it must always be recomputed from the current state of the genlMt hierarchy.", 'UniversalVocabularyMt', vStrDef).
 7670exactlyAssertedEL_next(comment, natFunction, "(natFunction NAT FUNCTION) states that FUNCTION is the function used in the non-atomic term NAT.  For example,  (natFunction (JuvenileFn Dog) JuvenileFn).  More precisely, (termOfUnit NAT (FUNCTION ...)) implies  (natFunction NAT FUNCTION).", 'UniversalVocabularyMt', vStrMon).
 7671exactlyAssertedEL_next(comment, natArgumentsEqual, "(natArgumentsEqual NAT1 NAT2) means that the\narguments of NAT1 and NAT2 unify.  For example,  (natArgumentsEqual (FemaleFn Dog) (MaleFn Dog).  More precisely, (and (termOfUnit NAT1 (FUNCTION1 . ARGS)) (termOfUnit NAT2 (FUNCTION2 . ARGS))) implies  (natArgumentsEqual NAT1 NAT2).", 'UniversalVocabularyMt', vStrMon).
 7672exactlyAssertedEL_next(comment, natArgument, "(natArgument NAT N TERM) means that TERM is in the Nth argument position of the non-atomic term NAT.  For example,  (natArgument (JuvenileFn Dog) 1 Dog).  Note that (termOfUnit NAT (FUNCTION ... ARGN ...)) implies  (natArgument NAT N ARGN).", 'UniversalVocabularyMt', vStrMon).
 7673exactlyAssertedEL_next(comment, myCreator, "<code>(myCreator X Y)</code> means that <code>Y</code> is the constant representing the person who introduced the constant <code>X</code> into the Cyc vocabulary. In general, the editing interfaces to the Cyc KB only allow the KB to be modified when an instance of Cyclist is designated as the author of the changes.  See also sourceOfTerm-Person.", 'BookkeepingMt', vStrDef).
 7674exactlyAssertedEL_next(comment, myCreationTime, "<code>(myCreationTime CONSTANT TIME)</code> means that the CycLConstant <code>CONSTANT</code> was created at <code>TIME</code>, an instance of CycUniversalDate.  The format of <code>TIME</code> is YYYYMMDD; that is, the first four digits give the year in which the constant was created, the next two digits give the month in which it was created, and the final two digits give the day of the month on which it was created. For example, 19910309 is March 9, 1991.", 'BookkeepingMt', vStrDef).
 7675exactlyAssertedEL_next(comment, myCreationSecond, "(myCreationSecond CONSTANT SECOND) means that the CycLConstant CONSTANT was created at the CycUniversalSecond SECOND on the day CONSTANT was created (the related predicate myCreationTime (q.v.) relates a CycLConstant to the day it was created).  The format of SECOND is HHMMSS; that is, the first two digits give the hour of the day on which the constant was created, the second two digits give the minute of the hour at which the constant was created, and the last two digits give the second of the minute at which the constant was created.  For example, midnight is 000000 (or simply 0), noon is 120000, 3:42:59 pm is 154259, and 11:59:59 pm is 235959.", 'BookkeepingMt', vStrMon).
 7676exactlyAssertedEL_next(comment, myCreationPurpose, "A BookkeepingPredicate and a DocumentationConstant that relates a CycL constant (or other reifiable denotational term) to the Cyc-based project for which the term was created.  (myCreationPurpose TERM PROJECT) means that TERM was created as part of work that was done for PROJECT, and implies that the creator of TERM (see myCreator) was working PROJECT at the time.", 'BookkeepingMt', vStrMon).
 7677exactlyAssertedEL_next(comment, multiplicationUnits, "A ternary predicate that relates UnitOfMeasure (q.v.) functions.  <code>(multiplicationUnits UNIT1 UNIT2 PRODUNIT)</code> means that <code>PRODUNIT</code> is the unit-of-measure that always returns the product of the values returned by <code>UNIT1</code> and <code>UNIT2</code> for two respective arguments (or argument-sequences) when it is itself applied to the product of those arguments (or sequences).  That is, whenever <code>(UNIT1 . ARGS1) = VALUE1</code> and <code>(UNIT2 . ARGS2) = VALUE2</code>, then <code>(PRODUNIT (TimesFn ARGS1 ARGS2)) = (TimesFn VALUE1 VALUE2)</code>.\n<p>\nFor example, (multiplicationUnits Mile Mile SquareMile) holds, and thus (TimesFn (Mile 2) (Mile 3)) is equal to (SquareMile 6).\n<p>\nThe predicate multiplicationUnits corresponds to (see functionCorrespondingPredicate) both of the functions UnitProductFn and PerFn (qq.v.).  Thus,\n<p>\n\t<code>(multiplicationUnits UNIT1 UNIT2 PRODUNIT)</code>\n<p>\nis equivalent to\n<p>\n\t<code>(equals PRODUNIT (UnitProductFn UNIT1 UNIT2))</code>\n<p>\nis equivalent to\n<p>\n\t<code>(equals UNIT1 (PerFn PRODUNIT UNIT2))</code> .", 'UniversalVocabularyMt', vStrDef).
 7678exactlyAssertedEL_next(comment, mtVisible, "A unary EvaluatablePredicate that applies to a Microtheory.  <code>(mtVisible MT)</code> means that the contents of <code>MT</code> are visible in the current query context.  \n\nIn general, \n<pre>\n(genlMt MT1 MT2) \n</pre>\nentails \n<pre>\n(ist MT1 (mtVisible MT2),\n</pre>\nbut the converse does not hold.  In particular, it fails when <code>MT1</code> is a ProblemSolvingCntxt.  For example, \n<pre>\n(ist EverythingPSC (mtVisible HumanSocialLifeMt))\n</pre>\nholds (in BaseKB), but\n<pre>\n(genlMt EverythingPSC HumanSocialLifeMt)\n</pre>\ndoes not hold (in BaseKB).", 'UniversalVocabularyMt', vStrMon).
 7679exactlyAssertedEL_next(comment, minQuantValue, "A specialization of scalarBounds (q.v.) that relates a given ScalarInterval (q.v.) to the minimum ScalarPointValue (q.v.) it subsumes (see quantitySubsumes). <code>(minQuantValue SCALAR POINT)</code> means that the lower limit of <code>SCALAR</code> is <code>POINT</code>.\n<p>\nFor example, if all mailroom employees earned from five to eight dollars per hour, <code>(minQuantValue \"MailroomPayRange\" (DollarsPerHour 5))</code> would hold.  Other examples:\n<pre>\n  (minQuantValue (Mile 15 20) (Mile 15))\n\n  (minQuantValue (Unity 6 12) 6).\n</pre>\n<p>\nSee also maxQuantValue and pointQuantValue.", 'UniversalVocabularyMt', vStrDef).
 7680exactlyAssertedEL_next(comment, minimizeExtent, "An instance of both MetaKnowledgePredicate and MetaPredicate (qq.v.) that is used to state that the Cyc system will \"assume\" that a (sequence of) thing(s) is not in the extension (see relationExtension) of a given predicate if the CycInferenceEngine is unable to prove that it is.  \n<p>\n<code>(minimizeExtent PRED)</code> means that, for any sequence of things <code><THING1, ..., THINGn></code> such that <code>(PRED THING1 ... THINGn)</code> holds, the fact that this holds is either expressed by some GAF (i.e. a \"ground atomic formula\"; see CycLClosedAtomicSentence) that is asserted in the Cyc Knowledge Base or is deducible via the inference engine from what is in the KB.  \n<p>\nThe practical import of a minimizeExtent assertion is that it reflects an underlying assumption that if the inference engine cannot prove some given sentence of the form <code>(PRED ARG1 ... ARGN)</code>, then that fact constitutes an argument for its negation <code>(not (PRED ARG1 ... ARGN))</code>; and, if the \"negation by failure\" inference parameter is turned on, the inference engine will actually conclude that this negation is true.  Note that a minimizeExtent assertion is weaker than the corresponding completeExtentEnumerable (q.v.) assertion would be, in that the latter does not require that the inference engine attempt to deduce <code>(PRED ARG1 ... ARGn)</code> before concluding that it is not true.  See also minimizeExtentForArg and the shared NoteOnClosedWorldAssumption.", 'UniversalVocabularyMt', vStrDef).
 7681exactlyAssertedEL_next(comment, minimize, "minimize allows Cyc to assume that a statement is not\ntrue unless it is known to be true.  Specifically, if for some\nbindings of the variables that appear in the minimized formula the\nformula with the bindings substituted in cannot be proved, then assume\nthe negation of the formula with the bindings substituted in.  From an\nexample in the KB: (minimize (disjointWith ?Collection\n?Collection)) and binding ?Collection to Poodle means if we cannot\nprove (disjointWith Poodle Poodle) assume (not (disjointWith\nPoodle Poodle, i.e. assume every Collection is nonempty unless\nwe know otherwise.  In the case where we bind ?Collection to some\nother variable ?Y and substituting in means if we cannot show\n(disjointWith ?Y ?Y) then assume the negation, (not (forAll ?Y\n(disjointWith ?Y ?Y))) which is equivalent to (thereExists ?Y\n(not (disjointWith ?Y ?Y))). This is one of the predicates that\nhas been created to allow Cyc to do negation by failure.  Other\nrelated predicates are minimizeExtent and minimizeExtentForArg. ", 'UniversalVocabularyMt', vStrDef).
 7682exactlyAssertedEL_next(comment, microtheoryDesignationArgnum, "Used to specify which argument of a given MicrotheoryDesignatingRelation\ndesignates the microtheory in which to interpret some formula.", 'UniversalVocabularyMt', vStrDef).
 7683exactlyAssertedEL_next(comment, meetsPragmaticRequirement, "A MetaKnowledgePredicate that is used to express that a pragmatic precondition on a given rule is satisfied.  The predicate takes as arguments a list of CycL variables and an asserted rule (see CycLRuleAssertion) in which those variables occur \"free\".  At the EL (\"epistemological level\"), meetsPragmaticRequirement sentences are not asserted as GAFs, but appear instead as the consequents of system-generated implies rules.  For a given sequence of values for the respective variables <code>VAR1</code>, ..., <code>VARn</code>, <code>(meetsPragmaticRequirement (TheList VAR1 ... VARn) RULE)</code> means that some pragmatic precondition placed on <code>RULE</code>'s being used by the Cyc inference engine (see pragmaticRequirement) is satisfied with respect to those values.\n<p>\nLet's make this more precise and explicit.  A pragmatic precondition for a rule is written like so:\n<p>\n<pre>\n   (pragmaticRequirement CONDITION RULE)\n</pre>\n<p>\nand gets canonicalized into a rule involving meetsPragmaticRequirement like so:\n<p>\n<pre>\n   (implies\n     CONDITION\n    (meetsPragmaticRequirement (TheList VAR1 ... VARn) RULE)),\n</pre>\n<p>\nwhere <code>VAR1, ..., VARn</code> are all and only the variables that occur free in <code>RULE</code> and thus include all (and possibly only) the variables that occur free in <code>CONDITION</code> (i.e. as <code>RULE</code> and <code>CONDITION</code> explicitly appear in the KB browser, without consideration of their having \"implicit\" initial universal quantifiers).\n<p>\nThe above meetsPragmaticRequirement rule is used in inference similarly to an abnormal rule.  If <code>CONDITION</code> is not known to hold for a given sequence of values <code><VAL1, ..., VALn></code> for its variables <code><VAR1, ..., VARn></code>, then those values do not \"meet the pragmatic requirement\" for <code>RULE</code>; and hence inference will not proceed using <code><VAL1, ..., VALn></code> with <code>RULE</code>.\n<p>\nThe effect of the foregoing is that any asserted rule <code>RULE</code> is implicitly treated by the Cyc inference engine as if it had the form\n<p>\n<pre>\n (implies\n  (meetsPragmaticRequirement (TheList VAR1 ... VARn) RULE)\n   RULE)\n</pre>\n<p>\n(with <code>VAR1, ..., VARn</code> as described above).\n<p>\nThis convention allows the logical content of a rule to be expressed independently of any pragmatic preconditions for its being used in inference.  If a rule has multiple pragmatic requirements, it must meet all of them to be used in inference.\n<p>\nAlso see abnormal, which is syntactically similar and has a related  interpretation.", 'UniversalVocabularyMt', vStrDef).
 7684exactlyAssertedEL_next(comment, means, "A MetaLanguagePredicate (q.v.) that relates SubLSExpressions to their meanings: the things in the intended model of the CycL language that those terms denote, refer to, stand for, or express. <code>(means TERM THING)</code> means that <code>TERM</code> denotes, refers to, stands for, or expresses <code>THING</code>. <code>TERM</code> will often be explicitly quoted, by being wrapped in the syncategorematic quotation symbol 'Quote'. For example, the true sentence '(means (Quote Plato) Plato)' means that the CycL term 'Plato' means (denotes) the person Plato. (Thus means's first argument-place is <i>not</i> \"implicitly quoted\"; cf. quotedArgument).\n<p>\nBut note that the first argument of means might not be quoted at all. Suppose (e.g.) that the term 'Plato' were the CycL constant most beloved of Cyclists, and that a new constant 'CyclistsFavoriteConstant' were reified and defined so as to reflect this fact. Then 'CyclistsFavoriteConstant' would denote the CycL constant 'Plato', which in turn denotes the man Plato; and so the sentence '(means CyclistsFavoriteConstant Plato)' -- which involves no quotation -- would be true.\n<p>\nNote finally that the sentence '(means Plato Plato)' is of course <i>not</i> true, as it means that the man Plato is a CycL term that denotes the man Plato, which is a patent falsehood since no man is a CycL term and no man denotes anything.\n<p>\nSee also expresses, denotes, hasDenotatum, quotedIsa, EscapeQuote, and the shared NoteAboutQuotingInCycL.", 'UniversalVocabularyMt', vStrMon).
 7685exactlyAssertedEL_next(comment, maxQuantValue, "A specialization of scalarBounds (q.v.) that relates a given ScalarInterval (q.v.) to the maximum ScalarPointValue (q.v.) it subsumes (see quantitySubsumes). <code>(maxQuantValue SCALAR POINT)</code> means that the upper limit of <code>SCALAR</code> is <code>POINT</code>.\n<p>\nFor example, if all mailroom employees earned from five to eight dollars per hour, <code>(maxQuantValue \"MailroomPayRange\" (DollarsPerHour 8))</code> would hold.  Other examples:\n<pre>\n  (maxQuantValue (Mile 15 20) (Mile 20))\n\n  (maxQuantValue (Unity 6 12) 12).\n</pre>\n<p>\nSee also minQuantValue and pointQuantValue.", 'UniversalVocabularyMt', vStrDef).
 7686exactlyAssertedEL_next(comment, maxQuantValue, "(maxQuantValue SCALAR POINT) means that the upper limit of the quantity SCALAR is POINT, an instance of ScalarPointValue.  SCALAR is an instance of ScalarInterval.  For example, the maxQuantValue for the pay of mail room employees might be (DollarsPerHour 6.5); e.g., (maxQuantValue `MailPay' (DollarsPerHour 6.5)).  Another example: (maxQuantValue (Unity 5 10) 10).", 'UniversalVocabularyMt', vStrDef).
 7687exactlyAssertedEL_next(comment, knownSentence, "A KBDependentRelation (q.v.) and  specialization of trueSentence (q.v.) that is used to state  that a given sentence is \"known\" to be true to the Cyc system. More precisely, (knownSentence SENT) means that SENT is provable  by the Cyc inference engine from sentences currently in the Knowledge  Base.  knownSentence is a non-assertible predicate (see  notAssertible).  Note that this predicate is not to be confused  with knownSentence, which is used to state that a given  sentence is explicitly asserted in the KB.", 'UniversalVocabularyMt', vStrMon).
 7688exactlyAssertedEL_next(comment, knownAntecedentRule, "A MetaKnowledgePredicate that is used to state a strong pragmatic directive to the CycInferenceEngine.  Asserting (knownAntecedentRule RULE) tells the inference engine to automatically generate a removal module to implement RULE; i.e. to solve queries unifying with the consequent of RULE by attempting to prove the substituted antecedent of RULE.  When this removal module is used during inference, it attempts to prove the substituted antecedent via removal only (see knownSentence).  It does not preclude other uses of RULE in inference.", 'UniversalVocabularyMt', vStrMon).
 7689exactlyAssertedEL_next(comment, ist, "This predicate relates a microtheory to any sentence that is true in it.  (ist MT SENT) means that the CycL sentence SENT (or, if you prefer, the proposition SENT expresses) is true in the microtheory MT.  Note that SENT need not actually be _asserted_ in MT; MT might for example \"inherit\" SENT from a more general microtheory.  (Cf. ist-Asserted.)", 'UniversalVocabularyMt', vStrDef).
 7690exactlyAssertedEL_next(comment, isa, "A TaxonomicSlot (q.v.) that relates things of any  kind to collections (see Collection) of which they are instances.   <code>(isa THING COL)</code> means that <code>THING</code> is an instance of the collection <code>COL</code>.   isa is by far the most commonly-occurring predicate in the Cyc Knowledge  Base, and is one of the relations most fundamental to the Cyc ontology. An important logical feature of isa is that it \"transfers through\"  genls (q.v.): <code>(isa THING COL)</code> and <code>(genls COL SUPERCOL)</code> jointly  imply <code>(isa THING SUPERCOL)</code>.  This logical feature is expressed in a  rule that -- along with various other rules that also sanction the  derivation of isa sentences -- has been asserted to the Knowledge Base.   As a result, only a small fraction of the isa based ground atomic  formulas (or \"GAF\"s; see CycLClosedAtomicSentence) the Cyc system  \"knows\" to be true have been manually asserted; the vast majority  have been derived, or are derivable, automatically by the Cyc inference  engine via the use of such rules.  See also elementOf.", 'UniversalVocabularyMt', vStrDef).
 7691exactlyAssertedEL_next(comment, irrelevantTerm, "A CycInferenceHeuristicRelevancePredicate. (irrelevantTerm TERM) states that the CycLClosedDenotationalTerm TERM should be heuristically considered less relevant to inferences made in the current Microtheory.  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrDef).
 7692exactlyAssertedEL_next(comment, irrelevantPredAssertion, "(irrelevantPredAssertion PREDICATE ASSERTION) states that the given ASSERTION should be heuristically considered very unlikely to be relevant to inferences concluding uses of the given PREDICATE in the current mt.  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrDef).
 7693exactlyAssertedEL_next(comment, irrelevantMt, "A CycInferenceHeuristicRelevancePredicate. (irrelevantMt MT) means that all assertions made in the Microtheory MT should be heuristically considered very unlikely to be relevant to inferences done in the Microtheory MT-1 in which (irrelevantMt MT) is asserted (where MT-1 and MT need not be the same).  As a consequence, note that when (irrelevantMt MT) is asserted in a Microtheory MT-1, each of the assertions in MT will be an irrelevantAssertion (q.v.) for inferences done in MT-1.", 'UniversalVocabularyMt', vStrMon).
 7694exactlyAssertedEL_next(comment, irrelevantAssertion, "A CycInferenceHeuristicRelevancePredicate. (irrelevantAssertion ASSERTION) states that the CycLAssertion ASSERTION should be heuristically considered very unlikely to be relevant to inferences in the current Microtheory.  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrDef).
 7695exactlyAssertedEL_next(comment, interArgResultIsaReln, "A quintary MetaRelation predicate for stating that a certain kind of complex, partly isa based relationship holds between a given argument to a given function and the corresponding value that is returned. (interArgResultIsaReln FUNC N RELATION RELATION-NAT-TERM-ARG RELATION-COLLECTION-ARG) means that, if there is a sentence asserted in the KB relating NAT-TERM and COLLECTION via RELATION and NAT-TERM is the RELATION-NAT-TERM-ARGth argument in the sentence and COLLECTION is the RELATION-COLLECTION-ARGth argument, then when NAT-TERM appears as the Nth argument to FUNC, then (regardless of what the other arguments to FUNC might be) the value (if any) of that function for those arguments is an instance of COLLECTION.  That is: if (RELATION ... NAT_TERM ... COLLECTION ...) or (RELATION ... COLLECTION ... NAT_TERM  ...) is an asserted sentence, and (FUNC ARG(1) ... ARG(N-1) NAT_TERM ...) = VALUE, then VALUE is an instance of COLLECTION. Obviously, COLLECTION must be a collection; so RELATION's RELATION-COLLECTION-ARGth argument-place is likely to be isa constrained (see argIsa) to Collection or some specialization thereof.", 'UniversalVocabularyMt', vStrMon).
 7696exactlyAssertedEL_next(comment, interArgResultIsa, "A quaternary MetaRelation predicate for stating that a certain kind of complex, partly isa -based relationship holds between a given argument to a given function and the corresponding value that is returned.\n<p>\n<code>(interArgResultIsa FUNC N INDEP-ARG-COL DEP-ARG-COL)</code> means that, when an instance of <code>INDEP-ARG-COL</code> appears as the <code>N</code>th argument to <code>FUNC</code>, then (regardless of what the other arguments to <code>FUNC</code> might be) the value (if any) of that function for those arguments is an instance of <code>DEP-ARG-COL</code>.  That is: if <code>INST</code> is an instance of <code>INDEP-ARG-COL</code> and <code>(FUNC ARG1 ... ARGN-1 INST ...) = VALUE</code>, then <code>VALUE</code> is an instance of <code>DEP-ARG-COL</code>.\n<p>\nFor example, <code>(interArgResultIsa RoundUpFn 1 RealNumber Integer)</code> means that the rounding-up function RoundUpFn returns an integer whenever it is given a real number as its first (and only) argument.\n<p>\nNote that, unlike (e.g.) the InterArgTypePredicates, interArgResultIsa <i>cannot</i> be used to put semantic well-formedness constraints on functions.  See also the similar but less flexible ternary interArg1ResultIsa et al.", 'UniversalVocabularyMt', vStrDef).
 7697exactlyAssertedEL_next(comment, interArgResultGenlReln, "A quintary MetaRelation predicate for stating that a certain  kind of complex, partly genls based relationship holds between a given  argument to a given function and the corresponding value that is returned.  (interArgResultGenlReln FUNC N RELATION RELATION-NAT-TERM-ARG RELATION-COLLECTION-ARG) means that, if there is a sentence asserted in the KB relating NAT-TERM and COLLECTION via RELATION and NAT-TERM is the RELATION-NAT-TERM-ARGth argument in the sentence and COLLECTION is the RELATION-COLLECTION-ARGth argument, then when NAT-TERM appears as the Nth argument to FUNC, then (regardless of what the other arguments to FUNC might be) the value (if any) of that function for those arguments is a subcollection of COLLECTION. That is: if (RELATION ... NAT_TERM ... COLLECTION ...) or  (RELATION ... COLLECTION ... NAT_TERM  ...) is an asserted sentence, and (FUNC ARG(1) ... ARG(N-1) NAT_TERM ...) = VALUE, then VALUE is a subcollection of COLLECTION. Obviously, COLLECTION must be a collection; so RELATION's RELATION-COLLECTION-ARGth argument-place is likely to be isa  constrained (see argIsa) to Collection or some specialization thereof.", 'UniversalVocabularyMt', vStrMon).
 7698exactlyAssertedEL_next(comment, interArgResultGenl, "A quaternary MetaRelation predicate for stating that a certain kind of complex, partly genls based relationship holds between a given argument to a given function and the corresponding value that is returned. (interArgResultGenls FUNC N INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, when a subcollection of INDEPENDENT-ARG-COL appears as the Nth argument to FUNC, then (regardless of what the other arguments to FUNC might be) the value (if any) of that function for those arguments is a subcollection of DEPENDENT-ARG-COL.  That is: if INST is a subcollection of INDEPENDENT-ARG-COL and (FUNC ARG(1) ... ARG(N-1) INST ...) = VALUE, then VALUE is a subcollection of DEPENDENT-ARG-COL.  Note that, unlike (e.g.) the InterArgTypePredicates, interArgResultGenl _cannot_ be used to put semantic well-formedness constraints on functions.  See also the similar but less flexible ternary interArg1ResultGenls et al.", 'UniversalVocabularyMt', vStrDef).
 7699exactlyAssertedEL_next(comment, interArgIsa, "A quintary instance of InterArgIsaPredicate (q.v.).   <code>(interArgIsa RELN INDEP-ARGNUM INDEP-COL DEP-ARGNUM DEP-COL)</code> means that,  when an instance of <code>INDEP-COL</code> appears as the <code>INDEP-ARGNUM</code>th argument to <code>RELN</code>,  a necessary condition for semantic well-formedness is that the <code>DEP-ARGNUM</code>th argument must be an instance of <code>DEP-COL</code>.  That is, if <code>INDEP-INST</code> is an instance of <code>INDEP-COL</code>, then <code>(RELN</code> ... <code>INDEP-INST</code> ...), where <code>INDEP-INST</code> is the <code>INDEP-ARGNUM</code>th (or \"independent\") argument to <code>RELN</code>, is semantically well-formed only if the <code>DEP-ARGNUM</code>th (or \"dependent\") argument (which is some item in the sequence <... <code>INDEP-INST</code> ...> other than the <code>INDEP-ARGNUM</code>th) is an instance of <code>DEP-COL</code>.\n<p>\nFor example, (interArgIsa performedBy 1 PurposefulAction 2 IntelligentAgent) means that, if <code>ACT</code> is a PurposefulAction, then <code>(performedBy ACT AGENT)</code> is semantically well-formed only if <code>AGENT</code> is an IntelligentAgent.\n<p>\nFor an explanation of semantic well-formedness, see CycLExpression-Assertible and its direct specializations.  For a more general explanation of independent and dependent arguments in the present sense, see InterArgConstraintPredicate.  For similar to but less flexible predicates than interArgIsa, which have already-fixed positions for the independent and dependent arguments, see the ternary interArgIsa1-2 et al.", 'UniversalVocabularyMt', vStrMon).
 7700exactlyAssertedEL_next(comment, interArgDifferent, "A MetaRelation used for stating a certain kind of necessary condition for being an element of the domain of a given Relation (see relationDomain).  Thus (to put it in terms of the semantics of CycL expressions) interArgDifferent can be used for stating a certain kind of truth- or denotation-condition for a given relation-denoting expression.  (interArgDifferent RELN N M) means that RELN (if it is a Predicate or other TruthFunction) only holds among or (if it is a Function-Denotational) only has a value for sequences of arguments whose Nth and Mth members are distinct (see different).  That is (assuming without loss of generality that N < M): if RELN is a predicate or other \"truth-function\" then (RELN ... ARGN ... ARGM ...) holds only if ARGN and ARGM are distinct, and if RELN is a function then it is defined for (i.e. associates a value with) a sequence <THING-1, ..., THING-N, ..., THING-M, ...> only if THING-N and THING-M are distinct.  For example, (interArgDifferent opponentsInConflict 1 2) means that no-one is his or her own opponent in a conflict.\n<p>\nNote that this predicate trivially holds for any relation with respect those argument-places it has that are subject to mutually disjoint (see disjointWith and cf. cosatisfiableInArgs) argument-type constraints (see ArgTypePredicate).", 'UniversalVocabularyMt', vStrMon).
 7701exactlyAssertedEL_next(comment, integerBetween, "A ternary IntangibleObjectRelatingPredicate that holds among Integers only.  <code>(integerBetween LOW MED HIGH)</code> means that <code>HIGH</code> is greaterThanOrEqualTo <code>MED</code>, and <code>MED</code> is greaterThanOrEqualTo <code>LOW</code>.", 'UniversalVocabularyMt', vStrDef).
 7702exactlyAssertedEL_next(comment, instanceElementType, "A binary FirstOrderCollectionPredicate that relates types of sets to the types of elements they have in common.  More precisely, <code>(instanceElementType SETTYPE COLLECTION)</code> means that every elementOf every instance of (see isa) <code>SETTYPE</code> is an instance of <code>COLLECTION</code>.  For example, both of these hold:\n<pre>\n  (instanceElementType PointSet Point)\n\n  (instanceElementType Set-Mathematical Thing) . \n</pre>\nSee the corresponding function SetOfTypeFn, which takes a given collection to the collection of <i>all</i> sets whose elements are instances of the former.  And see typeGenls for a similar predicate that relates collections of <i>collections</i> (rather than collections of sets) to their common element types.", 'UniversalVocabularyMt', vStrMon).
 7703exactlyAssertedEL_next(comment, indexicalReferent, "(indexicalReferent INDCONCEPT THING) means that in the context of the assertion, the IndexicalConcept INDCONCEPT has the referent THING.  This is a StrictlyFunctionalSlot, in keeping with the idea that the predicate will return one and only one 'value' for the second argument place at any given point in context space.  However, be advised that the arg2 will change from context to context.", 'UniversalVocabularyMt', vStrMon).
 7704exactlyAssertedEL_next(comment, independentArg, "A MetaPredicate that is used to state, of a given\n(ternary) InterArgConstraintPredicate, that it is (always) used to constrain a relation in such a way that a certain specified argument-place of the relation is for the \"independent\" argument (with respect to that constraint).  (independentArg INT-ARG-PRED N) means that any sentence of the form (INT-ARG-PRED RELN ...) constrains RELN in some way that treats RELN's Nth argument as independent.  For example, (independentArg interArgIsa3-4 3) holds.  See the comment on InterArgConstraintPredicate for an explanation of what it means to be an \"independent\" argument in this sense.  Note that independentArg is contrained to apply only to _ternary_ inter-argument constraint predicates, as only they have already-fixed positions for the corresponding independent and dependent arguments; thus it cannot (on pain of semantic malformedness) be applied to the quintary inter-argument constraint predicates, such as interArgIsa.", 'UniversalVocabularyMt', vStrDef).
 7705exactlyAssertedEL_next(comment, implies, "A binary LogicalConnective (q.v.) that corresponds to the material implication operator of propositional calculus.  The implies relation takes two CycLSentence-Assertibles as its arguments; and the syntactic result of applying the term 'implies' to two sentences is itself a sentence, called a \"conditional\" or \"implication\".  A sentence of the form (implies ANTECEDENT CONSEQUENT) is true if and only if ANTECEDENT is false or CONSEQUENT is true (or both).  Equivalently: it is not the case that ANTECEDENT is true and CONSEQUENT is false.  For example,\n<p>\n<pre>\n  (implies\n    (knows Muffet Patches-Cat)\n    (likesAsFriend Muffet Patches-Cat))\n</pre>\n<p>\nmeans that if Muffet knows Patches then she likes him.\n<p>\nCf. the predicate sentenceImplies, which is not a logical connective, and is primarily used in rules involving quantification over CycL sentences.", 'UniversalVocabularyMt', vStrDef).
 7706exactlyAssertedEL_next(comment, hypotheticalTerm, "(hypotheticalTerm TERM) states that TERM is a term that was hypothesized.  The most common reason a term is hypothesized is to pose a hypothetical query to Cyc.", 'UniversalVocabularyMt', vStrDef).
 7707exactlyAssertedEL_next(comment, holdsIn, "An instance of both TemporalPredicate and ModalPredicate that is used to state (in a somewhat indirect way) that a given sentence is true during a certain time period.  <code>(holdsIn TEMP SENT)</code> means that <code>SENT</code> is true at every moment in the temporalExtent (q.v.) of the TemporalThing <code>TEMP</code>.\n<p>\nFor example, the sentence <code>(holdsIn (YearFn 2003) (hasPets Curtis Patches-Cat))</code> means that throughout all of the year 2003 Curtis had Patches as a pet.  This entails (e.g.) that Curtis had Patches on 5 July 2003:\n<pre>\n  (holdsIn\n    (DayFn 5 (MonthFn July (YearFn 2003)))\n    (hasPets Curtis Patches-Cat))</code> .\n</pre>\n<p>\nSimilarly, <code>(holdsIn Patches-Cat (hasPets Curtis Patches-Cat))</code> means that Curtis has Patches as a pet for Patches's entire life.\n<p>\nSee also the more general predicate holdsSometimeDuring.\n<p>\nNote that a sentence of the form <code>(holdsIn TEMP (PRED ... ARGi ...))</code>, where <code>ARGi</code> is a TemporalThing, does <i>not</i> in general imply that <code>ARGi</code> temporally subsumes or even temporally intersects <code>TEMP</code>.  For example, <code>(holdsIn (YearFn 2003) (awareOf Curtis GeorgeWashington))</code> obviously doesn't imply that GeorgeWashington was alive in 2003.  <code>ARGi</code>'s temporally subsuming <code>TEMP</code> <i>does</i> follow, however, if <code>PRED</code> is a CotemporalPredicate that is contemporaryInArg (q.v.) in its <code>i</code>th argument-place (as hasPets is, in both argument-places).\n<p>\nNote also that there are two other ways to temporally-qualify sentences in CycL, which do not involve using holdsIn (or holdsSometimeDuring).  Both involve temporally qualifying the Microtheory in which the (otherwise unqualified) sentence is asserted, and either can be used to state something roughly equivalent to a holdsIn sentence.  Consider the first Curtis/Patches example above.  First, one could assert <code>(hasPets Curtis Patches-Cat)</code> in some microtheory <code>MT</code> such that <code>(holdsInTime-Always MT (YearFn 2003))</code>.  Second, one could assert <code>(hasPets Curtis Patches-Cat)</code> in a microtheory <code>MT'</code> such that both <code>(mtTimeIndex MT' (YearFn 2003))</code> and <code>(mtTimeParameter MT' TimePoint)</code> hold.  This later method, being the most developed and well-supported, is generally preferred over the others.\n<p>\nNote finally that it would be incorrect to assert a sentence like <code>(hasPets Curtis Patches-Cat)</code> in a non-temporally-qualified microtheory like the BaseKB, since Curtis didn't have Patches when (e.g.) he was a young boy, let alone in 3500 BCE.", 'UniversalVocabularyMt', vStrDef).
 7708exactlyAssertedEL_next(comment, hlPrototypicalInstance, "(hlPrototypicalInstance TERM COL) means that TERM is a prototypical instance of COL at the HL.  It is assumed that TERM has only two asserted assertions on it: one hlPrototypicalInstance assertion and one assertion of the form (isa TERM COL).  The CycInferenceEngine makes use of the prototypical instance during assertions to cache the work done by forward inference.  It is used when asserting the first isa assertion on a term with no other assertions about it yet.  <b>Do not assert comments, cyclistNotes or any other assertions on prototypical instances.</b>  They are intentionally minimal.", 'UniversalVocabularyMt', vStrDef).
 7709exactlyAssertedEL_next(comment, highlyRelevantTerm, "A CycInferenceHeuristicRelevancePredicate. (highlyRelevantTerm TERM) states that the CycLClosedDenotationalTerm TERM should be heuristically considered highly relevant to inferences made in the current Microtheory.  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrDef).
 7710exactlyAssertedEL_next(comment, highlyRelevantPredAssertion, "(highlyRelevantPredAssertion PREDICATE ASSERTION) states that the given ASSERTION should be heuristically considered highly relevant to inferences concluding uses of the given PREDICATE in the current mt.  See also other instances CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrDef).
 7711exactlyAssertedEL_next(comment, highlyRelevantMt, "A CycInferenceHeuristicRelevancePredicate. (highlyRelevantMt MT) means that all assertions in the Microtheory MT should be heuristically considered highly relevant to inferences done in the Microtheory MT-1 in which (highlyRelevantMt MT) is asserted (where MT-1 and MT need not be the same).  As a consequence, note that when (highlyRelevantMt MT) is asserted in a Microtheory MT-1, each of the assertions in MT will be a highlyRelevantAssertion (q.v.) for inferences done in MT-1.", 'UniversalVocabularyMt', vStrDef).
 7712exactlyAssertedEL_next(comment, highlyRelevantAssertion, "A CycInferenceHeuristicRelevancePredicate. <code>(highlyRelevantAssertion ASSERTION)</code> states that the CycLAssertion <code>ASSERTION</code> should be heuristically considered highly relevant to inferences that are performed in a context in which <code>(highlyRelevantAssertion ASSERTION)</code> is visible.  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrMon).
 7713exactlyAssertedEL_next(comment, greaterThanOrEqualTo, "A NumericComparisonPredicate (q.v.) that is a generalization of the mathematical greater-than-or equal-to <code>(>=)</code> relation to ScalarIntervals (q.v.) of all sorts, including quantitative intervals (see NumericInterval and Quantity) as well as point values (see ScalarPointValue).  <code>(greaterThanOrEqualTo VALUE1 VALUE2)</code> means that <code>VALUE1</code> is greater than or equal to <code>VALUE2</code> with respect to some scale that they are both on.  More precisely, there is some TotallyOrderedScalarIntervalType <code>SCALE</code> that both <code>VALUE1</code> and <code>VALUE2</code> are instances of and either (i) <code>SCALE</code> is a specialization of NumericInterval (e.g. RealNumber) and the minimum (see minQuantValue) of <code>VALUE1</code> is greater than or equal to the maximum (see maxQuantValue) of <code>VALUE2</code>, (ii) <code>(followingValueOnScale VALUE2 VALUE1 SCALE)</code> holds, or (iii) <code>(equals VALUE1 VALUE2)</code> holds.\n<p>\nSee also greaterThan and lessThanOrEqualTo.", 'UniversalVocabularyMt', vStrDef).
 7714exactlyAssertedEL_next(comment, greaterThan, "A NumericComparisonPredicate that is a generalization of the  mathematical greater-than ( > ) relation to ScalarIntervals (q.v.) of all sorts, including quantitative intervals (see NumericInterval and MeasurableQuantity) as well as point values (see ScalarPointValue).  <code>(greaterThan VALUE1 VALUE2)</code> means that  <code>VALUE1</code> is greater than <code>VALUE2</code> with respect to some scale that they  are both on.  More precisely, there is some TotallyOrderedScalarIntervalType SCALE that both <code>VALUE1</code> and <code>VALUE2</code> are instances of and either (i) <code>SCALE</code> is a specialization of  NumericInterval (e.g. RealNumber) and the minimum (see minQuantValue) of <code>VALUE1</code> is greater than the maximum (see maxQuantValue) of <code>VALUE2</code> or (ii) <code>(followingValueOnScale VALUE2 VALUE1 SCALE)</code> holds.", 'UniversalVocabularyMt', vStrDef).
 7715exactlyAssertedEL_next(comment, genMassNoun, "(genMassNoun TERM) means that the CycLReifiableDenotationalTerm TERM should be treated as a mass noun when CycL formulae containing TERM are paraphrased into English.  See also the related predicate prettyName.", 'UniversalVocabularyMt', vStrDef).
 7716exactlyAssertedEL_next(comment, genls, "A instance of TaxonomicSlotForCollections (q.v.) and  a specialization of generalizations.  genls relates a given collection  (see Collection) to those collections that subsume it.  More precisely, <code>(genls SUBCOL SUPERCOL)</code> means that <code>SUPERCOL</code> is a supercollection of <code>SUBCOL</code>:  anything that is an instance of (see isa) <code>SUBCOL</code> is also an instance of <code>SUPERCOL</code>.  For example, <code>(genls Dog Mammal)</code> holds.  genls is one of the most commonly-occurring predicates in the Cyc Knowledge Base, and one of  the relations most fundamental to the Cyc ontology.  See also subsetOf.", 'UniversalVocabularyMt', vStrDef).
 7717exactlyAssertedEL_next(comment, genlRules, "(genlRules RULE-SPEC RULE-GENL) means that the set of binding tuples that satisfy the open (universally quantified) variables in the consequent of RULE-SPEC via an application of RULE-SPEC will be a subset of the set of binding tuples that satisfy the open (universally quantified) variables in the consequent of RULE-GENL via an application of RULE-GENL.  For example, the following holds\n\n<pre>\n   (genlRules\n      (ist CCFBridgingMt\n        (implies\n          (and\n           (cCFCardiacValveRepairProcedure ?CVRP Plication-ValvularProcedure)\n           (rdf-type ?PROC HeartValveRepair-SurgicalProcedure)\n           (cCF-contains ?CVD ?CVRP)\n           (cCF-contains ?PROC ?CVD))\n          (isa ?PROC Plication-ValvularProcedure)))\n      (ist CCFBridgingMt \n       (implies\n         (rdf-type ?X HeartValveRepair-SurgicalProcedure)\n         (isa ?X HeartValveRepair-SurgicalProcedure)))) </pre>\n\n\nHence, if one was looking to return instances of HeartValveRepair-SurgicalProcedure, all other things being equal, there would be no need to query using both of these rules.  The rule in arg2 of genlRules here would get a superset of the answers that the rule in arg1 would return.\n ", 'UniversalVocabularyMt', vStrDef).
 7718exactlyAssertedEL_next(comment, genlPreds, "A MetaPredicate for stating that one predicate is a generalization of another.  <code>(genlPreds SPEC-PRED GENL-PRED)</code> means that <code>GENL-PRED</code> is a generalization of <code>SPEC-PRED</code>.  That is, <code>(GENL-PRED ARG1..ARGN)</code> holds whenever <code>(SPEC-PRED ARG1..ARGN)</code> holds.  For example, <code>(genlPreds touches near)</code> holds, as touching something implies being near it.\n<p>\nAs for the respective arities (see arity) of <code>SPEC-PRED</code> and <code>GENL-PRED</code>, (i) both predicates might have the same fixed-arity (see FixedArityRelation), (ii) both might have variable-arity (see VariableArityRelation), or (iii) <code>SPEC-PRED</code> might have a fixed-arity and <code>GENL-PRED</code> variable-arity.  (It cannot be the case that <code>SPEC-PRED</code> has variable-arity and <code>GENL-PRED</code> has a fixed-arity.)\n<p>\nSee also negationPreds, genlInverse, and negationInverse.", 'UniversalVocabularyMt', vStrDef).
 7719exactlyAssertedEL_next(comment, genlMt, "A reflexive and transitive BinaryPredicate that relates a Microtheory to a Microtheory.  <code>(genlMt SPEC-MT GENL-MT)</code> means that <code>SPEC-MT</code> is a specialization or extension of <code>GENL-MT</code>.  (Note that it need not be a <i>proper</i> specialization or extension.)  In particular, this entails that everything that is true in <code>GENL-MT</code> is also true in <code>SPEC-MT</code>.  This relation is sometimes expressed informally by saying that <code>SPEC-MT</code> \"sees\" <code>GENL-MT</code>.", 'UniversalVocabularyMt', vStrDef).
 7720exactlyAssertedEL_next(comment, genlInverse, "A MetaPredicate for stating that one binary  predicate is a generalization of the <i>inverse</i> of another binary predicate.   <code>(genlInverse PRED GENL-INV-PRED)</code> means that <code>GENL-INV-PRED</code> is a  \"generalized inverse\" of <code>PRED</code>.  That is, <code>(PRED ARG1 ARG2)</code> implies  <code>(GENL-INV-PRED ARG2 ARG1)</code>.  For example, <code>(genlInverse grandchildren ancestors)</code> means that grandparents are  ancestors of their grandchildren.  See also genlPreds and negationInverse.", 'UniversalVocabularyMt', vStrDef).
 7721exactlyAssertedEL_next(comment, genlCanonicalizerDirectives, "A transitive binary predicate that relates a given \nCanonicalizerDirective (q.v.) to more general ones.\n(genlCanonicalizerDirectives SPEC-DIRECTIVE GENL-DIRECTIVE) \nmeans that SPEC-DIRECTIVE is at least as specific a (set of) \ndirection(s) to the CycCanonicalizer as GENL-DIRECTIVE.  \nThat is, all the commands indicated by GENL-DIRECTIVE (and\npossibly others as well) are indicated by SPEC-DIRECTIVE.  \nFor example, (genlCanonicalizerDirectives\nLeaveSomeTermsAtELAndAllowKeywordVariables \nAllowKeywordVariables) holds.", 'CoreCycLImplementationMt', vStrMon).
 7722exactlyAssertedEL_next(comment, genKeyword, "An NLGenerationPredicate that\nrelates a given CycL denotational term to the SubL keyword \nthat is used to represent it in generating natural language \nfrom CycL.  (genKeyword CYCL-TERM KEYWORD) means that \nKEYWORD represents CYCL-TERM in the generation of natural \nlanguage paraphrases of CycL expressions, e.g. in genFormat \n(q.v.) assertions.", 'UniversalVocabularyMt', vStrDef).
 7723exactlyAssertedEL_next(comment, genFormat, "The Common Lisp format string ARG2 can be applied to the argument list ARG3 to generate pseudo-English for the Cyc Relation ARG1", 'UniversalVocabularyMt', vStrMon).
 7724exactlyAssertedEL_next(comment, forwardNonTriggerLiteral, "An HLPredicate that is used to state which literals in a forward rule should not be allowed to re-trigger forward inference.  This is useful for placing pragmatic restrictions on the applicability of forward rules.  It is only useful when used via pragmaticRequirement on a forward rule.\n<p>\nA pragmatic requirement of the form\n<pre>\n(pragmaticRequirement (forwardNonTriggerLiteral FORMULA) RULE),\n</pre>\nwhere <code>FORMULA</code> is a literal in the antecedent of <code>RULE</code>, ensures that new assertions that are instantiations of <code>FORMULA</code> do not trigger <code>RULE</code>.", 'UniversalVocabularyMt', vStrDef).
 7725exactlyAssertedEL_next(comment, formulaArity, "(formulaArity FORMULA INTEGER) means that the CycL formula FORMULA contains INTEGER arguments. See also FormulaArityFn.", 'UniversalVocabularyMt', vStrMon).
 7726exactlyAssertedEL_next(comment, forAll, "A binary Quantifier that corresponds to the standard universal quantifier of predicate calculus.  The relation forAll takes as its arguments a variable (ELVariable) and a sentence (ELSentence-Assertible) in which, typically, that variable occurs free.  A closed formula (see CycLClosedFormula) of the form (forAll VAR SENT) is a \"universally quantified\" sentence that states (roughly) that every thing in the universe of discourse satisfies SENT.  For example,\n<p>\n<pre>\n  (forAll ?THING (isa ?THING Individual))\n</pre>\n<p>\nmeans that everything is an individual.  And the sentence\n<p>\n<pre>\n  (forAll ?X\n    (implies\n      (isa ?X Cat)\n      (eatsWillingly ?X Grass-Plant)))\n</pre>\n<p>\nmeans that all cats eat grass.\n<p>\nA more precise definition of forAll is as follows.  Any occurence of VAR that is free in SENT is bound in (forAll VAR SENT).  If VAR is the only variable free in SENT, then (forAll VAR SENT) is a closed sentence that is true if and only if every thing that meets all of the argument-type constraints (see ArgTypePredicate) to which the position(s) in SENT occupied by VAR is (are) subject to satisfies SENT. If the variable VAR does _not_ occur free in SENT, then (forAll VAR SENT) is equivalent to SENT (and the 'forAll' is said to be \"vacuous\").  If variables other than VAR occur free in SENT, then (forAll VAR SENT) is an open sentence in which those other variables are still free.\n<p>\nNote that, for the sake of convenience and readability, universally quantified assertions (i.e. \"rules\") in the Cyc Knowledge Base appear in the KB browser -- and may be asserted to the KB -- without (any of) their initial 'forAll's.  Such assertions are considered to be \"implicitly quantified\": they are interpreted by the system just as if their initial quantifiers were explicitly present.  Thus the above sentence about cats would actually appear in the KB as:\n<p>\n<pre>\n  (implies\n    (isa ?X Cat)\n    (eatsWillingly ?X Grass-Plant)) .\n</pre>\n<p>\nNote also that certain RuleMacroPredicates (e.g. those with 'All' in their names) can be used to abbreviate universally quantified sentences.  Thus the same statement about cats can be even more tersely expressed with the atomic sentence\n<p>\n<pre>\n  (relationAllInstance eatsWillingly Cat Grass-Plant) .\n</pre>\n<p>\nCf. the existential quantifier thereExists.", 'UniversalVocabularyMt', vStrDef).
 7727exactlyAssertedEL_next(comment, followingValue, "An instance of both OrderingPredicate and ComparisonPredicate (qq.v.), and a specialization of both colinearQuantities and lessThan (qq.v.).  followingValue is simply the restriction of the very general lessThan relation to colinear Quantity[ies] (q.v.).  <code>(followingValue LO-QUANT HI-QUANT)</code> means that <code>LO-QUANT</code> and <code>HI-QUANT</code> are colinear quantities such that <code>HI-QUANT</code> is a higher or greater value than <code>LO-QUANT</code>.  It follows that there is some (unspecified) linear ordering (see TotallyOrderedQuantityType) to which both <code>LO-QUANT</code> and <code>HI-QUANT</code> belong.\n<p>\nNote that the above sentence would typically be asserted only if one or both of <code>LO-QUANT</code> and <code>HI-QUANT</code> are instances of GenericQuantity (or the more general NonNumericScalarQuantity), and -- as is usually the case -- they are not grounded in numerically-quantifiable units of measure (see NoteAboutGivingGenericValueFunctionsNumericValues).  If <code>LO-QUANT</code> and <code>HI-QUANT</code> <i>do</i> have numerical grounding, a followingValue assertion is unnecessary since numericallyEquals, greaterThanOrEqualTo, and greaterThan are automatically computable using arithmetic relations holding between the respective minimums and maximums (see minQuantValue and maxQuantValue) of <code>LO-QUANT</code> and <code>HI-QUANT</code>.  For example, one might well use followingValue to state that (HighAmountFn Glamour) is more glamorous than (LowAmountFn Glamour); but it is unnecessary to make a followingValue assertion about (MilesPerHour 5) and (MilesPerHour 25 35), since greaterThan is automatically computable in that case.\n<p>\nSee also GenericValueFunction and followingValueOnScale.", 'UniversalVocabularyMt', vStrDef).
 7728exactlyAssertedEL_next(comment, fanOutArg, "<code>(fanOutArg PRED N)</code> means that transitively-related assertions using <code>PRED</code> usually \"fan out\" in the direction of argument position <code>N</code>.  For example, (fanOutArg geographicalSubRegions 2) means that usually a geographical region has more direct sub-regions than super-regions, so for any region <code>REG</code> there will likely be more assertions of the form <code>(geographicalSubRegions REG SUB)</code> than there are assertions of the form <code>(geographicalSubRegions SUPER REG)</code>.", 'UniversalVocabularyMt', vStrDef).
 7729exactlyAssertedEL_next(comment, extentCardinality, "<code>(extentCardinality SETORCOL N)</code> means that there are <code>N</code> terms in the currently represented extent of SetOrCollection <code>SETORCOL</code>.  See also cardinality.", 'UniversalVocabularyMt', vStrMon).
 7730exactlyAssertedEL_next(comment, extConceptOverlapsColAndReln, "(extConceptOverlapsColAndReln COL RELN SOURCE STRING) means\nthat the external structured data source SOURCE variously uses the term\nnamed by STRING as a value that semantically maps to the Cyc Collection\nCOL, and as a slot that maps to the Cyc BinaryPredicate RELN.", 'UniversalVocabularyMt', vStrMon).
 7731exactlyAssertedEL_next(comment, expresses, "A MetaLanguagePredicate (q.v.) and a specialization of means (q.v.) that relates a CycL sentence to the Proposition (if any) it expresses with respect to the intended model of the CycL language.  <code>(expresses SENTENCE PROPOSITION)</code> means that <code>SENTENCE</code> expresses, or has as its <i>intensional</i> meaning, <code>PROPOSITION</code>.\nIn order to express a proposition (see CycLPropositionalSentence), a CycL sentence must at the very least be closed and obey the arity of its main operator.\n<p>\nFor example, the sentence\n<pre>\n  (likesAsFriend Muffet Murray)\n</pre>\nexpresses the proposition that Muffet likes Murray, and we can represent that fact as follows:\n<pre>\n  (expresses\n    (Quote (likesAsFriend Muffet Murray))\n    (ThatFn (likesAsFriend Muffet Murray)))\n</pre>\nNow the above sentence is of course nearly trivial, given the intimate connection that exists between the function ThatFn and the expresses relation.  But, as we shall see, not all <code>expresses</code> sentences are trivial.\n<p>\nAs the example illustrates, the first argument-term in an <code>expresses</code> statement might consist of a particular CycL sentence wrapped with <code>Quote</code>.  But note that this need not be the case.  Suppose the above <code>likesAsFriend</code> sentence happened to be the first CycL assertion made by Muffet.  We might then reify a constant named <i>MuffetsFirstCycLAssertion</i> to denote that sentence.  Then we could say:\n<pre>\n  (expresses\n    MuffetsFirstCycLAssertion\n    (ThatFn (likesAsFriend Muffet Murray)))\n</pre> \nAs the example also illustrates, the second argument-term in an <code>expresses</code> statement might consist of a non-atomic term formed by applying the functor <code>ThatFn</code> to a particular CycL sentence.  But this also need not be the case.  Suppose the proposition that Muffet likes Murray happened to be Murray's favorite proposition.  We might then reify a constant named <i>MurraysFavoriteProposition</i> to denote that proposition.  Then we could say:\n<pre>\n  (expresses\n    MuffetsFirstCycLAssertion\n    MurraysFavoriteProposition)\n</pre> \nSee also denotes.", 'UniversalVocabularyMt', vStrMon).
 7732exactlyAssertedEL_next(comment, expansionDefn, "(expansionDefn <Relation> <Symbol>) denotes that during canonicalization\nthe subl function definition of <Symbol> is used to transform an EL expression\n(<Relation> . <args>) into the appropriate HL formula.", 'UniversalVocabularyMt', vStrDef).
 7733exactlyAssertedEL_next(comment, expansion, "Some relations (namely, instances of MacroRelation (q.v.)) can be defined in terms of more basic or primitive constructs. <code>(expansion RELATION FORMULA)</code> associates <code>RELATION</code> with the <code>FORMULA</code> that defines it. The arg2 is allowed to reference generic-argument keywords, such as :ARG1 :ARG2 which represent respectively the arg1 and the arg2 within uses of <code>RELATION</code>.  For example, <code>(expansion genls (implies (isa ?object :ARG1) (isa ?object :ARG2)))</code> indicates that the gaf <code>(genls Poodle Dog)</code> is defined as <code>(implies (isa ?object Poodle) (isa ?object Dog)))</code>. Importantly, the expansion-formula arg2 must be necessary and sufficient; it denotes the definition of the uses of relation arg1; there can be only one expansion for any relation.  Furthermore, no two relations can share a common expansion; thus, there can be only one possible contraction from a formula that corresponds to an expansion into a compact form that references expandable relations.  For example, <code>(implies (isa ?object Poodle) (isa ?object Dog)))</code> has the unambiguous contraction of <code>(genls Poodle Dog)</code>. The expansion arg2 can (and should when possible) make use of relations that have expansions.  Note that the example above references implies which would itself have the expansion <code>(or (not :ARG1) :ARG2)</code>.  Thus, the full expansion of a relation can involve recursive expansions.  For example, the full expansion of genls would be <code>(or (isa ?object :ARG1) (not (isa ?object :ARG2))))</code>.  No relation may reference itself (either directly or indirectly via recursion) in its expansion (or in its full recursive expansion).  See ELRelation, TermMacroFunction, expansionAxiom.", 'UniversalVocabularyMt', vStrDef).
 7734exactlyAssertedEL_next(comment, exceptWhen, "A binary ExceptionPredicate that relates a general CycLAssertion to a condition (specified by a CycLSentence-Assertible) under which the assertion fails to hold, and thus under which the assertion should not be used as justification for other inferences.  <code>(exceptWhen EXCEPTION ASSERTION)</code> means that <code>ASSERTION</code> fails to hold in the case of <code>EXCEPTION</code>.  A default assumption is that <code>ASSERTION</code> <i>does</i> hold for all cases other than those covered by <code>EXCEPTION</code> (or by any other exception assertions there might be on <code>ASSERTION</code>).  For example, \n<pre>\n  (exceptWhen\n    (spatiallySubsumes NorthPoleOfEarth ?THING)\n    (implies \n      (isa ?THING GeographicalThing) \n      (thereExists ?OTHER \n        (northOf ?OTHER ?THING)))\n</pre>\t\nmeans that every geographical thing has something to the north of it, except when the former is spatially subsumed by the North Pole.  \n<p>\nNormally, as in the foregoing example, the <code>ASSERTION</code> is an (implicitly) universally quantified sentence, and the <code>EXCEPTION</code>, in effect, places a restriction on the range of values (for the universally quantified variables in <code>ASSERTION)</code> for which <code>ASSERTION</code> is true.  Since implicit universal quantification is always interpreted as having the widest possible scope, in the above example the occurrence of the variable <code>?THING</code> in the exception-giving sentence is interpreted as if it were bound by the same wide-scope universal quantifer that binds the two occurrences of <code>?THING</code> in the implies rule.\n<p>\nA common special case of exceptWhen is handled by exceptFor (q.v.).  \n<p>\nNote that assertions made at the EL level with exceptWhen are canonicalized into statements that do not contain exceptWhen, but instead contain the predicate abnormal (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7735exactlyAssertedEL_next(comment, exceptMt, "(exceptMt MT) means that (except ASSERTION) is true for all ASSERTIONs asserted in MT. In other words, in the current microtheory ASSERTION is not known to be true.  If ASSERTION is a rule, it will not fire.", 'UniversalVocabularyMt', vStrMon).
 7736exactlyAssertedEL_next(comment, exceptFor, "A binary ExceptionPredicate that relates a general CycLAssertion to a thing (specified by a CycLReifiableDenotationalTerm) for which the assertion fails to hold, and thus under which the assertion should not be used as justification for other inferences.  <code>(exceptFor TERM ASSERTION)</code> means that <code>ASSERTION</code> fails to hold for the denotatum of <code>TERM</code>.  A default assumption is that <code>ASSERTION</code> <i>does</i> hold for everything other than the denotatum of <code>TERM</code> (or any other known exceptions there might be on <code>ASSERTION</code>).  For example,\n<pre>\n     (exceptFor\n      Taiwan-RepublicOfChina\n      (implies\n        (isa ?X ChineseProvince)\n        (geopoliticalSubdivision China-PeoplesRepublic ?X)))\n</pre>\nmeans that Taiwan-RepublicOfChina is an exception to the rule that every Chinese province is a geo-political subdivision of the People's Republic of China.\n<p>\nexceptFor is a special case of exceptWhen (q.v.), and is only applicable when <code>ASSERTION</code> has exactly one (implicitly) universally quantified variable.  <code>(exceptFor TERM ASSERTION)</code> prevents <code>TERM</code> from binding to that variable, thereby blocking any conclusions about the denotatum of <code>TERM</code> that Cyc might otherwise draw from <code>ASSERTION</code>.\n<p>\nNote that assertions made at the EL level with exceptFor are canonicalized into statements that do not contain exceptFor, but instead contain the predicate abnormal (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7737exactlyAssertedEL_next(comment, except, "(except ASSERTION) means that there is an exception to ASSERTION in the current microtheory such that ASSERTION is not known to be true.  If ASSERTION is a rule, it will not fire.", 'UniversalVocabularyMt', vStrMon).
 7738exactlyAssertedEL_next(comment, exampleAssertions, "(exampleAssertions TERM ASSERTION) means that the CycLAssertion ASSERTION provides a good example of how to use the CycLReifiableDenotationalTerm TERM.", 'UniversalVocabularyMt', vStrDef).
 7739exactlyAssertedEL_next(comment, exactlyAssertedEL_next, "A KBDependentRelation (q.v.) and specialization of knownSentence (q.v.) that is used to state that a given CycLSentence-Assertible has been asserted in the KB (in some accessible Microtheory). More exactly, (exactlyAssertedEL_next SENT) is true in microtheory MT precisely when SENT canonicalizes without commutative handling of the sentence args into a set of clauses of the same form as the canonicalized form of some assertion in a microtheory accessible to MT. (The predicate is thus true both of assertions entered into the KB by hand and assertions deduced by Cyc from forward rules.)\n<p>\nThis predicate enables Cyc to select a subset of information when answering queries, filtering out more generic (asserted-without-commutative-canonicalization) information. Thus, for example, the query:\n<p>\n(knownSentence (bordersOn CentralUSATimeZone EasternUSATimeZone))\n<p>\nwill return True (in appropriate microtheories), whereas:\n<p>\n(exactlyAssertedEL_next (bordersOn CentralUSATimeZone EasternUSATimeZone))\n<p>\nwill not.", 'UniversalVocabularyMt', vStrMon).
 7740exactlyAssertedEL_next(comment, evaluationResultQuotedIsa, "A binary MetaRelation that holds between relations and collections. evaluationResultQuotedIsa is primarily used to indicate that any value returned by a given evaluatable function is a quoted instance of a given collection. Where FUNC is a Function-Denotational, (evaluationResultQuotedIsa FUNC COL) means that FUNC returns a quoted instance of COL for any sequence of arguments for which FUNC is defined. That is, (quotedIsa (FUNC ARG1 ... ARGn) COL) holds for any sequence <ARG1, ..., ARGN> for which FUNC has a value. For example, '(evaluationResultQuotedIsa SubstringFn SubLString)' holds, and it entails (e.g.) '(quotedIsa (SubstringFn \"ABC\" 1 2) SubLString)'.", 'UniversalVocabularyMt', vStrMon).
 7741exactlyAssertedEL_next(comment, evaluationDefn, "A CycInferenceDescriptorPredicate and InferenceRelatedBookkeepingPredicate that is used to relate an Cyc-evaluatable function or predicate to the name of the piece of code that is used to evaluate it.  (evaluationDefn RELN NAME) means that the SubLSymbol NAME is the name of a piece of Heuristic Level (SubL) code in the Cyc system that is used to compute the value of closed CycL formulas built from (the CycL name of) the EvaluatableRelation RELN.  For example, the sentence '(evaluationDefn MinusFn CYC-MINUS)' is asserted in the Knowledge Base.'", 'UniversalVocabularyMt', vStrDef).
 7742exactlyAssertedEL_next(comment, evaluateImmediately, "(evaluateImmediately FUNCTION) means that the canonicalizer will translate each non-atomic term (see the collection CycLNonAtomicTerm) whose initial (or \"0th\" argument-place) term denotes FUNCTION into the value to which the non-atomic term evaluates.  For example, if (evaluateImmediately PlusFn) held, then the non-atomic term `(PlusFn 2 3 4)' would canonicalize as `9'.  Note that a non-atomic term containing a nested non-atomic term whose initial term denotes another instance of EvaluatableFunction (call that instance OTHER-FUNCTION) will not canonicalize in this way, unless (evaluateImmediately OTHER-FUNCTION) is also true.  For example, `(PlusFn 2 (DifferenceFn 3 4))' would not canonicalize as `1' unless    \n(evaluateImmediately DifferenceFn) were also true.", 'UniversalVocabularyMt', vStrDef).
 7743exactlyAssertedEL_next(comment, evaluateAtEL, "(evaluateAtEL FUNCTION) means that the canonicalizer will translate each non-atomic term (see the collection CycLNonAtomicTerm) whose  initial (or \"0th\" argument-place) term denotes FUNCTION into the value to which the non-atomic term evaluates.  For example, if (evaluateAtEL PlusFn) holds in  a Microtheory MT, then the non-atomic term `(PlusFn 2 3 4)' will canonicalize as `9' in that MT.  Note that a non-atomic term containing a nested non-atomic term whose initial term denotes another instance of EvaluatableFunction (call that instance OTHER-FUNCTION) will not canonicalize in this way, unless (evaluateAtEL OTHER-FUNCTION) is also true in MT.  For example, `(PlusFn 2 (DifferenceFn 3 4))' will not canonicalize as `1' in MT unless    \n(evaluateAtEL DifferenceFn) is also true in MT.", 'UniversalVocabularyMt', vStrDef).
 7744exactlyAssertedEL_next(comment, evaluate, "A binary MetaLanguagePredicate that relates a thing to a thing that is known to denote it.  <code>(evaluate THING TERM)</code> means that <code>TERM</code> evalutes to <code>THING</code>: the Cyc system \"knows\" that <code>TERM</code> denotes <code>THING</code>.\n<p>\nNote that evaluate is notAssertible (q.v.).  Its most common uses are in rules or queries, with its first argument-place filled (syntactically speaking) with a variable.  In a query, evaluate is typically used to establish a binding between such a variable and an evaluatable expression.  If VAR is a variable, a literal of the form <code>(evaluate VAR TERM)</code> is satisfied by an HL module that evaluates <code>TERM</code> and binds <code>VAR</code> to the result.  For example, the literal '<code>(evaluate ?SUM (PlusFn 1 2))</code>' would bind '<code>?SUM</code>' to 3.  If evaluate's arg1 position is filled instead with a closed expression, then the HL module checks to see if the arg2 term evaluates to the denotatum of that arg1 expression.  For example, if asked the sentence '<code>(evaluate 3 (PlusFn 1 2))</code>' the system will return 'True'.", 'UniversalVocabularyMt', vStrDef).
 7745exactlyAssertedEL_next(comment, equiv, "A LogicalConnective that represents bi-directional implication in CycL.  It takes two arguments, each of which must be an instance of ELSentence-Assertible. (equiv FORMULA-1 FORMULA-2) means that FORMULA-1 is true precisely when FORMULA-2 is true; in other words, FORMULA-1 is true if and only if FORMULA-2 is true.  (An EL equiv formula is translated during canonicalization into an equivalent, less compact, conjunction of implies formulas.) See also the predicate sentenceEquiv.", 'UniversalVocabularyMt', vStrDef).
 7746exactlyAssertedEL_next(comment, equalSymbols, "A binary MetaPredicate and a specialization of equals, both of whose arguments are quotedArguments (q.v.), that can be used to make identity assertions about symbols.  Stated loosely,  <code>(equalSymbols X Y)</code> means that <code>X</code> and <code>Y</code> are one and the same symbol.  Given that the arguments are \"quoted\", however, it is more accurate to say: A closed atomic formula consisting of the expression <code>equalSymbols</code> followed by CycL expressions <code>A</code> and <code>B</code> (all enclosed within a pair of parentheses) is true if and only if <code>A</code> and <code>B</code> are (two occurrences of) the same expression.\n<p>\nNote that this is stronger than merely saying that <code>A</code> and <code>B</code> denote the same thing.  As an example (using English expressions for convenience), the name 'Bertrand Russell' and the description 'the author of \"On Denoting\"' are two different expressions, even though they both denote the same person.  Two symbols can even share the same intensional meaning and still be different symbols; e.g. 'bachelor' and 'unmarried male'.  The relation equalSymbols <i>does</i> hold, however, between 'bachelor' and 'bachelor' (at least if we pretend that 'bachelor' is a CycL expression), as it does between the CycL constant <code>BertrandRussell</code> and the CycL constant <code>BertrandRussell</code>.\n<p>\nSee also differentSymbols.", 'UniversalVocabularyMt', vStrDef).
 7747exactlyAssertedEL_next(comment, equals, "The binary identity relation.  <code>(equals THING1 THING2)</code> means that <code>THING1</code> and <code>THING2</code> are \"numerically\" (as opposed to \"qualitatively\") identical, i.e. they are one and the same thing.  A sentence of the above form is true if and only if the terms occupying the two argument-places of 'equals' denote the same thing.", 'UniversalVocabularyMt', vStrDef).
 7748exactlyAssertedEL_next(comment, ephemeralTerm, "(ephemeralTerm TERM) states that TERM is a term that only has meaning in this particular copy of the knowledge base.  A such, it can be viewed as an ephemeral concept which could likely be forgotten at some future point in time, perhaps by an explicit 'forgetting' process.  See also termDependsOn.", 'UniversalVocabularyMt', vStrMon).
 7749exactlyAssertedEL_next(comment, elInverse, "A binary RuleMacroPredicate and a specialization of genlInverse that relates a binary EL-only (see ELRelation-OneWay) predicate with its non-EL-only \"inverse correlate\".   (elInverse PRED EL-PRED) means that whenever a sentence of the form (EL-PRED ARG1 ARG2) is used to make an assertion, the CycCanonicalizer \"transforms\" it into the logically equivalent form (PRED ARG2 ARG1), and the latter is what actually gets stored in the Knowledge Base.\n<p>\nFor example, (genlInverse genls specs) entails that if I assert the sentence '(specs Animal Cat)', what gets stored in the KB is the sentence '(genls Cat Animal)'.", 'UniversalVocabularyMt', vStrDef).
 7750exactlyAssertedEL_next(comment, elementOf, "A very general binary predicate that relates a thing to any set or collection (see SetOrCollection) that it is a member or element of. <code>(elementOf THING SETORCOL)</code> means that <code>THING</code> is an element of <code>SETORCOL</code>.  \n<p>\nelementOf is a more general relation than isa.  Whereas isa is used exclusively to talk about membership in Collections,  elementOf can also be used to talk about membership in mathematical sets (see Set-Mathematical).", 'UniversalVocabularyMt', vStrDef).
 7751exactlyAssertedEL_next(comment, distributesOutOfArg, "(distributesOutOfArg <reln> <pred> <n>) is a directive to the canonicalizer that relation <reln> distrbutes out of a predicate <pred> when it appears as the top-most relation in the predicate's arg <n>.  Specifically, it denotes (distributesOutOfArg <reln> <pred> <n>) denotes that the canonicalizer will translate\n<p>\n(<pred> <arg-1> ... <arg-n-1> (<reln> <arg-n1> <arg-n2> ... <arg-nm>) <arg-n+1> ..)\n<p>\ninto\n<p>\n(<reln> (<pred> <arg-1> ... <arg-n-1> <arg-n1> <arg-n+1> ...)\n(<pred> <arg-1> ... <arg-n-1> <arg-n2> <arg-n+1> ...)\n...\n(<pred> <arg-1> ... <arg-n-1> <arg-nm> <arg-n+1> ...))", 'UniversalVocabularyMt', vStrDef).
 7752exactlyAssertedEL_next(comment, disjointWith, "A TaxonomicSlot predicate that relates Collections  (q.v.) that have no instances in common. <code>(disjointWith COL1 COL2)</code> means that <code>COL1</code> is disjoint with <code>COL2</code>: nothing is an instance of both. That is, there is no <code>THING</code> such that both <code>(isa THING COL1)</code> and <code>(isa THING COL2)</code> hold. For example, <code>(disjointWith Herbivore Carnivore)</code> holds because no animal is both a herbivore and a carnivore. Note that disjointWith is <b>not</b> irreflexive (see IrreflexiveBinaryPredicate): it is possible for a collection to be disjoint with itself, though only if it is empty (i.e. has no instances). Thus, for example, <code>(disjointWith Nothing Nothing)</code> holds.  Cf. intersectsWith.\n<p>\nAlso note that it is quite possible for two second (or higher) order collections to be disjoint even if an instance of one collection and an instance of the other collection themselves share instances.  Consider, for example, the disjoint collections SpatialThingTypeByShape and SpatialThingTypeByDimensionality.  RoundObject is an instance of the first and ThreeDimensionalThing is an instance of the second; and any solid spherical object is an instance of both of these latter collections.", 'UniversalVocabularyMt', vStrDef).
 7753exactlyAssertedEL_next(comment, differentSymbols, "This variable-arity predicate (see VariableArityRelation), all of whose argument-places are quotedArguments (q.v.), is used to make non-identity statements about two or more symbols. Stated loosely, (differentSymbols X1 X2 ... Xn) means that each of the Xi is a symbol that is different from all of the others.  Given that the arguments are \"quoted\", however, it is more accurate to say: A ground atomic formula (or \"GAF\"; see CycLClosedAtomicSentence) consisting of the expression `differentSymbols' followed by the CycL expressions E1, ..., En (all enclosed within a pair of parentheses) is true if and only if each Ei is a different expression from all of the others.  Note that two symbols can denote the same thing (in ordinary circumstances) and still be different symbols.  As an example (using English expressions for convenience), the proper name `Bertrand Russell' and the descriptive phrase `the author of \"On Denoting\"' are two different expressions, even though they both denote the same person. Two symbols can even share the same intensional meaning and yet be different symbols; e.g. `bachelor' and `unmarried man'.  The sentence `(differentSymbols BertrandRussell BertrandRussell)', on the other hand, is false.  See also equalSymbols and different.", 'UniversalVocabularyMt', vStrDef).
 7754exactlyAssertedEL_next(comment, different, "A variable-arity predicate (see VariableArityRelation) that is used to state the non-identity of two or more things. <code>(different THING1..THINGn)</code> means that for any <code>THING</code>i and <code>THING</code>j (where 0 <= i <= n, 0 <= j <= n, and i =/ j), <code>THING</code>i is not identical with <code>THING</code>j.  That is, each of <code>THING</code>1, ..., <code>THING</code>n is distinct from all of the others.  Cf. equals.", 'UniversalVocabularyMt', vStrDef).
 7755exactlyAssertedEL_next(comment, denotes, "A MetaLanguagePredicate (q.v.) that relates CycLDenotationalTerm to their denotata: the things in the intended model of the CycL language that those terms denote or stand for.  <code>(denotes TERM THING)</code> means that <code>TERM</code> denotes <code>THING</code>.  <code>TERM</code> will often be explicitly quoted, by being wrapped in the syncategorematic quotation symbol 'Quote'.  For example, the true sentence '(denotes (Quote Plato) Plato)' means that the CycL term 'Plato' denotes the person Plato.  (Thus denotes's first argument-place is <i>not</i> \"implicitly quoted\"; cf. quotedArgument).\n<p>\nBut note that the first argument of denotes might <i>not</i> be quoted at all.  Suppose (e.g.) that the term 'Plato' were the CycL constant most beloved of Cyclists, and that a new constant 'CyclistsFavoriteConstant' were reified and defined so as to reflect this fact.  Then 'CyclistsFavoriteConstant' would refer to the CycL constant 'Plato', which in turn denotes the man Plato; and so the sentence '(denotes CyclistsFavoriteConstant Plato)' -- which involves no quotation -- would be true.\n<p>\nNote also that not all CycL terms denote, not even all CycLClosedDenotationalTerms (q.v.).  For example, the term '(BorderBetweenFn Canada Mexico)' fails to denote anything (except perhaps in certain counterfactual contexts).\n<p>\nNote finally that the sentence '(denotes Plato Plato)' is of course <i>not</i> true, as it means that the man Plato is a CycL term that denotes the man Plato, which is a patent falsehood since no man is a CycL term and no man denotes anything.\n<p>\nSee also means, expresses, hasDenotatum, quotedIsa, EscapeQuote, and the shared NoteAboutQuotingInCycL.", 'UniversalVocabularyMt', vStrMon).
 7756exactlyAssertedEL_next(comment, defnSufficient, "A CycInferenceDescriptorPredicate.  (defnSufficient COL TEST) means that TEST is the name of a piece of code in the SubL implementation of Cyc that specifies, and tests for, a sufficient condition for a CycL term's denoting an instance of (see isa) the collection COL.  If TEST returns `T' (for `True') when applied to a particular term, then that term's denotatum is considered to be an instance of COL.  Note that TEST isn't necessarily a necessary test for membership in COL; that is, not all instances of COL must pass the test, unless TEST is also a defnNecessary for COL.  See the related predicates defnNecessary and defnIff.", 'UniversalVocabularyMt', vStrDef).
 7757exactlyAssertedEL_next(comment, defnNecessary, "A CycInferenceDescriptorPredicate.  \n(defnNecessary COL TEST) means that TEST is the name of a piece \nof code in the SubL implementation of Cyc that specifies, and tests \nfor, a necessary condition for a CycL term's denoting an instance of \n(see isa) the collection COL.  Only if TEST returns `T' (for \n`True') when applied to a particular term can that term's \ndenotatum be considered an instance of COL; all terms that denote \ninstances of COL must fulfill TEST's requirements, although there \nmay be additional requirements for denoting an instance of COL as \nwell.  See also defnSufficient and defnIff.", 'UniversalVocabularyMt', vStrDef).
 7758exactlyAssertedEL_next(comment, defnIff, "A CycInferenceDescriptorPredicate.  (defnIff COL TEST) means \nthat TEST is the name of a piece of code in the SubL implementation \nof Cyc that specifies, and tests for, a necessary and sufficient \ncondition for a CycL term's denoting an instance of (see isa) the \ncollection COL.  If and only if TEST returns `T' (for `True') when \napplied to a particular term can that term's denotatum be considered \nan instance of COL; all and only terms that denote instances of COL \nmust fulfill TEST's requirements.  See also defnNecessary and \ndefnSufficient.", 'UniversalVocabularyMt', vStrDef).
 7759exactlyAssertedEL_next(comment, definingMt, "(definingMt TERM MT) states that TERM only begins to have semantic meaning in microtheory MT. In microtheories in which MT is not  accessible, TERM is undefined. Additionally,  (termDependsOn TERM MT).", 'UniversalVocabularyMt', vStrDef).
 7760exactlyAssertedEL_next(comment, defaultReformulatorModePrecedence, "(defaultReformulatorModePrecedence PRIMARY-MODE\nSECONDARY-MODE TERTIARY-MODE ...), asserted in the microtheory MT,\nmeans that in MT or a specMt thereof (unless overridden),\nthe CycLReformulator will use PRIMARY-MODE as its primary mode,\nSECONDARY-MODE as its secondary mode, etc.  This helps the\nreformulator establish precedence of CycLReformulatorDirectives.\nDo not specify both tersify and verbosify.", 'UniversalVocabularyMt', vStrMon).
 7761exactlyAssertedEL_next(comment, defaultReformulationDirectionInModeForPred, "If the CycLReformulator is operating in MT in the mode MODE, and it\nencounters a reformulation rule with no reformulationDirectionInMode\nmeta-assertion for MODE stated in MT or a genlMt thereof, the extent of this\npredicate will be used to determine the reformulation direction of the\nrule.", 'UniversalVocabularyMt', vStrMon).
 7762exactlyAssertedEL_next(comment, decontextualizedPredicate, "(decontextualizedPredicate PRED) states that PRED is a predicate which is context-independent.  In effect, any use of PRED can be lifted into any microtheory.  Predicates which are labelled with decontextualizedPredicate typically have an argument which either implicitly or explicitly provides the implied context.  A good example of such a predicate is ist.", 'UniversalVocabularyMt', vStrMon).
 7763exactlyAssertedEL_next(comment, decontextualizedCollection, "(decontextualizedCollection COL) states that COL is a collection in which membership is context-independent.  In effect, any instance of COL is an instance of COL in every microtheory.", 'UniversalVocabularyMt', vStrMon).
 7764exactlyAssertedEL_next(comment, cycTransformationProofRule, "(cycTransformationProofRule PROOF RULE) means that RULE is the rule used by PROOF to prove its proven query.", 'UniversalVocabularyMt', vStrMon).
 7765exactlyAssertedEL_next(comment, cycTransformationProofBindings, "(cycTransformationProofBindings TRANSFORMATION-PROOF BINDING) means that BINDING is an InferenceBinding (using the appropriate variable from the transformation rule for TRANSFORMATION-PROOF) proven by TRANSFORMATION-PROOF.", 'UniversalVocabularyMt', vStrMon).
 7766exactlyAssertedEL_next(comment, constraint, "(constraint RULE) labels a given RULE assertion as a constraint.  Constraints are typically used to verify that a given logical expectation is already true, rather than to deduce (and then add) a new formula which would satisfy the expectation.  In other words, if a rule (implies P(?X) Q(?X)) is labelled as a constraint, then when P(?X) is determined to be true, we verify that Q(?X) is already true rather than add a new argument for Q(?X) using the rule and P(?X) as justification.", 'UniversalVocabularyMt', vStrDef).
 7767exactlyAssertedEL_next(comment, constrainsArg, "A MetaRelation predicate for stating that a given meta-relation is used to put an argument-type or format constraint (see e.g. ArgConstraintPredicate) on a given argument-place of a relation. (constrainsArg METARELN N) means that METARELN is always used to put a constraint on a relation's Nth argument-place.  For example, (constrainsArg arg2Isa 2) holds.  A slight deviation from the above occurs when N is 0: we take (constrainsArg METARELN 0) to mean that METARELN is used to constrain _all_ of a relation's argument-places; see e.g. argsIsa and argsGenl.", 'UniversalVocabularyMt', vStrDef).
 7768exactlyAssertedEL_next(comment, constantName, "(constantName CONSTANT STRING) means that the SubLString STRING is the \"name\" for the CycLConstant CONSTANT.  That is, STRING is the string of characters that make up CONSTANT, minus the initial \"#\" and the following \"$\".", 'UniversalVocabularyMt', vStrMon).
 7769exactlyAssertedEL_next(comment, constantID, "A predicate which relates each Cyc constant to an internal identification number for it. This number is unique within any given image, though not necessarily across images (for that, see constantGUID). <code>(constantID CONSTANT ID)</code> states that the NonNegativeInteger <code>ID</code> is the unique internal id for the CycLConstant <code>CONSTANT</code> (in the current image). For obvious reasons, this predicate is notAssertible.", 'UniversalVocabularyMt', vStrMon).
 7770exactlyAssertedEL_next(comment, constantGUID, "A strictly functional slot used to associate CycL constants with the GUID strings they are assigned. <code>(constantGUID CONSTANT GUID-STR)</code> means that the CycLConstant <code>CONSTANT</code> is associated with the GUIDString <code>GUID-STR</code>.  The arg1 position of this predicate is \"quoted\", so, for example, (constantGUID Dog  \"bd58daa0-9c29-11b1-9dad-c379636f7270\") means that the constant \"Dog\" itself, not the collection of dogs, is associated with the GUIDString \"bd58daa0-9c29-11b1-9dad-c379636f7270\".", 'UniversalVocabularyMt', vStrMon).
 7771exactlyAssertedEL_next(comment, consistent, "A predicate which asserts of sentences that they do not contradict currently known facts. (consistent SENTENCE) means that the CycLSentence-Assertible SENTENCE is consistent with assertions known in the current context.  Consequently, (consistent SENTENCE) holds in a Microtheory MT just in case, for any assertion ASSERT that holds in MT, SENTENCE does not imply the negation of ASSERT.  Note that this predicate is notAssertible. See also inconsistentWithMt.", 'UniversalVocabularyMt', vStrDef).
 7772exactlyAssertedEL_next(comment, conceptuallyRelated, "This predicate is used to state the fact of a conceptual link between two things, where a very complex sentence would be required in order to describe the precise nature of this link explicitly.  Examples of such conceptually-linked couples include PublicTransportationDevice / PublicTransportationScheduleDocument and Dog / DogFood.  The rationale for having such a predicate as conceptuallyRelated is similar to that behind many RuleMacroPredicates (q.v.).  Having complex relationships represented -- possibly redundantly -- in a more compact fashion makes for faster retrieval. Because things can be conceptually related in many different ways, no explicit definition for this predicate is provided.  Note that conceptuallyRelated is _not_ a SymmetricBinaryPredicate (q.v.); but see conceptuallyCoRelated for a specialization of this predicate that is symmetric.", 'UniversalVocabularyMt', vStrDef).
 7773exactlyAssertedEL_next(comment, completelyEnumerableCollection, "A unary InferenceCompletenessPredicate that is a specialization of completelyDecidableCollection (qq.v.).  <code>(completelyEnumerableCollection COL)</code> means that the CycInferenceEngine can generate a list of all of (and only) the instances of <code>COL</code>.  More precisely: given a query of the form <code>(isa VAR COL)</code>, the Inference Engine can (without using transformations) return a list of terms -- bindings for the variable <code>VAR</code> -- such that every instance (and no non-instance) of the collection <code>COL</code> is denoted by some binding on the list.\n<p>\nFor example, SkolemFunction is a completely enumerable collection.  (But note that SkolemFunction does <i>not</i> satisfy the more specialized completelyAssertedCollection (q.v.), as most of its instances are only asserted to be instances of one of its specializations, such as FixedAritySkolemFunction.)\n<p>\nSee also completeExtentEnumerable, which applies to Predicates.", 'CoreCycLMt', vStrMon).
 7774exactlyAssertedEL_next(comment, completelyDecidableCollection, "A unary InferenceCompletenessPredicate (q.v.) that applies to collections.  <code>(completelyDecidableCollection COL)</code> means that the CycInferenceEngine can determine if any given thing is an instance of <code>COL</code>.  More precisely: for any given instance <code>INST</code> whatsoever (and for no non-instances) of <code>COL</code>, there is a CycL term <code>INST-TERM</code> that denotes <code>INST</code> such that (without using transformations) the Inference Engine, given a query of the form <code>(isa INST-TERM COL)</code>, will return the answer <code>True</code>.\n<p>\nFor example, the collection Integer is completely decidable. Given any integer <code>INT</code>, the Cyc query <code>(isa INT Integer)</code> -- wherein <code>INT</code> is given its standard base-10 arabic numeral representation -- will come back <code>True</code>.\n<p>\nIf <code>COL</code> is completely decidable and Cyc fails to return <code>True</code> for some query <code>(isa TERM COL)</code>, that fact consitutes a strong argument for the truth of its negation <code>(not (isa TERM COL))</code>.  But note that it is not a conclusive argument: the normally-reliable \"unique name assumption\" might fail here, and the term <code>TERM</code> could conceivably denote something that Cyc can prove to be an instance of <code>COL</code> only under some <i>other</i> CycL name it has.  For suppose Pace's favorite number happens to be 3, but nobody has told that to Cyc.  Cyc can prove the sentence <code>(isa 3 Integer)</code>; but it might nevertheless fail to prove the equally true sentence\n<pre>\n  (isa (<b>FavoriteNumberOfFn</b> Pace) Integer) .\n</pre>\nSee also the more specific predicates completelyEnumerableCollection and completelyAssertedCollection.  And see completeExtentDecidable, which applies to Predicates.", 'CoreCycLMt', vStrMon).
 7775exactlyAssertedEL_next(comment, completeExtentEnumerableViaBackchain, "A unary InferenceCompletenessPredicate and a specialization of  minimizeExtent (qq.v.) that applies to predicates whose entire extents can be enumerated by reference to the transformation rules currently asserted on it.  For example, surgicalIncisionEmployed is completeExtentEnumerableViaBackchain in the context of certain medical domain microtheories because the pair of rules on it are sufficient to completely generate its entire extent within those microtheories.", 'CoreCycLMt', vStrMon).
 7776exactlyAssertedEL_next(comment, completeExtentEnumerableForValueInArg, "A ternary InferenceCompletenessPredicate and a specialization of completeExtentDecidableForValueInArg (q.v.) that can apply to a predicate and a specified value for a specified argument-place.  <code>(completeExtentEnumerableForValueInArg PRED VALUE N)</code> means that the CycInferenceEngine can enumerate every sequence in the extent of <code>PRED</code> whose <code>N</code>th item is <code>VALUE</code>.  In practical terms this means that, if asked a query of the form <code>(PRED ... VALUE ...)</code>, where <code>VALUE</code> appears in the <code>N</code>th argument-position and all of the other positions (>= 1) are filled with variables, the Inference Engine can return an extensionally complete list of binding-sequences for those variables.  That is, for every sequence <code>SEQ</code> in <code>PRED</code>'s extension whose <code>N</code>th member is <code>VALUE</code> (and for nothing else), the returned list contains a sequence of bindings (i.e. CycL terms) whose members denote, pointwise, the members of <code>SEQ</code> excepting <code>VALUE</code>.\n<p>\nFor example, (completeExtentEnumerableForValueInArg hasMembers InternationalMonetaryFund 1) holds, as Cyc can enumerate all the members of the International Monetary Fund.\n<p>\nIf PRED's extent is completely enumerable for <code>VALUE</code> in the <code>N</code>th argument and a given sequence of bindings <<code>TERM1</code>, ..., <code>TERM(N-1)</code>, <code>TERM(N+1)</code>, ...> (whose length matches the arity of <code>PRED</code>, if fixed) is <i>not</i> returned for the above query, that fact consitutes a strong argument for the truth of the negation (not <code>(PRED TERM1 ... TERM(N-1) VALUE TERM(N+1) ...))</code>.  But note that it is not a conclusive argument: the normally-reliable \"unique name assumption\" might fail here, and a term <code>TERM</code>i could conceivably denote something that Cyc can prove a member of a sequence in the extent of <code>PRED</code> only under some <i>other</i> CycL name it has.  For suppose Pace resides in Texas, but nobody has told that to Cyc.  Cyc can return the binding 'Texas-State' for the query '(cityInState CityOfDallasTX ?X)'; but it might nevertheless fail to return the equally correct binding '(StateOfResidenceFn Pace)'.\n<p>\nSee also the specialization completeExtentAssertedForValueInArg and see completeExtentEnumerableForArg.", 'CoreCycLMt', vStrMon).
 7777exactlyAssertedEL_next(comment, completeExtentEnumerableForArg, "A binary InferenceCompletenessPredicate (q.v.) that can apply to a predicate and a specified argument-place.  (completeExtentEnumerableForArg PRED N) means that, for any given thing ARGN, the CycInferenceEngine can enumerate every sequence in the extent of PRED whose Nth item is ARGN (see relationExtension and relationHoldsAmong).  In practical terms this means that, if asked a query of the form (PRED ... ARGN ...), where all of PRED's argument-places save the Nth are filled with variables, the Inference Engine can return an extensionally complete list of binding-sequences for the other (i.e. non-Nth) arguments.  That is, for every sequence SEQ in PRED's extension whose Nth member is ARGN (and for nothing else), the returned list contains a sequence of bindings (i.e. CycL terms) whose members denote, pointwise, the members of SEQ excepting ARGN.\n<p>\nFor example, (completeExtentEnumerableForArg cityInState 1) holds: given any city, Cyc can return a list of all the states (i.e. the one state, if any) in which it is located.\n<p>\nIf PRED's extent is completely enumerable for the Nth argument and a given sequence of bindings <TERM1, ..., TERM(N-1), TERM(N+1), ...> (whose length matches the arity of PRED, if fixed) is not returned for the above query, that fact consitutes a strong argument for the truth of the negation (not (PRED TERM1 ... TERM(N-1) ARGN TERM(N+1) ...)).  But note that it is not a conclusive argument: the normally-reliable \"unique name assumption\" might fail here, and a term TERMi could conceivably denote something that Cyc can prove a member of a sequence in the extent of PRED only under some _other_ CycL name it has.  For suppose Pace resides in Texas, but nobody has told that to Cyc.  Cyc can return the binding 'Texas-State' for the query '(cityInState CityOfDallasTX ?X)'; but it might nevertheless fail to return the equally correct binding '(StateOfResidenceFn Pace)'.\n<p>\nSee also completeExtentEnumerable and completeExtentEnumerableForValueInArg).", 'CoreCycLMt', vStrMon).
 7778exactlyAssertedEL_next(comment, completeExtentEnumerableForArg, "(completeExtentEnumerableForArg PRED ARGNUM) means that when the CycInferenceEngine   is asked a query of the form (PRED ... ARG ...) where ARG is any closed term in the                  ARGNUMth position, it can completely enumerate all possible bindings for the other argument          positions.                                                                                           This means that for any arguments (PRED ... NOT-ARGi ... ARG ... NOT-ARGj) for which the             NOT-ARGs are not a member of the enumerated bindings,                                                (not (PRED ... NOT-ARGi ... ARG ... NOT-ARGj)) is true.", 'CoreCycLMt', vStrMon).
 7779exactlyAssertedEL_next(comment, completeExtentEnumerable, "A unary InferenceCompletenessPredicate and a specialization of completeExtentDecidable and minimizeExtent (qq.v.) that applies to predicates whose entire extents can be enumerated by the CycInferenceEngine.  <code>(completeExtentEnumerable PRED)</code> means that the Inference Engine can, without using transformations, generate a list of all of (and only) the sequences of things among which <code>PRED</code> holds (see relationExtension and relationHoldsAmong).\n<p>\nFor example, (completeExtentEnumerable knownSentence) holds, as the Inference Engine could, if asked, list all of the assertions in the Knowledge Base.  Conversely, although the Inference engine could correctly determine if any given CycL sentence is in the extent of knownSentence (i.e completeExtentDecidable holds of knownSentence), it could not generate a list of all CycL sentences in the extent of knownSentence.\n<p>\nThe practical import of completeExtentEnumerable can be stated more precisely as follows.  Let's say that an N-length sequence of terms \"pointwise-denotes\" an N-length sequence of things just in case each term in the former denotes the corresponding item in the latter.  Suppose <code>(completeExtentEnumerable PRED)</code> holds.  If <code>PRED</code> is a FixedArityRelation of arity N and <code>VAR1...VARN</code> are N distinct CycLVariables, then, given a query of the form <code>(PRED VAR1 ... VARN)</code>, the Inference Engine can, without the use of Transformation Modules, return a list of N-length sequences of terms -- each sequence consisting of bindings for the respective variables <code>VAR1-VARN</code> -- such that every sequence in <code>PRED</code>'s extent (and nothing else) is pointwise-denoted by some term-sequence on the list.   If <code>PRED</code> is a VariableArityRelation, it is the same, except the given query should then have the form <code>(PRED . VARS)</code>, and there might be no constant length N shared by all of the term-sequences in the returned list.\n<p>\nIf <code>PRED</code>'s extent is completely enumerable and a given term-sequence <code><TERM-1, ..., TERM-N></code> is <i>not</i> in the list returned for the above query, that fact consitutes a <i>strong argument</i> for the truth of the negation <code>(not (PRED TERM-1 ... TERM-N))</code>, assuming that it's semantically well-formed.  But note that it is <i>not a conclusive argument</i>: the normally-reliable \"unique name assumption\" might fail here, and some term <code>TERM-I</code> could conceivably denote something that Cyc can prove to be a member of something in the extent of <code>PRED</code> only under some <i>other</i> CycL name it has.  For suppose Pace was also denoted by the (imaginary) CycL term <code>ErasmusCAnderson</code>, but Cyc did not know that Pace and Erasmus C. Anderson are the same person.  Cyc will return the term-sequence <<code>Pace, GeneralCycKE</code>> for the query <code>(cyclistPrimaryProject ?X ?Y)</code>; but it might nevertheless <i>fail</i> to return the sequence <<code>ErasmusCAnderson, GeneralCycKE</code>>, even though the sentence\n<pre>\n  (cyclistPrimaryProject ErasmusCAnderson GeneralCycKE)\n</pre>\nwas in fact true.", 'CoreCycLMt', vStrMon).
 7780exactlyAssertedEL_next(comment, completeExtentDecidableForValueInArg, "(completeExtentDecidableForValueInArg PRED VALUE ARGNUM) means that when the            CycInferenceEngine                                                                                 is asked a closed query of the form (PRED ... VALUE ...) where VALUE appears in the                  ARGNUMth position, either it can prove (PRED ... VALUE ...) without transformation,                  or (not (PRED ... VALUE ...)) is true.", 'CoreCycLMt', vStrMon).
 7781exactlyAssertedEL_next(comment, completeExtentDecidable, "A unary InferenceCompletenessPredicate (q.v.) that applies to predicates.  <code>(completeExtentDecidable PRED)</code> means that the CycInferenceEngine can determine if any given sequence of things is in the extent of <code>PRED</code> (see relationExtension and relationHoldsAmong).  More precisely: for any given n-length sequence <code>SEQ</code> among which <code>PRED</code> holds (and for nothing else), there are CycL terms <code>TERM<sub>1</sub></code>, ..., <code>TERM<sub>N</sub></code> that denote the respective items in <code>SEQ</code> such that (without using transformations) the Inference Engine, given a query of the form <code>(PRED TERM<sub>1</sub> ... TERM<sub>N</sub>)</code>, will return the answer <code>True<code>.\n<p>\nFor example, <code>(completeExtentDecidable integerBetween)</code> holds, as the Inference engine can correctly determine if any given triple of integers is such that the second member is numerically between the first and third.  Conversely, the extent of likesAsFriend is not decidable, as many of the friendships in the world are beyond Cyc's ken.\n<p>\nIf <code>PRED</code>'s extent is completely decidable and there are CycL terms <code>TERM<sub>1</sub>, ..., TERM<sub>N</sub></code> such that the sentence <code>(PRED TERM<sub>1</sub> ... TERM<sub>N</sub>)</code> is semantically well-formed but <i>not</i> provable by the Inference Engine, that fact consitutes a strong argument for the truth of its negation <code>(not (PRED TERM<sub>1</sub> ... TERM<sub>1</sub>))</code>.  But note that it is not a conclusive argument: the normally-reliable \"unique name assumption\" might fail here, and some <code>TERM<sub>I</sub></code> could conceivably denote something that Cyc can prove to be a member of a sequence in the extent of <code>PRED</code> only under some <i>other</i> CycL name it has.  For suppose Pace's favorite number happens to be 3, but nobody has told that to Cyc.  Cyc can prove the sentence <code>(integerBetween 1 2 3)</code>; but it might nevertheless fail to prove the equally true sentence\n<pre>\n  (integerBetween 1 2 (FavoriteNumberOfFn Pace)) .\n</pre>\nSee also the more specific predicates completeExtentEnumerable and completeExtentAsserted.  And see completelyDecidableCollection.", 'CoreCycLMt', vStrMon).
 7782exactlyAssertedEL_next(comment, completeExtentAssertedForValueInArg, "A ternary InferenceCompletenessPredicate and a specialization of completeExtentEnumerableForValueInArg (q.v.) that can apply to a predicate and a specified value for a specified argument-place.  (completeExtentAssertedForValueInArg PRED VALUE N) means that for every sequence of arguments that PRED holds of and whose Nth member is VALUE, there is an explicit assertion to that effect in the Cyc Knowledge Base.  Thus, if asked a query of the form (PRED ... VALUE ...), where VALUE appears in the Nth argument-position and all of the other positions (>= 1) are filled with variables, the Inference Engine -- simply via lookup of assertions in the KB -- can return an extensionally complete list of binding-sequences for those variables.  That is, for every sequence SEQ in PRED's extension whose Nth member is VALUE (and for nothing else), the returned list contains a sequence of bindings (i.e. CycL terms) whose members denote, pointwise, the members of SEQ excepting VALUE.\n<p>\nFor example, (completeExtentAssertedForValueInArg hasMembers InternationalMonetaryFund 1) holds, as all the members of the International Monetary Fund are asserted to be such in the KB.\n<p>\nIf PRED's extent is completely asserted for VALUE in the Nth argument and a given sequence of bindings <TERM1, ..., TERM(N-1), TERM(N+1), ...> (whose length matches the arity of PRED, if fixed) is not returned for the above query, that fact consitutes a strong argument for the truth of the negation (not (PRED TERM1 ... TERM(N-1) VALUE TERM(N+1) ...)).  But note that it is not a conclusive argument: the normally-reliable \"unique name assumption\" might fail here, and a term TERMi could conceivably denote something that Cyc can prove a member of something in the extent of PRED only under some _other_ CycL name it has.  For suppose Pace resides in Texas, but nobody has told that to Cyc.  The KB contains the assertion '(cityInState CityOfDallasTX Texas-State)'; but it might nevertheless fail to contain the equally true sentence '(cityInState CityOfDallasTX (StateOfResidenceFn Pace))'.\n<p>\nSee also completeExtentAsserted.", 'CoreCycLMt', vStrMon).
 7783exactlyAssertedEL_next(comment, completeExtentAsserted, "A unary InferenceCompletenessPredicate and a specialization of completeExtentEnumerable (q.v.) that applies to predicates whose entire extents are explicitly asserted in the Cyc Knowledge Base.  <code>(completeExtentAsserted PRED)</code> means that, for every sequence <code><THING1,..., THING<sub>N</sub>></code> that satisfies <code>PRED</code>, <code>(PRED THING1 ... THING<sub>N</sub>)</code> is asserted in the Knowledge Base.  That is, for each such sequence, there are reified CycL terms <code>PRED-NAME</code>, <code>TERM1</code>, ..., <code>TERM<sub>N</sub></code> -- which denote <code>PRED</code>, <code>THING1</code>, ..., <code>THING<sub>N</sub></code>, respectively -- such that the sentence <code>(PRED-NAME TERM1 ... TERM<sub>N</sub>)</code> built from those terms is an assertion in the KB.\n<p>\nIf completeExtentAsserted is true of <code>PRED</code>, then the CycInferenceEngine, when asked a query of the form <code>(PRED <b>. VARS</b>)</code>, can return a complete set of bindings for the variables in <code>VARS</code> simply via a lookup of assertions in the KB.  By a \"complete set of bindings\" is meant a set of sequences of terms such that, for each sequence <code><THING1, ..., THING<sub>N</sub>></code> in the extent of <code>PRED</code>, there is a corresponding sequence of terms <code><TERM1, ..., TERM<sub>N</sub>></code> returned wherein each <code>TERM<sub>I</sub></code> denotes <code>THING<sub>I</sub></code> (for 1 <= <code>I</code> <= <code>N</code>).\n<p>\nFor example, (completeExtentAsserted hourOfDayIndex-24Hour) holds.  Thus, the sentence <code>(hourOfDayIndex-24Hour TimeOfDay-1AM 1)</code> is one of twenty-four similar ground-atomic sentences asserted in the KB.  Conversely, (completeExtentAsserted argN) does <i>not</i> hold.  Thus, while the Inference Engine could generate the set of all true <code>argN</code> based ground-atomic sentences (i.e. completeExtentEnumerable holds of argN), the members of this set are not all asserted in the KB.\n<p>\nSee also completelyAssertedCollection, which applies to collections rather than predicates.", 'CoreCycLMt', vStrMon).
 7784exactlyAssertedEL_next(comment, commutativeInArgsAndRest, "A variable-arity MetaRelation used for \nstating that a given PartiallyCommutativeRelation (q.v.) is \"commutative\" \nwith respect to two or more argument-places, including all argument-places that \ncome after the ordinally highest one that is explicitly specified.  \n(commutativeInArgsAndRest RELN ARGNUM-1 ARGNUM-2 ... ARGNUM-N) means that \nRELN is commutative in its ARGNUM-1th, ARGNUM-2th, ..., and ARGNUM-Nth \narguments-places, along with any of its argument-places whose ordinal positions \nare greater than the greatest of the ARGNUM-i.  Thus RELN admits unrestricted \npermutation among any of these arguments.  More precisely (and assuming without \nloss of generality that ARGNUM-N is the numerically greatest of the ARGNUM-i):  \n(i) if RELN is a Predicate that holds of a given argument-sequence SEQ, then \nRELN also holds of any other sequence SEQ-PERMUTE obtainable from SEQ by \npermuting some or all of SEQ's ARGNUM-1th, ARGNUM-2th, ..., ARGNUM-Nth, and \nsubsequent items (while leaving all of SEQ's other items unchanged).  \n(ii) if RELN is a Function-Denotational that associates a given \nargument-sequence SEQ with the value VALUE, then RELN also associates any \nsequence SEQ-PERMUTE (as described above) with VALUE.  For example, \n(commutativeInArgsAndRest commutativeInArgsAndRest 2) \nhas as a consequence that whenever a sentence of the form \n(commutativeInArgsAndRest RELN 2 3 5) holds, so do the corresponding \nsentences (commutativeInArgsAndRest RELN 2 5 3), \n(commutativeInArgsAndRest RELN 3 2 5), and so on.  Note that since RELN \nis an instance of PartiallyCommutativeRelation, it must have at \nleast two argument-places that are commutative with each other and at \nleast one that is _not_ commutative with any other argument-place.  See\nalso commutativeInArgs.", 'UniversalVocabularyMt', vStrDef).
 7785exactlyAssertedEL_next(comment, commutativeInArgs, "A variable-arity MetaRelation used for stating that a given PartiallyCommutativeRelation (q.v.) is \"commutative\" with respect to two or more specified argument-places.\n<p>\n<code>(commutativeInArgs RELN ARGNUM-1 ... ARGNUM-N)</code> means that  <code>RELN</code> is commutative in its <code>ARGNUM-1</code>th, ..., and <code>ARGNUM-N</code>th arguments.  Thus <code>RELN</code> admits unrestricted permutation among  these arguments.  More precisely: (i) if <code>RELN</code> is a Predicate that  holds of a given argument-sequence <code>SEQ</code>, then <code>RELN</code> also holds of any other sequence <code>SEQ-PERMUTE</code> obtainable from <code>SEQ</code> by permuting some or all of <code>SEQ</code>'s <code>ARGNUM-1</code>th, ..., and <code>ARGNUM-N</code>th items (while leaving all of <code>SEQ</code>'s other items unchanged).  (ii) if <code>RELN</code> is a Function-Denotational that associates a given argument-sequence <code>SEQ</code> with the value <code>VALUE</code>, then <code>RELN</code> also associates any sequence <code>SEQ-PERMUTE</code> (as described above) with <code>VALUE</code>.\n<p>\nFor example, <code>(commutativeInArgs formsBorderBetween 2 3)</code> has as a consequence that whenever a sentence of the form <code>(formsBorderBetween BORDER REG1 REG2)</code> holds, so does the corresponding sentence  <code>(formsBorderBetween BORDER REG2 REG1)</code>.\n<p>\nIf <code>RELN</code> is commutative in at least two argument-places it is an AtLeastPartiallyCommutativeRelation.  If <code>RELN</code> is commutative in <i>all</i> argument-places it is, more specifically, a CommutativeRelation.  If <code>RELN</code> is commutative in at least two, but <i> not all</i>,\nargument-places it is, instead, a PartiallyCommutativeRelation.\n<p>\nNote that the fact that each argument-place of a given relation commutes with some other argument-place is not sufficient for its being fully commutative.  For example, a partially-commutative quaternary relation might be such that its first and third places commute with each other and its second and fourth places commute with each other.", 'UniversalVocabularyMt', vStrDef).
 7786exactlyAssertedEL_next(comment, comment, "A DocumentationPredicate (q.v.) that is used to relate a CycLIndexedTerm (usually a CycLConstant) to a SubLString containing an English explanation of the term's meaning and use, as an aid to humans (whether Cyclists or not) browsing the Cyc Knowledge Base.  <code>(comment TERM STRING)</code> means that <code>STRING</code> is a piece of Cyc documentation that explains the meaning and use of <code>TERM</code>.  For example, the passage you are reading now is the comment for the CycL constant `comment'.  See also cyclistNotes.", 'UniversalVocabularyMt', vStrDef).
 7787exactlyAssertedEL_next(comment, collectionIsaBackchainRequired, "<code>(collectionIsaBackchainRequired COLLECTION)</code>\n<p>\nmeans that rules that conclude\n<p>\n<code>(isa <anything> COLLECTION)</code>\n<p>\nmust be used in order to prove literals of the form\n<p>\n<code>(isa <anything> COLLECTION)</code>.\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled.  See also backchainRequired for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7788exactlyAssertedEL_next(comment, collectionIsaBackchainEncouraged, "<p>\n(collectionIsaBackchainEncouraged COLLECTION)\n<p>\nmeans that rules that conclude\n<p>\n(isa <anything> COLLECTION)\n<p>\nare most likely going to have to be used in order to prove literals of the form\n<p>\n(isa <anything> COLLECTION).\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled.  Note that it will not necessarily use rules of the form\n<p>\n(isa <anything> <variable>)\n<p>\nwhere <variable> might bind to COLLECTION, and it will not necessarily use rules of the form\n<p>\n(isa <anything> SPEC),\n<p>\nwhere (genls SPEC COLLECTION).\n<p>\nSee also backchainEncouraged for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7789exactlyAssertedEL_next(comment, collectionGenlsBackchainRequired, "<code>(collectionGenlsBackchainRequired COLLECTION)</code>\n<p>\nmeans that rules that conclude\n<p>\n<code>(genls <anything> COLLECTION)</code>\n<p>\nmust be used in order to prove literals of the form\n<p>\n<code>(genls <anything> COLLECTION)</code>.\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled. See also backchainRequired for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7790exactlyAssertedEL_next(comment, collectionGenlsBackchainEncouraged, "<p>\n(collectionGenlsBackchainEncouraged COLLECTION)\n<p>\nmeans that rules that conclude\n<p>\n(genls <anything> COLLECTION)\n<p>\nare most likely going to have to be used in order to prove literals of the form\n<p>\n(genls <anything> COLLECTION).\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled.  Note that it will not necessarily use rules of the form\n<p>\n(genls <anything> <variable>)\n<p>\nwhere <variable> might bind to COLLECTION, and it will not necessarily use rules of the form\n<p>\n(genls <anything> SPEC),\n<p>\nwhere (genls SPEC COLLECTION).\n<p>\nSee also backchainEncouraged for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7791exactlyAssertedEL_next(comment, collectionExpansion, "(collectionExpansion COL FORMULA) states that membership\nof a term in the collection COL is equivalent to FORMULA involving\nthat term being true.  The meta-variable :ARG1 is used to stand for\nthe term in FORMULA, and the meta-variable :ARG2 is used to stand for\nthe collection in FORMULA.", 'UniversalVocabularyMt', vStrMon).
 7792exactlyAssertedEL_next(comment, collectionConventionMt, "(collectionConventionMt COL MT) means that assertions of the form (isa INS COL), for any INS, are by convention asserted in MT.", 'UniversalVocabularyMt', vStrMon).
 7793exactlyAssertedEL_next(comment, collectionCompletelyEnumerableViaBackchain, "A unary InferenceCompletenessPredicate.  <code>(collectionCompletelyEnumerableViaBackchain COL)</code> means that the CycInferenceEngine can generate a list of all of (and only) the instances of <code>COL</code> by appeal to isa consequent rules.  For example, in certain medical domain microtheories, MazeProcedure-SurgicalProcedure is collectionCompletelyEnumerableViaBackchain because backchaining on its single rule is sufficient to generate all the relevant instances in those microtheories.", 'CoreCycLMt', vStrMon).
 7794exactlyAssertedEL_next(comment, collectionBackchainRequired, "<code>(collectionBackchainRequired COLLECTION)</code>\n<p>\nmeans that rules that conclude\n<p>\n<code>(isa <anything> COLLECTION)</code>\n<p>\nmust be used in order to prove literals of the form\n<p>\n<code>(isa <anything> COLLECTION)</code>\n<p>\nand rules that conclude\n<p>\n<code>(genls <anything> COLLECTION)</code>\n<p>\nmust be used in order to prove literals of the form\n<p>\n<code>(genls <anything> COLLECTION)</code>.\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled.  See also backchainRequired for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7795exactlyAssertedEL_next(comment, collectionBackchainEncouraged, "<p>\n(collectionBackchainEncouraged COLLECTION)\n<p>\nmeans that rules that conclude\n<p>\n(isa <anything> COLLECTION)\n<p>\nare most likely going to have to be used in order to prove literals of the form\n<p>\n(isa <anything> COLLECTION),\n<p>\nand rules that conclude\n<p>\n(genls <anything> COLLECTION)\n<p>\nare most likely going to have to be used in order to prove literals of the form\n<p>\n(genls <anything> COLLECTION).\n<p>\nThis directs the inference engine to use such rules even if HL predicate transformation is disabled. Note that it will not necessarily use rules of the form\n<p>\n([isa|genls] <anything> <variable>)\n<p>\nwhere <variable> might bind to COLLECTION, and it will not necessarily use rules of the form\n<p>\n([isa|genls] <anything> SPEC), where (genls SPEC COLLECTION).\n<p>\nSee also backchainEncouraged for the analogue of this predicate applicable to predicates rather than collections.", 'UniversalVocabularyMt', vStrMon).
 7796exactlyAssertedEL_next(comment, coExtensional, "A TaxonomicSlotForCollections (q.v.) that holds between collections whose extents (see extent) are exactly the same. (coExtensional COL1 COL2) means that COL1 and COL2 have all their elements in common: every instance of (see isa) one is an instance of the other.  Note that since collections (see Collection), unlike mathematical sets (see Set-Mathematical), are \"intensionally defined\", two collections can be coextensional without thereby being identical (see equals).  See also \ncoextensionalSetOrCollections.", 'UniversalVocabularyMt', vStrDef).
 7797exactlyAssertedEL_next(comment, canonicalizerDirectiveForArgAndRest, "A  CanonicalizerDirectivePredicate (q.v.) used (in conjunction with a  CanonicalizerDirective) to control the behavior of the CycCanonicalizer. (canonicalizerDirectiveForArgAndRest RELN N DIRECTIVE) means that  the CycCanonicalizer obeys DIRECTIVE when canonicalizing the Nth and subsequent (i.e. (N+1)th, (N+2)th, ...) arguments of any CycLFormula  whose main (or \"0th place\") operator denotes RELN.  See the instances  of CanonicalizerDirective for more information on how particular  directives affect canonicalization.  Also see canonicalizerDirectiveForArg and canonicalizerDirectiveForAllArgs.", 'CoreCycLImplementationMt', vStrMon).
 7798exactlyAssertedEL_next(comment, canonicalizerDirectiveForArg, "A CanonicalizerDirectivePredicate  (q.v.) used (in conjunction with a CanonicalizerDirective) to control the  behavior of the CycCanonicalizer.  (canonicalizerDirectiveForArg RELN  N DIRECTIVE) means that the CycCanonicalizer obeys DIRECTIVE when  canonicalizing the Nth argument of a CycLFormula whose main (or \"0th place\") operator denotes RELN.  See the instances of CanonicalizerDirective  for more information on how particular directives affect canonicalization. Also see canonicalizerDirectiveForArgAndRest and  canonicalizerDirectiveForAllArgs.", 'CoreCycLImplementationMt', vStrMon).
 7799exactlyAssertedEL_next(comment, canonicalizerDirectiveForAllArgs, "A  CanonicalizerDirectivePredicate (q.v.) used (in conjunction with a  CanonicalizerDirective) to control the behavior of the CycCanonicalizer. (canonicalizerDirectiveForAllArgs RELN DIRECTIVE) means that the  CycCanonicalizer obeys DIRECTIVE when canonicalizing any argument of a  CycLFormula whose main (or \"0th place\") operator denotes RELN.  See the  instances of CanonicalizerDirective for more information on how particular  directives affect canonicalization.  Also see canonicalizerDirectiveForArg and canonicalizerDirectiveForArgAndRest.", 'CoreCycLImplementationMt', vStrMon).
 7800exactlyAssertedEL_next(comment, backchainRequired, "(backchainRequired PREDICATE) means that rules that conclude PREDICATE must be used in order to prove literals involving PREDICATE.  In other words, when performing inferences, all literals involving PREDICATE must be eliminated using rules since there won't be any other way to prove them.  See also backchainEncouraged, backchainDiscouraged, and backchainForbidden.", 'UniversalVocabularyMt', vStrMon).
 7801exactlyAssertedEL_next(comment, backchainForbiddenWhenUnboundInArg, "backchainForbiddenWhenUnboundInArg is a predicate that\nallows users to prevent the inference engine from backchaining on a\nliteral when one or more of its arguments are unbound. That is, if\nPRED is a Predicate, N a positive integer less than or equal to the\narity of PRED, then (backchainForbiddenWhenUnboundInArg PRED N) that\nno rules concluding to a positive literal with PREDICATE as the arg0\n(in other words, no implies assertions in which a literal with\nPREDICATE as the arg0 appears in the consequent) will be used when\nattempting to prove (non-negated) literals with PREDICATE as the arg0\n*unless* argN in the literal is fully bound. For instance, the sentence\n<pre>\n(backchainForbiddenWhenUnboundInArg interestingSentence 1)\n</pre>\nprevents the inference engine from applying any rule concluding\ninterestingSentence, such as \n<pre>\n(implies\n  (maleficiary ?PROGRAM ?AGENT) \n  (interestingSentence ?AGENT (maleficiary ?PROGRAM ?AGENT)))\n</pre>\nunless and until <code>?AGENT</code> is bound.", 'UniversalVocabularyMt', vStrMon).
 7802exactlyAssertedEL_next(comment, backchainForbidden, "backchainForbidden is a predicate that allows users to cut down on the number of rules used to prove certain literals, and thus to increase the speed of inferences that involve proving those literals.  <code>(backchainForbidden PREDICATE)</code> means that no rules containing a positive literal with <code>PREDICATE</code> as the arg0 (in other words, no implies assertions in which a literal with <code>PREDICATE</code> as the arg0 appears in the consequent) will be used when attempting to prove (non-negated) literals with <code>PREDICATE</code> as the arg0.  Asserting <code>(backchainForbidden PREDICATE)</code> is useful when all (non-negated) literals with <code>PREDICATE</code> as the arg0 are expected to be solvable by lookup of ground atomic formulas (GAF's) already in the KB, and so rules won't be needed to prove them.  However, asserting <code>(backchainForbidden PREDICATE)</code> is usually counter-productive in contexts where some literals with <code>PREDICATE</code> as the arg0 are expected to be proven via backchaining on rules containing a positive literal with <code>PREDICATE</code> as the arg0.  See also the related predicates backchainRequired, backchainEncouraged, and backchainDiscouraged.", 'UniversalVocabularyMt', vStrMon).
 7803exactlyAssertedEL_next(comment, assertionUtility, "A CycInferenceHeuristicRelevancePredicate. (assertionUtility ASSERTION NUM) states that the CycLAssertion ASSERTION should be heuristically considered of utility NUM to inferences made in the current Microtheory. NUM should be a RealNumber between 1 and -1, with 1 indicating maximum utility, -1 indicating minimum utility, and 0 being agnostic with respect to utility.  (assertionUtility ASSERTION 1) is equivalent to (highlyRelevantAssertion ASSERTION). (assertionUtility ASSERTION -1) is equivalent to (irrelevantAssertion ASSERTION).  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrMon).
 7804exactlyAssertedEL_next(comment, assertionDirection, "An AssertionDescriptorPredicate that \nis used to state that a given CycLAssertion has a certain inference \n\"direction\", which indicates something about how and when the assertion \ncan be used in inferences by the Cyc system. (assertionDirection ASSERTION DIRECTION) means that ASSERTION has DIRECTION as its CycLAssertionDirection (q.v.).  DIRECTION is normally Backward-AssertionDirection (q.v.) when \nASSERTION is a rule and Forward-AssertionDirection (q.v.) when ASSERTION is \na ground atomic formula (or \"GAF\"; see CycLClosedAtomicSentence).  Note \nthat a CycL sentence is given a direction at the time of its assertion to the \nKnowledge Base, and this fact _need_not_ in general be reflected in another, \nassertionDirection GAF's being asserted (as that would of course lead to an infinite regress).", 'UniversalVocabularyMt', vStrMon).
 7805exactlyAssertedEL_next(comment, assertedTermSentences, "(assertedTermSentences THING SENTENCE) means that SENTENCE has been asserted to the Cyc Knowledge Base (and is thus a  CycLAssertion) and that THING is mentioned in SENTENCE.  More precisely, and assuming the assertedTermSentences formula contains no free variables (and \nis thus a \"ground atomic formula\" or \"GAF\"): the CycL term immediately following the constant `assertedTermSentences' in the formula occurs in SENTENCE.  For example, (assertedTermSentences France (bordersOn France Germany)) holds.  See also knownSentence and assertedPredicateArg for related predicates about assertions; and see termFormulas for a more general predicate that does not entail that SENTENCE has been asserted.", 'UniversalVocabularyMt', vStrMon).
 7806exactlyAssertedEL_next(comment, knownSentence, "A KBDependentRelation (q.v.) and specialization of knownSentence (q.v.) that is used to state that a given CycLSentence-Assertible has been asserted in the KB (in some accessible Microtheory). More exactly, (knownSentence SENT) is true in microtheory MT precisely when SENT canonicalizes into a set of clauses of the same form as the canonicalized form of some assertion in a microtheory accessible to MT. (The predicate is thus true both of assertions entered into the KB by hand and assertions deduced by Cyc from forward rules.) For the more specific claim that SENT is asserted <b>in MT</b>, see the predicate ist-Asserted.\n<p>\nThis predicate enables Cyc to select a subset of information when answering queries, filtering out more generic (inferrable-but-not-asserted) information. Thus, for example, the query:\n<p>\n(genls Dog Thing)\n<p>\nwill return True (in appropriate microtheories), whereas:\n<p>\n(knownSentence (genls Dog Thing))\n<p>\nwill not.", 'UniversalVocabularyMt', vStrDef).
 7807exactlyAssertedEL_next(comment, assertedPredicateArg, "(assertedPredicateArg OBJ N PREDICATE) means that a ground atomic formula (or \"GAF\"; see CycLClosedAtomicSentence) whose initial (or \"0th\" argument-place) term denotes PREDICATE, and whose Nth argument-place term denotes OBJ, is asserted in the Cyc Knowledge Base. Note that this predicate is itself notAssertible (q.v.), since it must be computed from the state of the knowledge base.", 'UniversalVocabularyMt', vStrMon).
 7808exactlyAssertedEL_next(comment, arityMin, "A MetaRelation for specifying the minimum number\nof arguments a given VariableArityRelation must take if the resulting formula is to be semantically well-formed.  <code>(arityMin RELN N)</code> means that semantic well-formedness requires that <code>RELN</code> take at least <code>N</code> arguments at a time.  More precisely: a formula <code>(RELN ARG<sub>1</sub> ... ARG<sub>M</sub>)</code> is semantically well-formed only if <code>M</code> is greater than or equal to <code>N</code>.  For example, the minimum-arity of any instance of UnitOfMeasure is 1.  Note that full semantic well-formedness requires obeying argument-type constraints (see ArgTypePredicate) as well as arity constraints. For a general explanation of semantic well-formedness, see CycLExpression-Assertible.  See also arityMax and arity.", 'UniversalVocabularyMt', vStrDef).
 7809exactlyAssertedEL_next(comment, arityMax, "A MetaRelation for specifying the maximum number\nof arguments a given VariableArityRelation can take if the \nresulting formula is to be semantically well-formed.  <code>(arityMax RELN N)</code> means \nthat semantic well-formedness requires that <code>RELN</code> take at most <code>N</code> arguments at \na time.  More precisely: a formula <code>(RELN ARG<sub>1</sub> ... ARG<sub>M</sub>)</code> is semantically \nwell-formed only if <code>M</code> is less than or equal to <code>N</code>.  For example, the \nmaximum-arity of any instance of UnitOfMeasure is 2.  Note that full semantic \nwell-formedness requires obeying argument-type constraints (see \nArgTypePredicate) as well as arity constraints.  For a general explanation \nof semantic well-formedness, see CycLExpression-Assertible.  See also \narityMin and arity.", 'UniversalVocabularyMt', vStrDef).
 7810exactlyAssertedEL_next(comment, arity, "A MetaRelation used for stating that a given  relation takes a specified number of arguments.  <code>(arity RELN N)</code>  means that that semantic well-formedness requires that <code>RELN</code> take  exactly <code>N</code> arguments at a time.  That is, a formula  <code>(RELN ARG<sub>1</sub> ... ARG<sub>M</sub>)</code> is semantically well-formed only if <code>M</code> = <code>N</code>.\n<p>\nFor example, the arity of any instance of BinaryPredicate is 2.\n<p>\nNote that full semantic well-formedness requires obeying argument-type constraints (see ArgTypePredicate) as well as arity constraints.  For a general explanation of semantic well-formedness, see CycLExpression-Assertible.  See also CycLExpression-Askable.", 'UniversalVocabularyMt', vStrDef).
 7811exactlyAssertedEL_next(comment, argsQuotedIsa, "A binary ArgQuotedIsaPredicate (q.v.) that is used to put a specified quoted-isa based argument-type constraint on all of a given relation's argument-places at once. (argsQuotedIsa RELN COL) means that semantic well-formedness requires that each argument to which RELN is applied (regardless of argument-place) be a quoted instance of COL. For example, '(argsQuotedIsa and CycLSentence-Assertible)' means that the relation and must only be applied to assertible CycL sentences. argsQuotedIsa is particularly useful for constraining (any and all of) the arguments of a VariableArityRelation (the preceding example being a case in point); though argQuotedIsa may be applied to fixed-arity relations as well. For an explanation of semantic well-formedness, see CycLExpression-Assertible and its immediate specializations.", 'UniversalVocabularyMt', vStrMon).
 7812exactlyAssertedEL_next(comment, argSometimesIsa, "(argSometimesIsa RELATION POSITIVE-INTERGER-N COLLECTION) means that semantic\nwell-formedness requires that anything given as the Nth argument to RELN must be\nan instance of COL at sometime or other.  More precisely, if (argSometimesIsa RELATION POSITIVE-INTERGER-N COLLECTION) then in order to assert: (RELATION ARG-N ... OTHER-ARGS)<MT TIME PAR>, it must be the case that there exists some time interval, t, such that (isa ARG-N COLLECTION)<MT t PAR>.", 'UniversalVocabularyMt', vStrDef).
 7813exactlyAssertedEL_next(comment, argsIsa, "A binary ArgIsaPredicate (q.v.) that is used to put a specified isa based argument-type constraint on all of a given relation's argument-places at once.  (argsIsa RELN COL) means that semantic well-formedness requires that each argument to which RELN is applied (regardless of argument-place) be an instance of COL.  For example, '(argsIsa PlusFn ScalarInterval)' means that the function PlusFn must only be applied to scalar intervals.   argsIsa is particularly useful for constraining (any and all of) the arguments to a VariableArityRelation (the preceding example being a case in point); though argsIsa may be applied to fixed-arity relations as well.  For an explanation of semantic well-formedness, see CycLExpression-Assertible and its immediate specializations.  See also argsGenl.", 'UniversalVocabularyMt', vStrDef).
 7814exactlyAssertedEL_next(comment, argsGenl, "A binary ArgGenlPredicate (q.v.) that is used to put \na specified genls based argument-type constraint on all of a given relation's \nargument-places at once.  (argsGenl RELN COL) means that semantic well-formedness requires that each argument to which RELN is applied (regardless of argument-place) be an subcollection of COL.  For example, `(argsGenl PerformSimultaneouslyFn Event)' means that the function PerformSimultaneouslyFn must only be applied to types of events.  argsGenl is particularly useful for constraining (any and all of) the arguments to a VariableArityRelation (the preceding example being a case in point); though argsGenl may be applied to fixed-arity relations as well.  For an explanation of semantic well-formedness, see CycLExpression-Assertible and its immediate specializations.  See also argsIsa.", 'UniversalVocabularyMt', vStrDef).
 7815exactlyAssertedEL_next(comment, argQuotedIsa, "A ternary Predicate (argQuotedIsa RELN N COL) means that semantic well-formedness requires that the term given as the Nth argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ... ARGN ...) is semantically well-formed only if (quotedIsa ARGN COL) holds. For example, (argQuotedIsa examplePredSentences 1 CycLSentence) holds. ", 'UniversalVocabularyMt', vStrMon).
 7816exactlyAssertedEL_next(comment, argIsa, "A ternary ArgIsaPredicate (q.v.).  <code>(argIsa RELN N COL)</code> means that semantic well-formedness requires that anything given as the <code>N</code>th argument to <code>RELN</code> must be an instance of <code>COL</code>.  That is, <code>(RELN ... ARG<sub>N</sub> ...)</code> is semantically well-formed only if <code>(isa ARG<sub>N</sub> COL)</code> holds.  For example, <code>(argIsa mother 1 Animal)</code> and <code>(argIsa argIsa 3 Collection)</code> both hold.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  For similar but less flexible binary predicates, see arg1Isa et al. See also argGenl.", 'UniversalVocabularyMt', vStrMon).
 7817exactlyAssertedEL_next(comment, argAndRestQuotedIsa, "A ternary ArgQuotedIsaPredicate (q.v.) used to place a specified quoted isa based argument-type constraint on a given VariableArityRelation (q.v.) with respect to any of its argument-places whose ordinal position is greater than or equal to a specified number. (argAndRestQuotedIsa RELN N COL) means that, as a necessary condition for semantic well-formedness, anything given as the Nth or greater argument to RELN must be a quoted instance of COL. Thus a closed formula (RELN ARG1..ARG(N)..ARG(N+1)..) is well-formed only if each of ARG(N)..ARG(N+1).. is a quoted instance of COL. See also argsQuotedIsa.", 'BookkeepingMt', vStrMon).
 7818exactlyAssertedEL_next(comment, argAndRestIsa, "A ternary ArgIsaPredicate (q.v.) used to \nplace a specified isa based argument-type constraint on a given \nVariableArityRelation (q.v.) with respect to any of its argument-places \nwhose ordinal position is greater than or equal to a specified number.\n(argAndRestIsa RELN N COL) means that, as a necessary condition for \nsemantic well-formedness, anything given as the Nth or greater argument \nto RELN must be an instance of COL.  Thus a closed formula\n(RELN ARG1..ARG(N)..ARG(N+1)..) is well-formed only if each of ARG(N)..ARG(N+1).. is an instance of COL.  See also argsIsa and argAndRestGenl.", 'UniversalVocabularyMt', vStrDef).
 7819exactlyAssertedEL_next(comment, argAndRestGenl, "A ternary ArgGenlPredicate (q.v.) used to \nplace a specified genls based argument-type constraint on a given \nVariableArityRelation (q.v.) with respect to any of its argument-places \nwhose ordinal position is greater than or equal to a specified number.\n(argAndRestGenl RELN N COL) means that, as a necessary condition for \nsemantic well-formedness, anything given as the Nth or greater argument \nto RELN must be an specialization of COL.  Thus a closed formula \n(RELN ARG1..ARG(N)..ARG(N+1)..) is well-formed only if each of ARG(N)..ARG(N+1).. is an instance of COL.  See also argsGenl and argAndRestIsa.", 'UniversalVocabularyMt', vStrDef).
 7820exactlyAssertedEL_next(comment, arg6SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg6SometimesIsa\nRELATION COLLECTION)</code> means that semantic well-formedness requires that\nanything given as the sixth argument to <code>RELATION</code> must be an\ninstance of <code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg6SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ... ARG6 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG6 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7821exactlyAssertedEL_next(comment, arg6QuotedIsa, "A binary Predicate (arg6QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the sixth argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ARG2 ARG3 ARG4 ARG5 ARG6 ...) is semantically well-formed only if (quotedIsa ARG6 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7822exactlyAssertedEL_next(comment, arg6Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg6Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the sixth argument to <code>RELN</code> must be an instance of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4 ARG5 ARG6 ...)</code> is semantically well-formed only if  <code>(isa ARG6 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argIsa for a similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7823exactlyAssertedEL_next(comment, arg6Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg6Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the sixth argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4 ARG5 ARG6 ...)</code> is semantically well-formed only if <code>(genls ARG6 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argGenl for a  similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7824exactlyAssertedEL_next(comment, arg6Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the sixth (or \"arg6\") argument-place of a given predicate.  (arg6Format PRED FORMAT) means that PRED's arg6 is constrained to FORMAT.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7825exactlyAssertedEL_next(comment, arg5SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg5SometimesIsa\nRELATION COLLECTION)</code> means that semantic well-formedness requires that\nanything given as the fifth argument to <code>RELATION</code> must be an\ninstance of <code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg3SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ... ARG5 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG5 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7826exactlyAssertedEL_next(comment, arg5QuotedIsa, "A binary Predicate (arg5QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the fifth argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ARG2 ARG3 ARG4 ARG5 ...) is semantically well-formed only if (quotedIsa ARG5 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7827exactlyAssertedEL_next(comment, arg5Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg5Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the fifth argument to <code>RELN</code> must be an instance of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4 ARG5</code> ...) is semantically well-formed only if  <code>(isa ARG5 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argIsa for a  similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7828exactlyAssertedEL_next(comment, arg5Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg5Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the fifth argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4 ARG5 ...)</code> is semantically well-formed only if <code>(genls ARG5 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argGenl for a  similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7829exactlyAssertedEL_next(comment, arg5Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the fifth (or \"arg5\") argument-place of a given predicate.  (arg5Format PRED FORMAT) means that PRED's arg5 is constrained to FORMAT.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7830exactlyAssertedEL_next(comment, arg4SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg4SometimesIsa\nRELATION COLLECTION)</code> means that semantic well-formedness requires that\nanything given as the fourth argument to <code>RELATION</code> must be an\ninstance of <code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg3SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ... ARG4 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG4 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7831exactlyAssertedEL_next(comment, arg4QuotedIsa, "A binary Predicate (arg4QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the fourth argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ARG2 ARG3 ARG4 ...) is semantically well-formed only if (quotedIsa ARG4 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7832exactlyAssertedEL_next(comment, arg4Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg4Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the fourth argument to <code>RELN</code> must be an instance of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4</code> ...) is semantically well-formed only if  <code>(isa ARG4 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argIsa for a  similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7833exactlyAssertedEL_next(comment, arg4Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg4Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the fourth argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is,  <code>(RELN ARG1 ARG2 ARG3 ARG4 ...)</code> is semantically well-formed only if  <code>(genls ARG4 COL)</code> holds.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its specializations.  See argGenl for a  similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7834exactlyAssertedEL_next(comment, arg4Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the fourth (or \"arg4\") argument-place of a given predicate.  (arg4Format PRED FORMAT) means that PRED's arg4 is constrained to FORMAT.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7835exactlyAssertedEL_next(comment, arg3SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg3SometimesIsa\nRELATION COLLECTION)</code> means that semantic well-formedness requires that\nanything given as the third argument to <code>RELATION</code> must be an\ninstance of <code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg3SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ... ARG3 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG3 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7836exactlyAssertedEL_next(comment, arg3QuotedIsa, "A binary Predicate (arg3QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the third argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ARG2 ARG3 ...) is semantically well-formed only if (quotedIsa ARG3 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7837exactlyAssertedEL_next(comment, arg3Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg3Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the third argument to <code>RELN</code> must be an instance of COL.  That is, <code>(RELN ARG1 ARG2 ARG3</code> ...) is semantically well-formed only if <code>(isa ARG3 COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argIsa for a similar but more flexible ternary  predicate.", 'UniversalVocabularyMt', vStrMon).
 7838exactlyAssertedEL_next(comment, arg3Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg3Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the third argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is, <code>(RELN ARG1 ARG2 ARG3 ...)</code> is semantically well-formed only if <code>(genls ARG3 COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argGenl for a similar but more flexible ternary  predicate.", 'UniversalVocabularyMt', vStrMon).
 7839exactlyAssertedEL_next(comment, arg3Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the third (or \"arg3\") argument-place of a given predicate.  (arg3Format PRED FORMAT) means that PRED's arg3 is constrained to FORMAT.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7840exactlyAssertedEL_next(comment, arg2SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg2SometimesIsa\nRELATION COLLECTION)</code> means that semantic well-formedness requires that\nanything given as the second argument to <code>RELATION</code> must be an\ninstance of <code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg2SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ... ARG2 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG2 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7841exactlyAssertedEL_next(comment, arg2QuotedIsa, "A binary Predicate (arg2QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the second argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ARG2 ...) is semantically well-formed only if (quotedIsa ARG2 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7842exactlyAssertedEL_next(comment, arg2Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg2Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the second argument to RELN must be an instance of <code>COL</code>.  That is, <code>(RELN ARG1 ARG2</code> ...) is semantically well-formed only if <code>(isa ARG2 COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argIsa for a similar but more flexible ternary  predicate.", 'UniversalVocabularyMt', vStrMon).
 7843exactlyAssertedEL_next(comment, arg2Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg2Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the second argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is, <code>(RELN ARG1 ARG2</code> ...) is semantically well-formed only if <code>(genls ARG2 COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argGenl for a similar but more flexible ternary  predicate.", 'UniversalVocabularyMt', vStrMon).
 7844exactlyAssertedEL_next(comment, arg2Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the second (or \"arg2\") argument-place of a given predicate.  <code>(arg2Format PRED FORMAT)</code> means that <code>PRED</code>'s arg2 is constrained to <code>FORMAT</code>.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7845exactlyAssertedEL_next(comment, arg1SometimesIsa, "An ArgSometimesIsaPredicate and ArgTypeBinaryPredicate, <code>(arg1SometimesIsa RELATION\nCOLLECTION)</code> means that semantic well-formedness requires that anything\ngiven as the first argument to <code>RELATION</code> must be an instance of\n<code>COLLECTION</code> at some time.  More precisely, if\n<code>(arg1SometimesIsa RELATION COLLECTION)</code> holds then in order to\nassert <code>(RELATION ARG1 ...)</code>, it must only be the case that there\nexists some time interval (including Always-TimeInterval) in which\n<code>(isa ARG1 COLLECTION)</code> holds.", 'UniversalVocabularyMt', vStrMon).
 7846exactlyAssertedEL_next(comment, arg1QuotedIsa, "A binary Predicate (arg1QuotedIsa RELN COL) means that semantic well-formedness requires that the term given as the first argument to RELN must be an instance of the SubLExpressionType COL. That is, (RELN ARG1 ...) is semantically well-formed only if (quotedIsa ARG1 COL) holds.", 'UniversalVocabularyMt', vStrMon).
 7847exactlyAssertedEL_next(comment, arg1Isa, "A binary ArgIsaPredicate (q.v.).  <code>(arg1Isa RELN COL)</code>  means that semantic well-formedness requires that anything given as the first argument to <code>RELN</code> must be an instance of <code>COL</code>.  That is, <code>(RELN ARG<sub>1</sub> ...)</code> is semantically well-formed only if <code>(isa ARG<sub>1</sub> COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argIsa for a similar but more flexible ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7848exactlyAssertedEL_next(comment, arg1Genl, "A binary ArgGenlPredicate (q.v.).  <code>(arg1Genl RELN COL)</code>  means that semantic well-formedness requires that anything given as the first argument to <code>RELN</code> must be a subcollection of <code>COL</code>.  That is, <code>(RELN ARG1</code> ...) is semantically well-formed only if <code>(genls ARG1 COL)</code> holds.  For an  explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.  See argGenl for a similar but more flexible  ternary predicate.", 'UniversalVocabularyMt', vStrMon).
 7849exactlyAssertedEL_next(comment, arg1Format, "An instance of ArgFormatPredicate (q.v.) used to place a particular Format (q.v.) constraint on the first (or \"arg1\") argument-place of a given predicate.  (arg1Format PRED FORMAT) means that PRED's arg1 is constrained to FORMAT.  See the reified instances Format for\nfurther details.", 'UniversalVocabularyMt', vStrDef).
 7850exactlyAssertedEL_next(comment, and, "A LogicalConnective that represents conjunction in CycL. It is a VariableArityRelation, taking an arbitrary number of ELSentence-Assertibles as arguments.  <code>(and P Q ... Z)</code> is true if and only if all of the sentences <code>P</code>, <code>Q</code>, ..., and <code>Z</code> are true.", 'UniversalVocabularyMt', vStrDef).
 7851exactlyAssertedEL_next(comment, afterRemoving, "When a gaf is unasserted, afterRemovings are called on the gaf dependent on the predicate of the gaf.  (afterRemoving PRED HOOK) means that HOOK will be called on gaf whose predicate is PRED.  If the gaf predicate has multiple afterRemovings, the order of execution is not guaranteed.  Also, afterRemovings are retriggered on the removal of each of the arguments to a gaf.", 'UniversalVocabularyMt', vStrMon).
 7852exactlyAssertedEL_next(comment, afterAdding, "Whenever a gaf is asserted, afterAddings are called on the gaf dependent on the predicate of the gaf.  (afterAdding PRED HOOK) means that HOOK will be called on gaf whose predicate is PRED.  If the gaf predicate has multiple afterAddings, the order of execution is not guaranteed.  Also, afterAddings are retriggered on the addition of new arguments to an existing gaf.", 'UniversalVocabularyMt', vStrMon).
 7853exactlyAssertedEL_next(comment, admittedSentence, "(admittedSentence SENTENCE) states that SENTENCE is a CycLSentence which is both syntactically and semantically well-formed with respect to argument constraints only.  For example, (admittedSentence (bordersOn Canada France)) is true in WorldGeographyDualistMt, but not in WorldGeographyMt, since Canada and France are known to be instances of GeographicalRegion in the former microtheory, but not in the latter microtheory.  See also admittedArgument.", 'UniversalVocabularyMt', vStrMon).
 7854exactlyAssertedEL_next(comment, admittedNAT, "(admittedNAT NAT) states that NAT is a CycLNonAtomicTerm which is both syntactically and semantically well-formed wrt arg constraints.  For example, (admittedNAT (MotherFn Muffet)) is true precisely in those mts in which Muffet satisfies all the applicable arg1 constraints imposed by MotherFn.  See also admittedSentence.", 'UniversalVocabularyMt', vStrMon).
 7855exactlyAssertedEL_next(comment, admittedArgument, "A ternary MetaRelation predicate that is used to state that a given thing meets the argument-type constraints on a given argument-place of a given relation. <code>(admittedArgument THING ARGNUM RELN)</code> means that <code>THING</code> satisfies all of the (single-argument) argument-type constraints (see ArgIsaPredicate and ArgGenlPredicate) for the <b><code>ARGNUM</b>-th</code> argument position of <code>RELN</code>.  \n<p>\nFor example, both of the following sentences hold:\n<pre>  (admittedArgument AbrahamLincoln 1 wife)\n\n  (admittedArgument Cougar 1 JuvenileFn) .</pre>\nSee also admittedAllArgument and admittedSentence.", 'UniversalVocabularyMt', vStrMon).
 7856exactlyAssertedEL_next(comment, admittedAllArgument, "A ternary MetaRelation predicate that relates a Collection to an integer (representing an argument-place) to a Relation such that every instance of the collection is an admittedArgument (q.v.) to the specified argument-place of the relation.  <code>(admittedAllArgument COL ARGNUM RELN)</code> means that every instance of <code>COL</code> satisfies all of the (single-argument) argument-type constraints (see ArgIsaPredicate and ArgGenlPredicate) for the <code>ARGNUM</code>th argument position of <code>RELN</code>.  Note that <code>COL</code> is required <i>not</i> to be an  EmptyCollection.\n<p>\nFor example, <code>(admittedAllArgument FemaleHuman 1 spouse)</code> and <code>(admittedAllArgument PersonTypeByActivity 1 JuvenileFn)</code> both hold.", 'UniversalVocabularyMt', vStrMon).
 7857exactlyAssertedEL_next(comment, abnormal, "A binary MetaKnowledgePredicate that is used to state exceptions to a given general CycLAssertion.  Typically, an abnormal assertion will be the result of the CycCanonicalizer having \"transformed\" a sentence asserted at the EL level that was built from an ExceptionPredicate (i.e. exceptWhen or exceptFor).  While perhaps less common-sensically intuitive than exceptWhen or exceptFor, abnormal facilitates an efficient and uniform handling of exceptions.\n<p>\nHere, in more detail, is how abnormal is used.  Every default rule in our system, schematically:\n<p>\nP[X1 ... Xn] -> Q[X1 ... Xn]\n<p>\n(with X1, ..., Xn free in both P and Q) is implicitly treated as\n<p>\n(not (\"abnormal-for-this-rule\" X1 ... Xn)) & (P[X1 ... Xn] -> Q[X1 ... Xn]) .\n<p>\nThus rules without exceptions need never incur the overhead of default reasoning.  Since a different \"abnormality\" relation would otherwise be needed for every default rule in the system, we use instead a single predicate -- abnormal -- which takes the rule in question as an argument.  And the other argument to abnormal is a List of variables (or of a single closed term) over which abnormality is computed; this allows abnormal to be binary rather than variable-arity.  Hence a sentence of the form\n<p>\n(exceptWhen EXCEPTION RULE) ,\n<p>\nin which each of the variables X1, ..., Xn occurs free in both EXCEPTION and RULE, gets canonicalized to an implies rule that concludes to an abnormal sentence:\n<p>\n<pre>\n(implies\n  EXCEPTION\n  (abnormal (TheList X1 .... Xn) RULE)) .\n</pre>\n<p>\nAnd a sentence of the form\n<p>\n(exceptFor TERM RULE) ,\n<p>\nin which exactly one variable X occurs free in RULE, gets canonicalized to a sentence of the form\n<p>\n(abnormal (TheList TERM) RULE) .\n<p>\nSee also pragmaticallyNormal.", 'UniversalVocabularyMt', vStrDef).
 7858exactlyAssertedEL_next(comment, 'WFFSupportedTerm', "The collection of all CycLTerms that have some kind of special support in the CycWellFormednessChecker.", 'UniversalVocabularyMt', vStrMon).
 7859exactlyAssertedEL_next(comment, 'WFFSupportedPredicate', "The collection of all Predicates that are supported in some way by the CycWellFormednessChecker, either to satisfy, impose, or relax well-formedness constraints.", 'UniversalVocabularyMt', vStrMon).
 7860exactlyAssertedEL_next(comment, 'WFFDirectivePredicate', "The collection of all Predicates which can affect what WFF standards to impose on a given sentence.", 'UniversalVocabularyMt', vStrMon).
 7861exactlyAssertedEL_next(comment, 'WFFConstraintSatisfactionPredicate', "The collection of all Predicates which can satisfy well-formedness constraints.  More specifically, only assertions of the form (PRED . ARGS), where PRED is an instance of WFFConstraintPredicate, can directly satisfy a well-formedness constraint, i.e. cause any previously ill-formed sentence to become well-formed, given the same WFF standards.  Any assertion could _indirectly_ satisfy a well-formedness constraint, for instance by triggering a forward rule or an afterAdding.  A common case of this is the afterAddings on spec-preds of isa and genls.", 'UniversalVocabularyMt', vStrMon).
 7862exactlyAssertedEL_next(comment, 'WFFConstraintPredicate', "The collection of all Predicates which can impose well-formedness constraints.  More specifically, only assertions of the form (PRED . ARGS), where PRED is an instance of WFFConstraintPredicate, can directly impose a well-formedness constraint, i.e. cause a previously well-formed sentence to become ill-formed, given the same WFF standards.  Any assertion could _indirectly_ impose a well-formedness constraint, for instance by triggering a forward rule or an afterAdding.", 'UniversalVocabularyMt', vStrMon).
 7863exactlyAssertedEL_next(comment, 'Wednesday', "A collection of CalendarDays and an \ninstance of DayOfWeekType.  Wednesday is the collection of all \n(and only) wednesdays.", 'UniversalVocabularyMt', vStrMon).
 7864exactlyAssertedEL_next(comment, 'VariableAritySkolemFunction', "The subcollection of SkolemFunctions with variable arity. These are only created when a sequence variable is in the scope of the skolem.", 'UniversalVocabularyMt', vStrDef).
 7865exactlyAssertedEL_next(comment, 'VariableAritySkolemFuncN', "The subcollection of SkolemFuncNs with variable arity. These are only created when a sequence variable is in the scope of  a bounded existential.", 'UniversalVocabularyMt', vStrDef).
 7866exactlyAssertedEL_next(comment, 'VariableArityRelation', "A specialization of Relation.  Each instance of VariableArityRelation is a relation that can take a variable number of arguments. The degree of variability for a given such relation can be constrained using the predicates arityMin and arityMax. Examples of VariableArityRelations include the predicate different and the function PlusFn.  Thus the terms '(PlusFn 1 2)' and '(PlusFn 1 2 3)' are both well-formed. Cf. FixedArityRelation.", 'UniversalVocabularyMt', vStrDef).
 7867exactlyAssertedEL_next(comment, 'UnreifiableFunction', "A specialization of Function-Denotational instances of which are such  that their values are not reified in the Cyc system.  More precisely, an instance of UnreifiableFunction is such that closed \"NATs\" (see  CycLNonAtomicTerm) built from its standard CycL name are _not_ instances of  HLReifiedDenotationalTerm.   Constrast with ReifiableFunction.  Usually it is more efficient to make functions reifiable; but it is not desirable  to reify every non-atomic term, such as those built from (names of)  instances of FunctionFromQuantitiesToQuantities.  For example, it would be cumbersome to reify every term of the form (Inch N) that happened to appear in a CycL assertion.", 'UniversalVocabularyMt', vStrDef).
 7868exactlyAssertedEL_next(comment, 'Unknown-HLTruthValue', "An instance of CycHLTruthValue. Unknown-HLTruthValue is the attribute of being neither known to be true nor known to be false.", 'BaseKB', vStrDef).
 7869exactlyAssertedEL_next(comment, 'UniversalVocabularyMt', "This is the microtheory which contains the 'definitional' assertions about everything in Cyc's universe of discourse.  Definitional assertions about a concept are those which are intrinsic to the concept's nature and cannot be violated in any context.", 'UniversalVocabularyMt', vStrMon).
 7870exactlyAssertedEL_next(comment, 'UniversalVocabularyImplementationMt', "This is the microtheory which contains the assertions about CycL terms which are necessary for Cyc's inference engine to reason about those terms.", 'BaseKB', vStrMon).
 7871exactlyAssertedEL_next(comment, 'Unity', "An instance of ZeroDimensionalUnitOfMeasure (q.v.) that takes one or two numbers or other NumericIntervals (q.v.) as argument(s) and returns the continuous numeric-interval that spans between and includes those arguments.  Given one argument, Unity behaves like an identity function.\n<p>\nMore precisely: for any numeric-interval <code>NUM</code>, <code>(Unity NUM)</code> = <code>NUM</code>; and for any two numeric-intervals <code>LO</code> and <code>HI</code> such that <code>(greaterThanOrEqualTo HI LO)</code>, <code>(Unity LO HI)</code> is the numeric-interval that ranges from the least point-value (see Number-General) subsumed by (see quantitySubsumes) <code>LO</code> to the greatest point-value subsumed by <code>HI</code>.\n<p>\nIn practice, <code>LO</code> and <code>HI</code> will typically be two distinct RealNumbers, and <code>(Unity LO HI)</code> will be the continuous ProperIntervalOnNumberLine that ranges from <code>LO</code> to <code>HI</code>.  For example, (Unity 1 10) is the interval from 1 to 10 inclusive.  But note that <code>LO</code> and/or <code>HI</code> might themselves be proper intervals: (Unity (Unity 7 9) 11) is thus the interval from 7 to 11 inclusive.\n<p>\nUnity is classified as a UnitOfMeasure mainly in order to simplify the application of quasi-mathematical operations (e.g. PerFn, UnitProductFn) to units-of-measure generally.  For example, TimesPerDay is defined as the result of \"dividing\" (via PerFn) Unity by DaysDuration.", 'UniversalVocabularyMt', vStrDef).
 7872exactlyAssertedEL_next(comment, 'UnitProductFn', "A binary UnitOfMeasureDenotingFunction that takes two UnitOfMeasure (q.v.) functions and returns the unit-of-measure function whose value for any given argument is the multiplicative \"product\" of the respective values yielded by the first two units, when one unit is applied to that same argument and the other unit is applied to 1.  That is, <code>(UnitProductFn UNIT1 UNIT2)</code> is the function <code>PRODUCT-FN</code> such that, for any number or other NumericInterval <code>NUM</code>, <code>(PRODUCT-FN NUM)</code> = <code>(TimesFn (UNIT1 NUM) (UNIT2 1))</code>.\n<p>\nFor example, (UnitProductFn Meter Meter) is SquareMeter; and (e.g.) (SquareMeter 5) is equal to (TimesFn (Meter 5) (Meter 1)). Also, (UnitProductFn  Kilowatt HoursDuration) is KilowattHour.\n<p>\nSee also PerFn.", 'UniversalVocabularyMt', vStrDef).
 7873exactlyAssertedEL_next(comment, 'UnitOfMeasure', "A specialization of ScalarDenotingFunction (q.v.).  Each instance of UnitOfMeasure is a function that takes one or two numbers or other NumericIntervals as arguments, and returns as value a MeasurableQuantity (q.v.), such as a Distance or a Speed or a Volume.  If a unit of measure is applied to one number (see Number-General) the result is a precise quantity that is a ScalarPointValue; if applied to two (different) numbers -- or to one (or two) ProperIntervalOnNumberLine(s) -- the result is a closed-interval quantity that is a ScalarProperInterval.  For example, (Meter 5) is the distance five meters and (Meter 5 10) is the distance \"five to ten meters (inclusive)\".\n<p>\n(A partial exception to the above is the unit-of-measure Unity (q.v.), which always returns a NumericInterval rather than a MeasurableQuantity.)\n<p>\nSpecializations of UnitOfMeasure grouped by what they measure include UnitOfTime, UnitOfSpeed, and UnitOfVolume.  Other specializations are OneDimensionalUnitOfMeasure, MultiDimensionalUnitOfMeasure, UnitOfMeasureWithPrefix and UnitOfMeasureNoPrefix.", 'UniversalVocabularyMt', vStrDef).
 7874exactlyAssertedEL_next(comment, 'UncanonicalizerAssertionFn', "UncanonicalizerAssertionFn is used by the CycUncanonicalizer and should rarely (if ever) need to be seen by users or referenced in assertions entered at the EL level.  It is used by the uncanonicalizer to denote an CycLAssertion after it is transformed to its canonical EL formula.", 'UniversalVocabularyMt', vStrMon).
 7875exactlyAssertedEL_next(comment, 'UnaryRelation', "The collection of all fixed-arity relations of arity 1 (see arity).  The most notable specializations of UnaryRelation are UnaryPredicate and UnaryFunction (qq.v.).", 'UniversalVocabularyMt', vStrMon).
 7876exactlyAssertedEL_next(comment, 'UnaryPredicate', "A specialization of both UnaryRelation and Predicate.  UnaryPredicate is the collection of all predicates whose arity (see arity) is 1.", 'UniversalVocabularyMt', vStrDef).
 7877exactlyAssertedEL_next(comment, 'UnaryFunction', "A specialization of both FixedArityFunction and UnaryRelation (qq.v.).  Each instance of UnaryFunction is a function that always takes a single argument, i.e. has an arity (see arity) of 1.", 'UniversalVocabularyMt', vStrDef).
 7878exactlyAssertedEL_next(comment, 'Tuesday', "A collection of CalendarDays and an \ninstance of DayOfWeekType.  Tuesday is the collection of all \n(and only) tuesdays.", 'UniversalVocabularyMt', vStrMon).
 7879exactlyAssertedEL_next(comment, 'TruthValue', "TruthValue is a collection of mathematical objects; it contains the abstract, logical objects True and False.", 'UniversalVocabularyMt', vStrMon).
 7880exactlyAssertedEL_next(comment, 'TruthFunction', "A major subcollection of Relation that subsumes the collections Predicate, LogicalConnective, and Quantifier (qq.v.). Truth-functions, or rather the expressions that represent or denote them, are used to form sentences.  More precisely, any CycL expression that denotes an instance of TruthFunction (and only such an expression) can appear in the \"0th\" argument-position (i.e. as the term immediately following the opening parenthesis) of a CycLSentence.  \n<p>\nThe name 'TruthFunction' derives in part from the fact that the sentences thus formed (if semantically well-formed and quantificationally closed; see CycLSentence-Assertible and CycLClosedSentence) are the kind of expression that can be true or false (with respect to a given context and interpretation). Though not really functions (cf. Function-Denotational), many TruthFunctions are \"truth-functional\" in the sense that the truth-value of a (closed, semantically well-formed) sentence <code>(RELN ARG1..ARGN)</code> built using a truth-function <code>RELN</code> is uniquely determined (with respect to a given context) by <code>RELN</code> together with the argument(s) <code>ARG1..ARGN</code> to which it is applied.  For example, the sentence <code>(mother ChelseaClinton HillaryClinton)</code> is made true (in the actual world) by the fact that Chelsea Clinton's mother is Hillary Clinton.", 'UniversalVocabularyMt', vStrDef).
 7881exactlyAssertedEL_next(comment, 'True', "An instance of TruthValue (q.v.).  True is the logical notion of truth.  That is, the term 'True' is used as a sentential constant of CycL that is true under every model theoretic interpretation.  For example, (booleanResult T/F True) means that the result obtained from the true-or-false test T/F is True.  Cf. False.", 'BaseKB', vStrDef).
 7882exactlyAssertedEL_next(comment, 'TransitiveBinaryPredicate', "A BinaryPredicateTypeByLogicalFeature and thus a specialization of BinaryPredicate.  A binary predicate <code>PRED</code> is an instance of TransitiveBinaryPredicate only if it has the following property: For any <code>THING1</code>, <code>THING2</code>, and <code>THING3</code>, if both of these hold:\n<pre>\n  (PRED THING1 THING2)\n  (PRED THING2 THING3)\n</pre>\nThen so does this:\n<pre>\n  (PRED THING1 THING3) .\n</pre>\nNote that a necessary condition on <code>PRED</code>'s being transitive is that its two argument-places must be co-satisfiable; see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement.\n<p>\nInstances of TransitiveBinaryPredicate include greaterThan,\ngeographicalSubRegions, and cotemporal.  \n<p>\nCf. QuasiTransitiveBinaryPredicate and AntiTransitiveBinaryPredicate.", 'UniversalVocabularyMt', vStrDef).
 7883exactlyAssertedEL_next(comment, 'TransformationModuleSupportedPredicate', "The collection of all Predicates which are supported by some CycTransformationModule.", 'UniversalVocabularyMt', vStrMon).
 7884exactlyAssertedEL_next(comment, 'TransformationModuleSupportedCollection', "The collection of all Collections which are supported by some CycTransformationModule.", 'UniversalVocabularyMt', vStrMon).
 7885exactlyAssertedEL_next(comment, 'TLVariableFn', "Denotes HL variables at the TL: arg1 is the HL index of the variable; arg2 is the EL string name of the variable.", 'UniversalVocabularyMt', vStrDef).
 7886exactlyAssertedEL_next(comment, 'TLReifiedNatFn', "Denotes a reified nat term at the TL: arg1 is the formula of the nat.", 'UniversalVocabularyMt', vStrDef).
 7887exactlyAssertedEL_next(comment, 'TLAssertionFn', "Denotes HL assertion terms at the TL (e.g., assertions appearing as terms within meta-assertions): arg1 is the mt of the assertion; arg2 is the formula of the assertion.", 'UniversalVocabularyMt', vStrDef).
 7888exactlyAssertedEL_next(comment, 'TimesFn', "A VariableArityRelation that represents multiplication in CycL. (TimesFn MULT1 MULT2 ...) yields a quantity which is the result of multiplying MULT1 MULT2 (...) together. All arguments to TimesFn must be instances of ScalarInterval, as is its result. Thus (TimesFn 2 3 4) returns 24; (TimesFn Pi-Number E-LogarithmBase) returns pi times e. For division see QuotientFn.", 'UniversalVocabularyMt', vStrDef).
 7889exactlyAssertedEL_next(comment, 'Thursday', "A collection of CalendarDays and an  instance of DayOfWeekType.  Thursday is the collection of all  (and only) thursdays.", 'UniversalVocabularyMt', vStrMon).
 7890exactlyAssertedEL_next(comment, 'Thing', "Thing is the \"universal collection\": the collection which, by definition, contains everything there is.  Every thing in the Cyc ontology -- every Individual (of any kind), every Set-Mathematical, and every Collection -- is an instance of (see isa) Thing.  Similarly, every collection is a subcollection of (see genls) Thing.  Trivially, Thing is both an instance of and a subcollection of itself, and is not a subcollection of any other collection.  (Note that the above reference to \"every thing in the Cyc ontology\" is <i>not</i> meant to be limited to things actually <i>reified</i> in the Cyc system, but includes (e.g.) every instance -- reified or not, known or not -- of every collection recognized by Cyc.)", 'UniversalVocabularyMt', vStrDef).
 7891exactlyAssertedEL_next(comment, 'TheUser', "TheUser denotes the `current user' of an individual, running Cyc image.  Note that at any moment there may actually be many current users of an image, communicating with it through various sorts of API: HTML-based browser, telnet API connection, etc. TheUser serves as a placeholder allowing Cyc to keep track of relevant characteristics (including authorization, sophistication level) of each distinct user.", 'BaseKB', vStrDef).
 7892exactlyAssertedEL_next(comment, 'TheTerm', "A special kind of term that allows back-reference to any individual thing that satisfies the constraints on the TheTerm.  E.g., 'Suppose a cat walks into a fish store.  The cat is likely to get into a lot of trouble.'  'The cat' in the second sentence refers back to 'a cat' in the first; i.e., any cat that walks into a fish store.  In Cyc, the constraints for a TheTerm in a given context are given by use of the predicate theTermConstraints on the unit representing that context.  In lifting assertions out of that context, the constraints are added as antecedents.", 'UniversalVocabularyMt', vStrDef).
 7893exactlyAssertedEL_next(comment, 'TheSetOf', "A binary SetDenotingFunction and ScopingRelation that takes a variable and an open sentence to a set, where the open sentence specifies a necessary and sufficient membership condition for the set.  If <code>SENT</code> is an open CycLSentence-Assertible in which <code>VAR</code> is the only variable occuring free, (TheSetOf <code>VAR SENT</code>) is the Set-Mathematical of exactly those things that satisfy <code>SENT</code>.  For example, (TheSetOf ?X (and (isa ?X Dog) (mainColorOfObject ?X BlackColor))) is the set of black dogs.\n<p>\nNote that if <code>VAR</code> does not occur free in <code>SENT</code>, or is not the only variable occuring free in <code>SENT</code>, the term <code>(TheSetOf VAR SENT)</code> will be itself be open (see CycLOpenNonAtomicTerm) and thus will not denote anything.  Given that a true sentence is satisfied by <i>everything</i>, we stipulate that <code>(TheSetOf VAR SENT)</code> is undefined whenever <code>SENT</code> is closed in order to avoid commitment to a \"universal set\". \n<p>\nSee also TheSet, which is used to specify a set by enumerating its elements.  And see TheCollectionOf.", 'UniversalVocabularyMt', vStrDef).
 7894exactlyAssertedEL_next(comment, 'TheSet', "A variable-arity SetDenotingFunction that is used to specify a set by enumerating its elements.  For any finite sequence <code>THING1,...,THING<sub>N</sub></code> (<code>N</code> >= 1), (TheSet <code>THING1...THING<sub>N</sub>)</code> is the Set-Mathematical whose elements (see elementOf) are precisely <code>THING1,...,THING<sub>N</sub></code>.  For example, (TheSet SonnyBono Cher) is the set whose only elements are Sonny and Cher.  \n<p>\nNote that in the degenerate case where <code>N</code> is zero, (TheSet) is TheEmptySet.  \n<p>\nSee also the related function TheSetOf, which is used to specify a set by giving a necessary and sufficient membership condition.  And see TheList and TheCollection.", 'UniversalVocabularyMt', vStrDef).
 7895exactlyAssertedEL_next(comment, 'TheList', "TheList is a function that combines its arguments into a list.  For any ITEM(1), ..., ITEM(n), each of which is an instance of Thing, (TheList ITEM(1) ... ITEM(n)) gives the instance of List-Extensional whose first member is ITEM (1), ..., and whose last member is ITEM(n). Note that in general ITEM(1), ..., ITEM(n) do not have to be distinct, though they do if (TheList ITEM(1) ... ITEM(n)) is an instance of ListWithoutRepetition.", 'UniversalVocabularyMt', vStrDef).
 7896exactlyAssertedEL_next(comment, 'TheEmptySet', "TheEmptySet is the empty (or \"null\") set: the unique set that has no elements.  Note that TheEmptySet is an instance of Set-Mathematical and thus _not_ an instance of Collection.", 'UniversalVocabularyMt', vStrDef).
 7897exactlyAssertedEL_next(comment, 'TheEmptyList', "An instance of ListWithoutRepetition. TheEmptyList is a list that has no members (see listMembers).  Note that any list that has no members is identical with TheEmptyList; thus TheEmptyList is the only list whose length is 0.  Note also that TheEmptyList is a sublist (see subLists) of every list.  Note finally that TheEmptyList is not the same as TheEmptySet (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7898exactlyAssertedEL_next(comment, 'TheCollectionOf', "A collection denoting function that takes a CycL variable and an open formula with exactly one free variable to the collecion of things satisfying that formula.", 'BaseKB', vStrDef).
 7899exactlyAssertedEL_next(comment, 'TernaryRelation', "The collection of all fixed-arity relations of arity 3 (see arity).  The most notable specializations of TernaryRelation are TernaryPredicate and TernaryFunction (qq.v.).", 'UniversalVocabularyMt', vStrMon).
 7900exactlyAssertedEL_next(comment, 'TernaryPredicate', "A specialization of both TernaryRelation and Predicate.  TernaryPredicate is the collection of all predicates whose arity (see arity) is 3.", 'UniversalVocabularyMt', vStrDef).
 7901exactlyAssertedEL_next(comment, 'TernaryFunction', "A specialization of FixedArityFunction and TernaryRelation.  An instance FUNC of FixedArityFunction is an instance of TernaryFunction if and only if FUNC has an arity of three.", 'UniversalVocabularyMt', vStrDef).
 7902exactlyAssertedEL_next(comment, 'TemporaryEnglishParaphraseMt', "This is a temporary MT for holding paraphrase assertions prior to review, after which time they will be moved to EnglishParaphraseMt", 'BaseKB', vStrDef).
 7903exactlyAssertedEL_next(comment, 'SymmetricBinaryPredicate', "A specialization of both BinaryPredicate and CommutativeRelation (qq.v.).  A binary predicate <code>PRED</code> is an instance of SymmetricBinaryPredicate if and only if (i) for any things <code>X</code> and <code>Y</code>, if <code>(PRED X Y)</code> then <code>(PRED Y X)</code> and (ii) the single-argument argument type constraints (see argIsa and argGenls) on <code>PRED</code>'s two argument-places are co-satisfiable (see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement).  Note that if <code>PRED</code> satisfies condition (i), then it also satisfies condition (ii) as long as <code>(PRED A B)</code> holds for some <code>A</code> and <code>B</code>.\n<p>\nInstances of SymmetricBinaryPredicate include siblings, teammates, connectedTo, and bordersOn.", 'UniversalVocabularyMt', vStrDef).
 7904exactlyAssertedEL_next(comment, 'Sunday', "A collection of CalendarDays and an  instance of DayOfWeekType.  Sunday is the collection of all  (and only) sundays.", 'UniversalVocabularyMt', vStrMon).
 7905exactlyAssertedEL_next(comment, 'substring-CaseInsensitive', "<code>(substring-CaseInsensitive SUBSTRING STRING)</code> means that the <code>CharacterString SUBSTRING</code> is a substring of the <code>CharacterString STRING</code> with case ignored in both <code>SUBSTRING</code> and <code>STRING</code>. For case-sensitive tagging use the more specialized predicate, <code>substring</code>.", 'UniversalVocabularyMt', vStrMon).
 7906exactlyAssertedEL_next(comment, 'SubLSymbol', "The collection of all SubLAtoms that are also \"symbols\" in the SubL language.  That is, each instance of SubLSymbol satisfies the defnIff SYMBOLP.  Note that `symbol' has a very specific, technical meaning in SubL.  Save for those that are variables (see SubLVariable), SubLSymbols are rarely used in CycL assertions, except within those built with certain CycInferenceDescriptorPredicates like defnIff. Examples of SubL symbols include the symbols 'GENLS' and 'CYC-SYSTEM-NON-VARIABLE-SYMBOL-P'. Note also that SubLSymbol is a \"quoted-collection\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7907exactlyAssertedEL_next(comment, 'SubLString', "A subcollection of SubLAtomicTerm (q.v.) whose instances can be used to denote character-strings.  In the SubL language (as in English), one can refer to a particular character-string by simply putting a pair of quotation marks around it.  Semantically, what this amounts to is using a certain character-string to denote itself.  \n<p>\nMore precisely: a given SubLString STRING is a character-string such that, when it appears inside a pair of double-quotation marks, STRING is interpreted as denoting itself (i.e. STRING).  The surrounding quotation-marks are <i>not</i> considered to be parts of STRING; rather, they are syncategorematic symbols whose role is merely to indicate that a string is being referred to.  Thus, in the context of the sentence '(firstName Lenat \"Doug\")', the four-character string 'Doug' denotes itself: the string `Doug'.  \n<p>\nNote that <i>not</i> every CharacterString is a SubLString: there are some restrictions on what characters a SubL-string can contain. Note also that SubLStrings are <i>atomic</i> terms (see SubLAtomicTerm and CycLAtomicTerm), as they cannot be constructed out of other SubL (or CycL) terms via the syntax (grammar) of SubL (or CycL).  Thus although the string 'hotdog' can indeed be obtained from 'hot' and 'dog' via concatenation (see ConcatenateStringsFn), the <i>syntax</i> of SubL (or CycL) itself contains no rule that licenses such a construction (see e.g. the comments on SubLSExpression, CycLExpression, CycLTerm, CycLFormula, and various subcollections thereof).  Note finally that SubLString is a \"quoted-collection\" (see quotedCollection).  Thus the sentence '(isa \"hotdog\" SubLString)' means, just as one would expect, that the six-character string 'hotdog' (not the eight-character quote-inclusive '\"hotdog\"'; see above) is an instance of SubLString.", 'UniversalVocabularyMt', vStrDef).
 7908exactlyAssertedEL_next(comment, 'SubLSExpression', "The collection of all expressions of the SubL language.  SubL is the implementation language of the Cyc system, and it subsumes the CycL language.  The CycL grammar is more strict than the SubL grammar. Thus, while every CycLExpression is a SubLSExpression, the converse is not true. Examples of SubLSExpressions that are not CycLExpressions include Arabic decimal numeric expressions such as '123', expressions like '(1 2 3)' that denote lists of numbers, and \"dotted pair\" expressions like '(Cat . Dog)'.", 'UniversalVocabularyMt', vStrDef).
 7909exactlyAssertedEL_next(comment, 'SubLRealNumber', "The collection of all number-denoting expressions in the CycL language that are _not_ CycL constants or NATs, but are terms of SubL, the underlying implementation language of the Cyc system. SubLRealNumbers are numeric strings of the Arabic decimal system, including the decimal point and scientific notation.  Examples include the terms `212' and `3.14159d0'.  Non-examples include the expressions `One', `(Meter 6)', `(Unity 3)', `:34', `PlusInfinity', and `Avogadro's number'.  Note that this collection, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7910exactlyAssertedEL_next(comment, 'SubLQuoteFn', "<code>(SubLQuoteFn SUBL-EXPRESSION)</code> is one of exactly two escapes to SubL from CycL, the other being ExpandSubLFn.  These are the only two ways to represent arbitrary SubL in CycL.  SubLQuoteFn encapsulates <code>SUBL-EXPRESSION</code> such that it will not be rejected by the CycL wff-checker as ill-formed CycL.  For example, <code>(SubLQuoteFn (+ 1 2))</code>, which <i>is</i> a CycLExpression, denotes the SubLSExpression (+ 1 2), which itself is <i>not</i> a CycLExpression.", 'UniversalVocabularyMt', vStrMon).
 7911exactlyAssertedEL_next(comment, 'SubLPositiveInteger', "The collection of all positive-integer-denoting expressions in the CycL language that are <i>not</i> CycL constants or NATs, but are terms of SubL, the underlying implementation language of the Cyc system.  SubLPositiveIntegers  are numeric strings of the Arabic decimal system (not including the decimal point or scientific notation).  Examples include the expressions '2', '12', and '4'.  Non-examples include '0', '4.012', '(Meter 6)', '(Unity 3.3)', ':34', and 'PlusInfinity'.  Note that SubLPositiveInteger is a \"quoted-collection\" (see quotedCollection); thus the sentence '(isa 12 SubLPositiveInteger)' means that the expression '12' (not the number 12) is an instance of SubLPositiveInteger.", 'UniversalVocabularyMt', vStrDef).
 7912exactlyAssertedEL_next(comment, 'SubLNonVariableSymbol', "The collection of all SubLSymbols except SubLVariables (qq.v.); a subcollection of CycLClosedAtomicTerm.  Note that `symbol' has a very specific, technical meaning in SubL; SubLNonVariableSymbols are rarely used in CycL assertions, except within those built with certain CycInferenceDescriptorPredicates like defnIff and those whose arguments are KeywordVariableTemplates (qq.v.). Examples of SubL non-variable symbols include the symbols `GENLS', `:ARG1', and `CYC-SYSTEM-NON-VARIABLE-SYMBOL-P'.  Note that this collection, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7913exactlyAssertedEL_next(comment, 'SubLNonVariableNonKeywordSymbol', "The collection of all SubLSymbols except SubLVariables (q.v.) and SubLKeywords (q.v.); a subcollection of CycLClosedAtomicTerm.  Note that `symbol' has a very specific, technical meaning in SubL; SubLNonVariableNonKeywordSymbols are rarely used in CycL assertions, except within those built with certain CycInferenceDescriptorPredicates like defnIff. Examples of SubL non-variable non-keyword symbols include the symbols `GENLS' and `CYC-SYSTEM-NON-VARIABLE-NON-KEYWORD-SYMBOL-P'.  Note that this collection, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7914exactlyAssertedEL_next(comment, 'SubLNonNegativeInteger', "The collection of all non-negative-integer-denoting expressions in the CycL language that are _not_ CycL constants or NATs, but are terms of SubL, the underlying implementation language of the Cyc system.  SubLNonNegativeIntegers \nare numeric strings of the Arabic decimal system (not including the decimal point or scientific notation).  Examples include the expressions `0', `12', and `4'.  Non-examples include `4.012', `(Meter 6)', `(Unity 3.3)', `:34', and `PlusInfinity'.  Note that SubLNonNegativeInteger is a \"quoted-collection\" (see quotedCollection); thus the sentence `(isa 12 SubLNonNegativeInteger)' means that the expression `12' (and not \nthe number 12) is an instance of SubLNonNegativeInteger.", 'UniversalVocabularyMt', vStrDef).
 7915exactlyAssertedEL_next(comment, 'SubLList', "A collection of list-denoting expressions that are not represented in CycL (i.e. they are not CycLConstants or CycLNonAtomicTerms) but are represented in SubL, the underlying implementation language of the Cyc system.  Each instance of SubLList is a sequence of SubLListOrAtoms (q.v.) enclosed in parentheses.  SubL lists are those things that pass the defnIff LISTP. Note that this collection is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7916exactlyAssertedEL_next(comment, 'SubLKeyword', "The subcollection of SubLSymbol consisting of all SubL keywords.  Instances include the symbols `:KEYWORD', `:OBJECT', and `:PLURAL'.  Every instance of SubLKeyword satisfies (in the sense relevant to defnIff) `KEYWORDP'.  Note that SubLKeyword, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7917exactlyAssertedEL_next(comment, 'SubLInteger', "The collection of all integer-denoting expressions in the CycL language that are _not_ CycL constants or NATs, but are terms of SubL, the underlying implementation language of the Cyc system.  SubLIntegers  are numeric strings of the Arabic decimal system (including the negative-value symbol `-', but _not_ the decimal point or scientific notation) that denote integers.  Examples include the expressions `0', `12', and `-4' (which denote the integers 0, 12, and -4, respectively).  Non-examples include `4.012', `(Meter 6)', `(Unity 3.3)', `:34', and `PlusInfinity'.  Note that SubLInteger is a \"quoted-collection\" (see quotedCollection). Thus the sentence `(isa 12 SubLInteger)' means that the expression `12' (and not the number 12) is an instance of SubLInteger.  Similarly, the assertion `(genls SubLInteger Integer)' means (not that each SubL integer is an integer, but) that each  instance of SubLInteger _denotes_ an instance of Integer (see the shared NoteAboutUseVersusMention).", 'UniversalVocabularyMt', vStrDef).
 7918exactlyAssertedEL_next(comment, 'SubLExpressionType', "A collection of collections.  Each instance of SubLExpressionType is a type (i.e. a subcollection) of SubLSExpression.", 'UniversalVocabularyMt', vStrMon).
 7919exactlyAssertedEL_next(comment, 'SubLCharacter', "The collection of all character-denoting terms in the CycL language that are SubLAtomicTerms (q.v.). (SubL, which subsumes CycL, is the underlying implementation language of the Cyc system.)  A given SubLCharacter CHAR-TERM is itself a string consisting of the hash-symbol (`#'), followed by the backslash (`\\'), followed (in most cases) by the character CHAR that CHAR-TERM denotes.  For example, the SubLCharacter `#\\A'\ndenotes the character `A'.  (An exception to the above is when CHAR is a non-printing or control character, in which case a specially-designated string\nappears after the `#\\'.)", 'UniversalVocabularyMt', vStrDef).
 7920exactlyAssertedEL_next(comment, 'SubLAtomicTerm', "The collection of all atomic denotational terms in the CycL language that are not explicitly represented in CycL (i.e. they are neither CycLConstants nor CycLVariables) but are represented in SubL, the underlying implementation language of the Cyc system.  \"Atomic\" here means not constructable from other terms via the SubL syntax.  Examples include the terms '212', ':NOUN', '#x', and 'VARIABLE-P'. Do not confuse this collection with SubLAtom, most of whose instances, while they are expressions of SubL, are <i>not</i> part of CycL.  Note that this collection, like most instances of CycLExpressionType, is \"quoted\".", 'UniversalVocabularyMt', vStrDef).
 7921exactlyAssertedEL_next(comment, 'SubLAtom', "A collection of SubLExpressions that are atomic: they cannot be decomposed into other SubL expressions. Save for certain variables (see SubLVariable), instances of SubLAtom are rarely used in CycL assertions (other than assertions built with certain CycInferenceDescriptorPredicates like defnIff). Many SubL atoms are not even CycLExpressions.  Do not confuse this collection with SubLAtomicTerm, which is a CycLExpressionType (though its instances are neither CycL constants nor CycL variables).  Note that SubLAtom is a \"quoted-collection\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 7922exactlyAssertedEL_next(comment, 'SkolemFunctionFn', "SkolemFunctionFn is used by the CycCanonicalizer and should rarely (if ever) need to be seen by users or referenced in assertions entered at the EL level.  It is used by the canonicalizer to denote a skolem function before it is reified, when the skolem is derived from a formula asserted at the EL level that uses thereExists. Its arity is 3: the first argument is a list of the term variable arguments of the denoted skolem function, (term variables which are in the scope of the existential), the second argument is a variable which uniquely identifies the existentially quantified variable by which the denoted skolem will be represented in the canonical version of the formula, and the third is  a sequence variable if there is a sequence variable argument of the denoted skolem function (which there will be iff there is a sequence variable in the scope of the existential), and NIL otherwise.", 'UniversalVocabularyMt', vStrDef).
 7923exactlyAssertedEL_next(comment, 'SkolemFunction', "A specialization of IndeterminateTermDenotingFunction and ReifiableFunction (qq.v.).  SkolemFunction is a collection of system-generated functions that implement existential quantification in Cyc.  Whenever someone asserts to the Knowledge Base a sentence that contains 'thereExists' (in an arg0 position), Cyc automatically creates a new instance of SkolemFunction and rewrites the assertion using that Skolem function.\n<p>\nFor example, suppose we want Cyc to know that every animal has a birth date.   So we assert the following sentence:\n<p>\n<pre>\n  (implies\n    (isa ?X Animal)\n    (thereExists ?Y\n      (birthDate ?X ?Y))) .\n</pre>\n<p>\nIn response, Cyc automatically reifies a new unary instance of SkolemFunction (call it 'BirthDateFn') that takes any given animal to its date of birth, and then rewrites our rule using BirthDateFn instead of thereExists, as\n<p>\n<pre>\n  (implies\n    (and\n      (isa ?X Animal)\n      (termOfUnit ?Y (BirthDateFn ?X)))\n    (birthDate ?X ?Y)) .\n</pre>\n<p>\nNote that actual Cyc-generated Skolem function names currently (02/04) consist of the prefix 'SKF-' follow by a numeral.", 'UniversalVocabularyMt', vStrDef).
 7924exactlyAssertedEL_next(comment, 'SkolemFuncNFn', "SkolemFuncNFn is used by the CycCanonicalizer and should rarely\n(if ever) need to be seen by users or referenced in assertions entered\nat the EL level.  It is used by the canonicalizer to denote a skolem\nfunction before it is reified, when the skolem is derived from a formula\nasserted at the EL level that uses thereExistAtLeast,\nthereExistAtMost, or thereExistExactly.  Its arity is 4: the first\nargument is a list of the term variable arguments of the denoted skolem function,\n(term variables which are in the scope of the bounded existential).\nThe second argument is a variable which uniquely identifies the\nexistentially quantified variable by which the denoted skolem will\nbe represented in the canonical version of the formula.\nThe third is a sequence variable if there is a sequence variable\nargument of the denoted skolem function (which there will be iff there\nis a sequence variable in the scope of the bounded existential), and NIL otherwise.\nThe fourth is an interval specifying the number of things which may satisfy the formula.", 'UniversalVocabularyMt', vStrDef).
 7925exactlyAssertedEL_next(comment, 'SkolemFuncN', "SkolemFuncN is a collection of Cyc system-generated functions that partially implement existential quantifications in Cyc.  Whenever someone asserts to Cyc an expression that contains a 'thereExistAtLeast', a 'thereExistAtMost', or a 'thereExistExactly' quantifier, Cyc automatically creates a new instance of SkolemFuncN and rewrites the assertion using this skolem function instead of that existential quantifier.  See also termOfUnit. At this time (3/98), skolem functions are automatically named by the Cyc system using the prefix 'SKF-' followed by a number.", 'UniversalVocabularyMt', vStrDef).
 7926exactlyAssertedEL_next(comment, 'SingleEntry', "An instance of Format (q.v.) that can be specified to hold of a given predicate with respect to a given argument-place (see argFormat).  (argFormat PRED N SingleEntry) means that, for any particular way of fixing the other arguments to PRED besides the Nth, there is at most one thing such that, if taken as the Nth argument, PRED holds of those arguments.  That is, if the sequences <... ARGN ...> and <... ARGN-PRIME ...> differ at most in their Nth items and both (PRED ... ARGN ...) and (PRED ... ARGN-PRIME ...) hold, then ARGN = ARGN-PRIME (see equals).  For example, the format of biologicalMother's second argument-place is single-entry, since an animal can only have one biological mother.  A predicate with a single-entry format argument-place is thus a StrictlyFunctionalPredicate (q.v.) that is strictly functional with respect to that argument-place (see strictlyFunctionalInArgs).  Contrast with SetTheFormat.", 'BaseKB', vStrDef).
 7927exactlyAssertedEL_next(comment, 'SiblingDisjointCollectionType', "A KBDependentCollection of collections of  collections (and thus an instance of CollectionTypeType and a specialization of CollectionType).  A sibling-disjoint collection type is such that its known  (i.e. KB-represented) instances are collections that -- save for any that are related to each other by  genls and any that are explicitly asserted to be exceptions (see  siblingDisjointExceptions) -- are disjoint from each other. \n<p>\nMore precisely, each instance <code>SIB</code> of SiblingDisjointCollectionType is a collection of collections that has the following KB-dependent property: \n<p>\nFor any two known instances <code>COL1</code> and <code>COL2</code> of   <code>SIB</code>, at least one of the following is known to hold: \n<pre>\n  (a) (genls COL1 COL2)\n  (b) (genls COL2 COL1)\n  (c) (siblingDisjointExceptions COL1 COL2)\n  (d) (disjointWith COL1 COL2)\n</pre>  \nMoreover, note that if <code>MT</code> is a context (see Microtheory) in which (i) both <code>(isa COL1 SIB)</code> and <code>(isa COL2 SIB)</code> hold and (ii)  neither <code>(genls COL1 COL2)</code> nor <code>(genls COL2 COL1)</code> nor <code>(siblingDisjointExceptions COL1 COL2)</code> is known to hold (see knownSentence), then \n<code>(disjointWith COL1 COL2)</code> holds by default in <code>MT</code>.   \n<p>\nFor example, in BiologyMt both Person and Dog are instances of the  sibling-disjoint collection type BiologicalSpecies, while neither  (genls Person Dog) nor (genls Dog Person) nor  (siblingDisjointExceptions Person Dog) is known to hold in that  context; consequently, (disjointWith Person Dog) holds by default  in BiologyMt.  Instances of SiblingDisjointCollectionType include  BiologicalTaxon (and its specializations), OrganismPartType, and RelationshipTypeByArity.\n<p>\nSee the generalization SiblingDisjointSetOrCollectionType.  Also cf. the stronger notion of DisjointCollectionType.", 'UniversalVocabularyMt', vStrDef).
 7928exactlyAssertedEL_next(comment, 'SiblingDisjointAttributeType', "A collection of collections.  Each instance of SiblingDisjointAttributeType is a collection of quantities.  If COL is such a collection, then nothing can have two instances of COL as quantities unless those two instances are related in a quantitySubsumes relationship to each other.  See also SiblingDisjointCollectionType.", 'UniversalVocabularyMt', vStrDef).
 7929exactlyAssertedEL_next(comment, 'SetTheFormat', "An instance of Format (q.v.) that can be specified to hold of a given predicate with respect to a given argument-place (see argFormat).  (argFormat PRED N SetTheFormat) means that, for any particular way of fixing the other arguments to PRED besides the Nth, there might be any number (including zero) of things such that, if taken as the Nth argument, PRED holds of those arguments.  For example, the format of biologicalMother's first argument-place is SetTheFormat, since a female animal might have any number of offspring.  Unlike the other reified instances of Format, SetTheFormat actually places no restriction at all on what PRED might or might not hold of with respect to the relevant argument-place.  But one should not infer from this that entry-format assertions using SetTheFormat are pointless; for they forestall duplication of effort by serving notice that the entry-format of a given argument-place has previously been considered and SetTheFormat was deemed the appropriate format.  SetTheFormat is the most commonly-encountered format in the Cyc Knowledge Base.  Contrast with SingleEntry.", 'BaseKB', vStrDef).
 7930exactlyAssertedEL_next(comment, 'SetOrCollection', "A specialization of MathematicalThing.  Something is an instance of SetOrCollection just in case it is a collection (i.e. an instance of Collection) or a mathematical set (i.e. an instance of Set-Mathematical).  Instances of Set-Mathematical and instances of Collection (and thus instances of SetOrCollection) share some basic common features.  All instances of Collection and all instances of Set-Mathematical (and thus all instances of SetOrCollection) are abstract entities, lacking spatial and temporal properties.  Nearly all instances of Collection (except \"empty\" collections) and nearly all instances of Set-Mathematical (except the empty set; see TheEmptySet) have \"elements\" (i.e. instances or members; see elementOf); hence set-or-collections may stand to one another in generalized set-theoretic relations such as subsetOf and disjointWith (qq.v.).  (It is this shared feature of having elements that provides the basic rationale for reifying the collection SetOrCollection.)  Nevertheless, sets and collections differ in two important ways.  First, each collection is intrinsically associated with an intensional criterion for membership -- a more or less natural property (or group of properties) possessed by all of (and only) its elements.  Collections are thus akin to kinds.  In contrast, the elements of a set are not required to be homogeneous in any respect: any things whatsoever may together constitute the elements of a set.  The second major difference between sets and collections is that no two distinct sets can be coextensional (i.e. have exactly the same elements; see coExtensional).  Sets can thus be identified purely on the basis of their extensions (see extent).  Collections, on the other hand, are individuated by their intensional criteria for membership.  So collections that have exactly the same elements might nevertheless be distinct, differing in their respective membership criteria.  (Note that the general relationship between collections and their \"intensional criteria for membership\" in the above sense is not something that is currently represented explicitly in the Knowledge Base (though this seems a worthwhile area for future work); still the comment and other \"definitional\" assertions on a given collection should ideally convey a reasonably clear and precise idea of its associated membership criterion.)", 'UniversalVocabularyMt', vStrDef).
 7931exactlyAssertedEL_next(comment, 'Set-Mathematical', "A specialization of SetOrCollection (q.v.); the collection of mathematical sets.  An instance of Set-Mathematical can be any arbitrary set of Things.  A good way to explain this notion with respect to the Cyc ontology is to contrast Set-Mathematical with Collection (q.v.).  First, while the instances of a given collection all have some more-or-less significant (often \"natural\") property or properties in common, the elements (see elementOf) in a given set might have nothing in common (besides membership in that set).  Second, while it is in principle possible for two distinct collections to have exactly the same elements (with respect to a given context), this cannot happen in the case of sets, which are individuated strictly in terms of their extensions (see extent).  Third (and specifically regarding their expression in the CycL language), unlike with collections, rarely will it be desirable to create a new constant to denote a particular set.  Instead, a set will often be either (a) intensionally specified by a defining property via TheSetOf (q.v.), as in `(TheSetOf ?X (and (isa ?X Integer) (greaterThan ?X 42)))', or (b) extensionally specified by enumerating its elements via TheSet (q.v.), as in `(TheSet 3 4 5)'; see also ThePartition and TheCovering.", 'UniversalVocabularyMt', vStrDef).
 7932exactlyAssertedEL_next(comment, 'September', "A specialization of CalendarMonth.  Each instance of September is the ninth month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7933exactlyAssertedEL_next(comment, 'SententialRelation', "A collection of mathematical objects.  Each instance of SententialRelation is by definition either a LogicalConnective or a Quantifier.", 'UniversalVocabularyMt', vStrDef).
 7934exactlyAssertedEL_next(comment, 'ScopingRelation', "A specialization of Relation whose instances are used to determine a \"scope\" with respect to one or more variables and to bind any free occurrences of those variables that are inside that scope.  Each instance of ScopingRelation takes as its arguments (at least) a variable or list of variables (see CycLVariable and CycLVariableList) and a formula (see CycLExpression-Assertible).  The former argument is the scoping relation's \"scoping\" argument (see scopingArg), and the latter its \"scoped formula\" argument (see scopedFormulaArg).\n<p>\nSyntactically, the formula (SCOPINGRELN VAR SENT) might either be a sentence or a non-atomic term (see CycLNonAtomicTerm), depending on which ScopingRelation it is built from.  Suppose for simplicity that the sentence SENT itself contains no ScopingRelation expressions, so that any variables occurring in SENT are not bound (i.e. they are _free_).  Then, in the formula (SCOPINGRELN VAR SENT), the _scope_ of the occurrence of the term SCOPINGRELN is SENT, and any free occurrence of the variable VAR in SENT is said to be _bound_ by that occurrence of SCOPINGRELN, and thus is bound (and hence not free) with respect to the entire formula.  (The occurrence of VAR immediately to the right of SCOPINGRELN is also considered bound with respect to the entire formula.)\n<p>\nSemantically, if the formula (SCOPINGRELN VAR SENT) is _closed_ (i.e. if it contains no free occurrence of any variable), then it will in some sense be \"about\" the value(s) of VAR that satisfy SENT.  That is, if (SCOPINGRELN VAR SENT) is a closed sentence it will state something about those values, while if (SCOPINGRELN VAR SENT) is a closed NAT it will (purport to) denote something related to those values.  For an example of the former case see thereExists; for the latter case see TheSetOf.  (If there are no free occurrences of VAR inside SENT, then (SCOPINGRELN VAR SENT) is a \"vacuous\" application of SCOPINGRELN that means exactly what SENT means.)\n<p>\nInstances of ScopingRelation include all of the Quantifiers and Lambda.", 'UniversalVocabularyMt', vStrDef).
 7935exactlyAssertedEL_next(comment, 'ScalarPointValue', "A specialization of ScalarInterval (q.v.).  Each instance of ScalarPointValue is a specific number or quantity, as opposed to a range of numbers or quantities (cf. ScalarProperInterval).  Instances of ScalarPointValue include all reals numbers and other Number-Generals (q.v.), as well as specific instances of Quantity such as (Meter 3) and (SecondsDuration 10).", 'UniversalVocabularyMt', vStrDef).
 7936exactlyAssertedEL_next(comment, 'ScalarInterval', "A specialization of TupleOfIntervals (q.v.).  Roughly put, this is the collection of all things that can be ranked according to some one-dimensional scale.  Instances of ScalarInterval are numbers or quantities possessing only sign and magnitude.  They are construed as <i>one-tuples</i> (see Tuple) of intervals.  They are to be contrasted with VectorIntervals (q.v.), which possess a direction as well as a magnitude, and are construed as two-membered tuples of intervals.\n<p>\nScalarInterval is partitioned into the two collections NumericInterval (which is the collection of numbers and number-ranges of all kinds) and Quantity (qq.v).  A Quantity is usually specified with a numeric-interval, as with (Meter 3)), but it might also be given in a generically-ranked way, as with (HighAmountFn Happiness); see the specializations MeasurableQuantity and NonNumericQuantity.  The magnitude of a scalar might be given by a specific number (see ScalarPointValue) or by a proper range of numbers (see ScalarProperInterval).\n<p>\nNote that the instances of MathematicalFunctionOnScalars (q.v.), which include artithmetic functions such as addition (see PlusFn) and division (see QuotientFn), are defined broadly so as to apply not only to numbers, but to (numerically-measured) scalar intervals generally.  Thus (PlusFn (Meter 3) (Meter 5)) is equal to (Meter 8).", 'UniversalVocabularyMt', vStrMon).
 7937exactlyAssertedEL_next(comment, 'ScalarIntegralValue', "A specialization of ScalarPointValue (q.v.).  Each instance of ScalarIntegralValue is either an Integer or a MeasurableQuantity  (q.v.) that is the value returned when some UnitOfMeasure (q.v.) function is applied to an Integer.  In the latter case, the quantity is said to be \"integral with respect to\" that unit-of-measure (see integralWRTUnit).\n<p>\nFor example, both 6 and (Inch 6) are scalar integral values.  The latter is integral with respect to Inch.\n<p>\nScalarIntegralValues are the admitted arguments for, and the values returned by, GreatestCommonDivisorFn and LeastCommonMultipleFn (qq.v.).\n<p>\nNote that, despite appearances to the contrary, (Foot-UnitOfMeasure 0.5) is a scalar integral value that is integral with respect to Inch, as it is equal to the scalar integral (Inch 6).  It might even be argued that, in principle, <i>every</i> MeasurableQuantity is integral with respect to some (reified or not) unit-of-measure or other.  But that is a contentious issue on which we need not take sides.", 'UniversalVocabularyMt', vStrMon).
 7938exactlyAssertedEL_next(comment, 'Saturday', "A collection of CalendarDays and an \ninstance of DayOfWeekType.  Saturday is the collection of all \n(and only) saturdays.", 'UniversalVocabularyMt', vStrMon).
 7939exactlyAssertedEL_next(comment, 'RuleTemplate', "Terms denoting formulas (typically without support for efficient inference) that can be (partially) instantiated as Cyc assertions (typically with support for efficient inference); see trueRule and ruleTemplateAssertion.", 'UniversalVocabularyMt', vStrMon).
 7940exactlyAssertedEL_next(comment, 'RoundUpFn', "An instance of EvaluatableFunction.  When applied to an instance INTERVAL of ScalarInterval, RoundUpFn returns an instance ROUNDED-INTERVAL of ScalarInterval in which the minimum and maximum ranges of INTERVAL have been rounded upwards to integer values.  For example, (RoundUpFn (Meter 2.5 5.2)) is (Meter 3 6).", 'UniversalVocabularyMt', vStrDef).
 7941exactlyAssertedEL_next(comment, 'RoundDownFn', "(RoundDownFn QUANTITY) converts QUANTITY into one where the maximum and minimum ranges have been rounded downwards to integer values.  For example, (RoundDownFn (Meter 2.5)) denotes (Meter 2).", 'UniversalVocabularyMt', vStrDef).
 7942exactlyAssertedEL_next(comment, 'RoundClosestFn', "(RoundClosestFn QUANTITY) converts QUANTITY into one where the maximum and minimum ranges have been rounded to the closest integer values.  For example,  (RoundClosestFn (Meter 2.41)) denotes (Meter 2),  (RoundClosestFn (Meter 2.7)) denotes (Meter 3), and (RoundClosestFn (Meter 1.6 4.2)) denotes  (Meter 2 4). If QUANTITY is exactly between two integers (that is, in the form integer+0.5), then it is rounded to the one that is even. So, (RoundClosestFn (Meter 2.5)) denotes (Meter 2), and (RoundClosestFn (Meter 7.5)) denotes (Meter 8). See also RoundUpFn, RoundDownFn.", 'UniversalVocabularyMt', vStrDef).
 7943exactlyAssertedEL_next(comment, 'RemovalModuleSupportedPredicate-Specific', "The collection of all Predicates which are supported by some CycRemovalModule-Specific.  Sentences of the form (PRED . ARGS), where PRED is an instance of RemovalModuleSupportedPredicate-Specific, have special inference support.", 'UniversalVocabularyMt', vStrMon).
 7944exactlyAssertedEL_next(comment, 'RemovalModuleSupportedPredicate-Generic', "The collection of all Predicates which are supported by some CycRemovalModule-Generic.  An assertion of the form (PRED . ARGS), where PRED is an instance of RemovalModuleSupportedPredicate-Generic, may affect the provability of sentences other than just sentences whose predicate is PRED.  This is what is meant by 'generic' in this sense.", 'UniversalVocabularyMt', vStrMon).
 7945exactlyAssertedEL_next(comment, 'RemovalModuleSupportedCollection-Generic', "The collection of all Collections which are supported by some CycRemovalModule-Generic.  An assertion of the form (isa INS COL), where COL is an instance of RemovalModuleSupportedCollection-Generic, may affect the provability of sentences that do not mention COL explicitly.  In particular, it may affect the provability of sentences mentioning INS.", 'UniversalVocabularyMt', vStrMon).
 7946exactlyAssertedEL_next(comment, 'RelaxArgTypeConstraintsForVariables', "A CanonicalizerDirective  (q.v.) that directs the CycCanonicalizer (specifically, the  CycWellFormednessChecker) to relax the argument-type constraints it usually imposes on variables.  For example, this canonicalizer directive  would allow the sentence `(and (isa ?X Collection) (isa ?X Individual))'  to be admitted, though it would otherwise be rejected as ill-formed due to  the mutually disjoint argument-type constraints (see ArgTypePredicate) on the positions occupied by the two occurrences of the variable `?X'.", 'CoreCycLImplementationMt', vStrDef).
 7947exactlyAssertedEL_next(comment, 'RelationInstanceExistsFn', "(relationInstanceExists PRED THING COLL) says that THING stands in the relation PRED to some (not necessarily known) instance of the Collection COLL. (RelationInstanceExistsFn PRED THING COLL) denotes this instance of COLL.", 'UniversalVocabularyMt', vStrMon).
 7948exactlyAssertedEL_next(comment, 'RelationExistsInstanceFn', "(relationExistsInstance PRED COLL THING) says that some (not necessarily known) instance INS of the Collection COLL stands in the relation PRED to THING. (RelationExistsInstanceFn PRED COLL THING) denotes INS.", 'UniversalVocabularyMt', vStrMon).
 7949exactlyAssertedEL_next(comment, 'RelationExistsAllFn', "The predicate relationExistsAll states that for every instance of a collection, some other term exists in a certain relationship.  An arbitrary such term is a function of the instance, the predicate, the collection, and the type of the other term.  (RelationExistsAllFn TERM PRED DEP-COL INDEP-COL) allows one to denote this `arbitrary such term that so exists' in a named fashion.", 'UniversalVocabularyMt', vStrMon).
 7950exactlyAssertedEL_next(comment, 'RelationAllExistsFn', "An IndeterminateTermDenotingFunction (q.v.) that is closely related to relationAllExists.  If both (relationAllExists PRED INDEP-COL DEP-COL) and (isa INDEP-INS INDEP-COL) hold,  then (PRED INDEP-INS (RelationAllExistsFn INDEP-INS PRED INDEP-COL DEP-COL) also holds.  Thus the term '(RelationAllExistsFn INDEP-INS PRED INDEP-COL DEP-COL)' \"indeterminately denotes\" some instance of DEP-COL that is related to INDEP-INS by PRED.  For instance, since (relationAllExists citizens Country Person) and (isa Malaysia Country) both hold, so does (citizens Malaysia (RelationAllExistsFn Malaysia citizens Country Person)).", 'UniversalVocabularyMt', vStrMon).
 7951exactlyAssertedEL_next(comment, tRelation, "A specialization of MathematicalObject and the collection of all relations.  Each instance of Relation is a relation that can hold among one or more things, depending on whether the relation is unary, binary, ternary, or whatever (see arity and relationalArity).  A unary relation (such as unknownSentence) is a sort of degenerate case that holds of  certain individual things (in this case, all sentences that are unknown to Cyc).  A binary relation (such as likesAsFriend) relates one thing to another (in this case, it relates one sentient animal to another just in case the first likes the second).  A ternary relation relates certain triples of things.  And so on.  There are also relations of no particular fixed arity; see VariableArityRelation.\n<p>\nNames of relations can be used to construct sentences and other formulas.  More precisely, CycL terms that denote Relations can appear in the \"0th\" argument (or \"arg0\") position of a CycLFormula (q.v.), i.e. as the term immediately following the formula's opening parenthesis.\n<p>\nAn important subcollection of Relation is TruthFunction (q.v.), whose instances are intimately related to truth-values, as reflected in the fact that the CycL expressions that denote truth-functions can appear in the arg0 position of a CycLSentence; and a sentence (if quantificationally closed; see CycLClosedSentence), will generally be either true or false (with respect to a given context or interpretation).  The major subcollections of TruthFunction are Predicate, LogicalConnective, and Quantifier (qq.v.).\n<p>\nAnother important subcollection of Relation is Function-Denotational (q.v.), the collection of all functions.  A CycL term that denotes a function can appear in the arg0 position of a CycLNonAtomicTerm (q.v.).\n<p>\nSee also relationExtension and relationHoldsAmong.", 'UniversalVocabularyMt', vStrDef).
 7952exactlyAssertedEL_next(comment, 'ReifiableFunction', "A specialization of Function-Denotational.   Each instance of ReifiableFunction is denoted by a CycL constant that can stand in the 0th (or \"arg0\") position in a CycLReifiableNonAtomicTerm  (q.v.).  For example, GovernmentFn is a reifiable function, so the term  `(GovernmentFn France)' is a reifiable non-atomic term (or \"NAT\").   And since this particular term actually _is_ reified in the Cyc Knowledge  Base, it is, more specifically, a CycLNonAtomicReifiedTerm (or \"NART\").   The NART `(GovernmentFn France)' is treated more or less the same as if  it were a CycL constant (named, say, `GovernmentOfFrance').  Similary, the constant for GovernmentFn can be applied to the constant (or other  reified or reifiable term) for _any_ instance of GeopoliticalEntity to form a reifiable NAT that denotes that region's government; and should this NAT appear in a sentence that is asserted to the KB, it will thereby become a NART. Note, however, that not all NATs are such that it is desireable that  they should become reified (i.e. become NARTs) if they appear in  assertions; for more on this see UnreifiableFunction.", 'UniversalVocabularyMt', vStrDef).
 7953exactlyAssertedEL_next(comment, 'ReformulatorIrrelevantFORT', "The collection of Cyc FORTs that are not relevant to the reformulator.", 'UniversalVocabularyMt', vStrMon).
 7954exactlyAssertedEL_next(comment, 'ReformulatorHighlyRelevantFORT', "The collection of Cyc FORTs that are highly relevant to the reformulator.", 'UniversalVocabularyMt', vStrMon).
 7955exactlyAssertedEL_next(comment, 'ReformulatorHighlyRelevantFORT', "The collection of Cyc FORTs that are highly relevant to the reformulator.           An example of such a FORT would be one that is referenced in a large           number of reformulator rules in the KB (see intances of            CycLReformulationRulePredicate).", 'UniversalVocabularyMt', vStrMon).
 7956exactlyAssertedEL_next(comment, 'ReformulatorDirectivePredicate', "The collection of Predicates which can affect the\nbehaviour of the CycLReformulator or its submodules.  When\nreformulator directive GAFs are asserted, they are only relevant to\nthe reformulator when it is reformulating expressions in the\nmicrotheory in which the directive is asserted, or a specMt thereof.", 'UniversalVocabularyMt', vStrMon).
 7957exactlyAssertedEL_next(comment, 'ReformulationNeitherDirection', "A meta-property of a CycLReformulatorDirective,\nmeaning that no arg is to be interpreted as either the 'from' or 'to' arg.\nSee reformulationDirectionInMode for how this\ndirection can be used.", 'BaseKB', vStrMon).
 7958exactlyAssertedEL_next(comment, 'ReformulationForwardDirection', "A meta-property of a CycLReformulatorDirective, meaning\nthat there exist two arguments in the directive such that the\nlower-numbered arg (e.g. arg1 for a binary predicate) is the 'from'\narg, the input to the reformulator, and that the higher-numbered arg\n(e.g. arg2 for a binary predicate) is the 'to' arg, the output of the\nreformulator.  Its semantics are more fully determined by context.\nThis is the default preferredReformulationDirection for\nreformulatorRules.  See reformulationDirectionInMode for how this\ndirection can be used.", 'BaseKB', vStrMon).
 7959exactlyAssertedEL_next(comment, 'ReformulationBackwardDirection', "A meta-property of a CycLReformulatorDirective, meaning\nthat there exist two arguments in the directive such that the\nhigher-numbered arg (e.g. arg2 for a binary predicate) is the 'from'\narg, the input to the reformulator, and that the lower-numbered arg\n(e.g. arg1 for a binary predicate) is the 'to' arg, the output of the\nreformulator.  Its semantics are more fully determined by context.\nSee reformulationDirectionInMode for how this\ndirection can be used.", 'BaseKB', vStrMon).
 7960exactlyAssertedEL_next(comment, 'ReflexiveBinaryPredicate', "The specialization of BinaryPredicate whose instances are reflexive relations.  A reflexive binary predicate relates anything that meets the predicate's argument constraints to that thing itself.  Typically, a reflexive predicate has precisely the same constraints on both of its argument-places.\n<p>\nMore precisely: a binary predicate <code>PRED</code> is an instance of ReflexiveBinaryPredicate if and only if both (i) for every <code>X</code> that satisfies the constraints on (i.e is an admittedArgument for) <i>both</i> argument-places of <code>PRED</code>, <code>(PRED X X)</code> holds and (ii) <code>PRED</code>'s two argument-places are \"co-satisfiable\" with respect to their (single-argument) type constraints (see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement).\n<p>\nInstances of ReflexiveBinaryPredicate include physicalParts, inRegion, genls, and equals.", 'UniversalVocabularyMt', vStrDef).
 7961exactlyAssertedEL_next(comment, 'RealNumber', "The collection of real numbers; a specialization of both  IntervalOnNumberLine and ScalarPointValue (qq.v.).  Each  instance of RealNumber is a single point on the real number  line, which has no upper or lower bounds.  Specializations  of this collection include Integer, RationalNumber, and  NegativeNumber.  Note that RealNumber is also a specialization  of ComplexNumber (q.v.), and any instance of the former  constitutes a degenerate case of the latter, in that the value  along the real's \"imaginary axis\" is zero (cf. ImaginaryNumber).", 'UniversalVocabularyMt', vStrDef).
 7962exactlyAssertedEL_next(comment, 'QuotientFn', "An instance of both BinaryFunction and EvaluatableFunction.  When applied to an instance DIVIDEND of ScalarInterval and an instance DIVISOR of ScalarInterval, QuotientFn returns an instance of ScalarInterval that is the result of dividing DIVIDEND by DIVISOR.  For example, (QuotientFn 24 6) is 4, (QuotientFn (Meter 3) (SecondsDuration 2)) is (MetersPerSecond 1.5) (i.e., 1.5 meters per second), and (QuotientFn (SecondsDuration 2) (Meter 3)) is ((PerFn SecondsDuration Meter) 0.6666666666666666) (i.e., 0.6666666666666666 seconds per meter).  Note that (QuotientFn DIVIDEND 0) is undefined for any instance DIVIDEND of ScalarInterval.", 'UniversalVocabularyMt', vStrDef).
 7963exactlyAssertedEL_next(comment, 'Quote', "The symbol 'Quote' is used in CycL as a device for referring to particular CycL expressions, in much the same way that quotation marks are often used in English in order to \"mention\" (rather than simply \"use\") an English word or phrase.  (And in much the same way that single-quotes are used in the preceding sentence in order to refer to a particular CycL symbol.)  If <code>EXPR</code> is a CycL expression, the term <code>(Quote EXPR)</code> -- formed by writing 'Quote' followed by <code>EXPR</code> and enclosing the result in parentheses -- is interpreted as denoting <code>EXPR</code> itself, as opposed to whatever it is (if anything) that <code>EXPR</code> ordinarily denotes (i.e. what it denotes when not inside the scope of <code>Quote</code> or in a quotedArgument position).  For example, while the CycL constant <code>Plato</code> denotes a certain Greek philosopher, the compound expression <code>(Quote Plato)</code> denotes the term <code>Plato</code> itself.  Similarly, the expression <code>(Quote <b>?X</b>)</code> denotes the variable <code><b>?X</b></code>, and the expression <code>(Quote (isa Plato Philosopher))</code> denotes the sentence <code>(isa Plato Philosopher)</code>.\n<p>\n<code>Quote</code> is also used in conjunction with the symbol <code>EscapeQuote</code> (q.v.), as a device for making <i>general</i> statements about CycL expressions.  Let <code>EXPR = (E<sub>1</sub>...E<sub>n</sub>)</code> be a well-formed CycL expression whose <b>n</b> immediate constituents are the CycL expressions <code>E<sub>1</sub></code>, ..., and <code>E<sub>n</sub></code> (where <b>n</b> >= 1).  The expression \n<pre>\n  (Quote EXPR) = (Quote (E<sub>1</sub>...E<sub>n</sub>))\n</pre> \n-- consisting of the symbols <code>Quote</code>, <code>EXPR</code>, and a surrounding pair of parentheses -- is a term that denotes <code>EXPR</code>.  The expression (call it <i><b>EQ</b></i>) \n<pre>\n  (Quote (E<sub>1</sub>...(EscapeQuote E<sub>i</sub>) ...E<sub>n</sub>)\n</pre> \n(where 1 <= <b>i <= n</b>) is a term whose meaning is similar to <code>(Quote EXPR)</code>, except that any free occurrence of a variable in <code>E<sub>i</sub></code> remains free with respect to <b>EQ</b> as a whole.  If <code>E<sub>i</sub></code> contains no free variables, then <b>EQ</b> is a closed term (see CycLClosedDenotationalTerm) that denotes <code>EXPR</code>, and is equivalent to <code>(Quote EXPR)</code>.  If <code>E<sub>i</sub></code> does contain free variables, then <b>EQ</b> is an open term (see CycLOpenDenotationalTerm) in which exactly the same variables occur free; and any closed instantiation of <b>EQ</b> denotes the corresponding instantiation of <code>EXPR</code>.  (A <i>closed instantiation</i> of an open expression is any <i>closed</i> expression that results from simultaneously replacing each free occurrence of a variable in the open expression with some closed term, replacing any two occurrences of the same variable by the same closed term.)\n<p>\nFor a simple example, the variable <code><b>?X</b></code> occurs free in the term\n<pre>\n  (Quote (EscapeQuote (MotherFn <b>?X</b>)) ;\n</pre>\nand one instantiation of this is the closed term\n<pre>\n  (Quote (EscapeQuote (MotherFn Plato)) ,\n</pre>\nwhich denotes the non-atomic term <code>(MotherFn Plato)</code>.  \n<p>\nFor a more interesting example, consider a case where <i>some but not all</i> of the free variables in a term are quoted.  In the expression\n<pre>\n  (Quote (loves (EscapeQuote <b>?X</b>) <b>?Y</b>))\n</pre>\nonly <code><b>?X</b></code> occurs free -- the <code><b>?Y</b></code> is quoted. Thus this instantiation of the above:\n<pre>\n  (Quote loves (EscapeQuote Plato) <b>?Y</b>)\n</pre>\nis a closed term that denotes the <i>open</i> formula <code>(loves Plato <b>?Y</b>)</code>.  \n<p>\nNote that the sort of quotation done in the first example above can also be done -- and done more elegantly -- using just QuasiQuote instead of Quote and EscapeQuote.  But the sort of quotation done in the second example cannot be accomplished with QuasiQuote.\n<p>\nSee also QuasiQuote, EscapeQuote, denotes, quotedIsa, quotedArgument, NoteAboutQuotingInCycL, and NoteAboutSyncategorematicSymbols.", 'UniversalVocabularyMt', vStrMon).
 7964exactlyAssertedEL_next(comment, 'QuintaryRelation', "The collection of all fixed-arity relations of arity 5 (see arity).  The most notable specializations of QuintaryRelation are QuintaryPredicate and QuintaryFunction (qq.v.).", 'UniversalVocabularyMt', vStrMon).
 7965exactlyAssertedEL_next(comment, 'QuintaryPredicate', "A specialization of Predicate and QuintaryRelation.  QuintaryPredicate is the collection of all predicates whose arity (see arity) is 5.", 'UniversalVocabularyMt', vStrDef).
 7966exactlyAssertedEL_next(comment, 'QuintaryFunction', "A specialization of both QuintaryRelation and Function-Denotational. An instance of Function-Denotational FUNC is an instance of QuintaryFunction if and only if FUNC has an arity of 5.", 'UniversalVocabularyMt', vStrDef).
 7967exactlyAssertedEL_next(comment, 'QueryMt', "The instance of IndexicalConcept used specifically for referring to 'the microtheory in which this particular query is being run'.  This allows for a certain amount of reflection in queries, since it allows one to pose a query about the Microtheory of the very same Ask.  It is useful for cases where one wants to obtain certain facts about the context of an Ask without specifying anything more about that context.", 'BaseKB', vStrMon).
 7968exactlyAssertedEL_next(comment, 'QuaternaryRelation', "The collection of all fixed-arity relations of arity 4 (see arity).  The most notable specializations of QuaternaryRelation are QuaternaryPredicate and QuaternaryFunction (qq.v.).", 'UniversalVocabularyMt', vStrMon).
 7969exactlyAssertedEL_next(comment, 'QuaternaryPredicate', "A specialization of both QuaternaryRelation and Predicate.   QuaternaryPredicate is the collection of all predicates whose arity (see arity) is 4.", 'UniversalVocabularyMt', vStrDef).
 7970exactlyAssertedEL_next(comment, 'QuaternaryFunction', "A specialization of both FixedArityFunction and QuaternaryRelation (qq.v.).  Each instance of QuaternaryFunction is a function that always takes four arguments at a time, i.e. has the arity (see arity) 4.", 'UniversalVocabularyMt', vStrMon).
 7971exactlyAssertedEL_next(comment, 'QuasiQuote', "A quotation device for making general statements about CycL expressions.  QuasiQuote allows for any free variables occurring inside an expression to which it is applied to \"escape\" (i.e. remain free with respect to) the quotation.  It is thus similar in function to, though less flexible than, the combination of Quote and EscapeQuote (qq.v.).\n<p>\nTo be more precise: the syncategorematic symbol <code>QuasiQuote</code> is a device for allowing genuinely free variables to occur inside quoted expressions, in order that one may meaningfully \"quantify into\" such expressions and thereby <i>generalize</i> over them.  It can thus be instructively compared to the symbol <code>Quote</code> (q.v.), which is used to make statements about <i>particular</i> CycL expressions.  Let <code>EXPR</code> be a well-formed CycL expression.  The expression <code>(Quote EXPR)</code> -- consisting of the symbols <code>Quote</code>, <code>EXPR</code>, and a surrounding pair of parentheses -- is a term that denotes <code>EXPR</code>.  The expression <code>(QuasiQuote EXPR)</code> is a term whose meaning is similar to <code>(Quote EXPR)</code>, except that any free occurrence of a variable in <code>EXPR</code> remains free with respect to <code>(QuasiQuote EXPR)</code> as a whole.  If <code>EXPR</code> contains no free variables, then <code>(QuasiQuote EXPR)</code> is a closed term (see CycLClosedDenotationalTerm) that denotes <code>EXPR</code>, and is equivalent to <code>(Quote EXPR)</code>.  If <code>EXPR</code> contains any free occurrences of variables, then <code>(QuasiQuote EXPR)</code> is an open term (see CycLOpenDenotationalTerm) in which exactly the same variables occur free; and any closed instantiation of <code>(QuasiQuote EXPR)</code> denotes the corresponding instantiation of <code>EXPR</code>.  (A <i>closed instantiation</i> of <code>EXPR</code> is any closed expression that results from replacing each free occurrence of a variable in <code>EXPR</code> with some closed term, and replacing any two occurrences of the same variable by the same closed term.)\n<p>\nFor an example, the variable <code>?X</code> occurs free in the term\n<pre>\n  (QuasiQuote (MotherFn ?X)) ;\n</pre>\nand one instantiation of this is the closed term\n<pre>\n  (QuasiQuote (MotherFn Plato)) ,\n</pre>\nwhich denotes the non-atomic term <code>(MotherFn Plato)</code>.  And the (implicitly quantified) rule\n<pre>\n  (isa (QuasiQuote (MotherFn ?X)) CycLNonAtomicTerm)\n</pre>\nmeans, in effect, that any closed instantiation of the open term <code>(MotherFn ?X)</code> -- e.g. <code>(MotherFn Plato)</code> -- is a non-atomic term of CycL.\n<p>\nSee also denotes, quotedIsa, quotedArgument, NoteAboutQuotingInCycL, and NoteAboutSyncategorematicSymbols.", 'UniversalVocabularyMt', vStrMon).
 7972exactlyAssertedEL_next(comment, 'QuantityConversionFn', "(QuantityConversionFn UNIT QUANTITY) converts QUANTITY into an equivalent quantity expressed using UNIT as the unit of measure.  For example, (QuantityConversionFn Inch (Foot-UnitOfMeasure 2)) denotes (Inch 24).", 'UniversalVocabularyMt', vStrDef).
 7973exactlyAssertedEL_next(comment, 'Quantifier', "A specialization of SententialRelation and ScopingRelation (qq.v.).  Each instance of Quantifier takes as its arguments (at least) a variable (see CycLVariable) and a sentence (see CycLSentence-Assertible), and is used to make a certain kind of generic quantitative statement regarding the things that satisfy the sentence.  Typically, the variable VAR will occur free in the sentence SENT, and in the quantified sentence (QUANT VAR SENT ...) these occurrences of VAR are bound by that occurrence of QUANT.  (If VAR does not occur free in SENT, then the quantified sentence is a \"vacuous quantification\" that is equivalent to SENT by itself.  For the definitions of 'free' and 'bound' occurrences of variables, see ScopingRelation.)  For example, '(thereExists ?X (isa ?X Dog))' means that there exists at least one dog.  Other instances of Quantifier are forAll, thereExistExactly, thereExistAtLeast, and thereExistAtMost.", 'UniversalVocabularyMt', vStrDef).
 7974exactlyAssertedEL_next(comment, 'ProblemSolvingCntxt', "A specialization of Microtheory.\nProblemSolvingCntxts are microtheories that are used to reason about \nparticular situations.  Queries posed in ProblemSolvingCntxts are\nexpected to draw -- via the genlMt relation -- on a large number\nof other microtheories.  A ProblemSolvingCntxt is usually created \nfor temporary use with a problem at hand, and is discarded after the \nproblem is dealt with.  In contrast, a GeneralMicrotheory (q.v.), e.g., \nis created for lasting use.  Specializations of ProblemSolvingCntxt \ninclude ParsingContext and ScenarioTestingMicrotheory.", 'UniversalVocabularyMt', vStrMon).
 7975exactlyAssertedEL_next(comment, 'prettyString-Canonical', "(prettyString TERM STRING) means that STRING is the English word or expression (sequence of words) commonly used to refer to TERM.  The predicate prettyString is used by the code which generates CycL to English paraphrases, but its applicability is not restricted to this use.", 'UniversalVocabularyMt', vStrDef).
 7976exactlyAssertedEL_next(comment, 'PredicateTypeByArity', "A collection of collections.  Each instance of PredicateTypeByArity is a collection of Predicates having the same arity.  Instances include UnaryPredicate, BinaryPredicate, and TernaryPredicate.", 'UniversalVocabularyMt', vStrDef).
 7977exactlyAssertedEL_next(comment, tPred, "A specialization of TruthFunction (q.v.).  Each instance of Predicate is either a property of things (see UnaryPredicate) or a relationship holding between two or more things.  Like other truth-functions, predicates, or rather the expressions that represent or denote them, are used to form sentences.  More precisely, any CycL expression that denotes an instance of Predicate (and only such an expression) can appear in the \"0th\" (or \"arg0\") position (i.e. as the term following the opening parenthesis) of a CycLAtomicSentence (q.v.).  Important specializations of Predicate include UnaryPredicate, BinaryPredicate, TernaryPredicate, QuaternaryPredicate, and QuintaryPredicate.  Note that, despite its name, Predicate is a collection of <i>relations</i>, and not a collection of expressions that represent or denote such relations.", 'UniversalVocabularyMt', vStrDef).
 7978exactlyAssertedEL_next(comment, 'PositiveInteger', "A specialization of Integer.  An instance INT of Integer is an instance of PositiveInteger just in case INT is an integer greater than 0.", 'UniversalVocabularyMt', vStrDef).
 7979exactlyAssertedEL_next(comment, 'PlusFn', "A variable-arity MathematicalFunctionOnScalars that is an extension of the arithmetical operation of addition to measurable ScalarIntervals (q.v.) generally.  Where  <code>ADDEND1</code>, ..., and <code>ADDENDn</code> are pairwise numericallyComparable (q.v.), <code>(PlusFn ADDEND1 ... ADDENDn)</code> is the arithmetic sum of <code>ADDEND1</code>, ..., and <code>ADDENDn</code>.  For example, (PlusFn 2 3 4) is 9, and (PlusFn (Meter 1.5) (Meter 0.7)) is (Meter 2.2).\n<p>\nNote that the term <code>(PlusFn ADDEND1 ... ADDENDn)</code> is undefined if there are <code>ADDENDi</code> and <code>ADDENDj</code> (1 <code><= i,j <= n)</code> that are not comparable.  For example, <code>(PlusFn (MinutesDuration 1) (Meter 3))</code> is undefined, since (MinutesDuration 1) is a Time-Quantity and (Meter 3) is a Distance, and time-quantities are not comparable with distances.\n<p>\nFor subtraction, see DifferenceFn.", 'UniversalVocabularyMt', vStrDef).
 7980exactlyAssertedEL_next(comment, 'PlusAll', "A NumericQuantifier function that takes a SetOrCollection and a UnaryFunction as its arguments. (PlusAll <b>SETORCOL FUNC</b>) is the result of adding up the results of successively applying <b>FUNC</b> to each element of <b>SETORCOL</b>.  For example:\n<pre>\n    (PlusAll (TheSet 4 9) SquareRootFn)\n  = (PlusFn (SquareRootFn 4) (SquareRootFn 9))\n  = (PlusFn 2 3)\n  = 5.", 'UniversalVocabularyMt', vStrDef).
 7981exactlyAssertedEL_next(comment, 'PerFn', "A binary UnitOfMeasureDenotingFunction (q.v.) that takes two UnitOfMeasure (q.v.) functions and returns a UnitOfRatio (q.v.) composed of them.  <code>(PerFn UNIT1 UNIT2)</code> is a unit <code>RATIO-FN</code> for measuring the ratio of <code>UNIT1</code> units to <code>UNIT2</code> units.   That is, for any number or other NumericInterval <code>NUM</code>, <code>(RATIO-FN NUM)</code> = <code>(QuotientFn (UNIT1 NUM) (UNIT2 1))</code>.\n<p>\nFor example, (PerFn Meter SecondsDuration) is a UnitOfSpeed function that measures meters-per-second.  When applied to (e.g.) the integer 20, this unit-of-speed returns the particular Speed equal to\n<pre>\n  (QuotientFn (Meter 20) (SecondsDuration 1))\n</pre>\nor 20 meters-per-second.\n<p>\nNote that <code>UNIT1</code> and <code>UNIT2</code> must <i>not</i> be interconvertibleUnits (q.v.), or <code>(PerFn UNIT1 UNIT2)</code> is undefined.  Otherwise, <code>UNIT1</code> and <code>UNIT2</code> would effectively \"cancel each other out\", and the value returned by PerFn for those arguments would not be a UnitOfRatio.\n<p>\nSee also UnitProductFn.", 'UniversalVocabularyMt', vStrDef).
 7982exactlyAssertedEL_next(comment, 'Percent', "A variable-arity MathematicalFunctionOnScalars (q.v.).  When applied to a number or other NumericInterval (pair of numeric-intervals), Percent returns the instance of IntervalOnNumberLine that is its argument (the interval between its two arguments) divided by 100.  For example (Percent 110) is 1.1, and (Percent 10 20) is (Unity 0.1 0.2): the interval between 0.1 and 0.2 inclusive.", 'UniversalVocabularyMt', vStrDef).
 7983exactlyAssertedEL_next(comment, 'PartiallyCommutativeRelation', "An instance of RelationTypeByLogicalFeature (q.v.) and a specialization of AtLeastPartiallyCommutativeRelation.  Each instance  of PartiallyCommutativeRelation <code>PARTCOMRELN</code> is a predicate or function that is commutative in some, but not all, of its argument-places (see  commutativeInArgs).  More precisely, suppose for example that <code>PARTCOMRELN</code> is a predicate (function) that is commutative only in its odd-numbered  argument-places, and that <code>PARTCOMRELN</code> holds among (has the value <code>VAL</code> for) a given sequence of arguments <code>SEQ</code>.  It follows that <code>PARTCOMRELN</code> also holds among (has the same value <code>VAL</code> for) any other sequence <code>SEQ-PRIME</code> obtainable from <code>SEQ</code> by permuting some or all of the odd-numbered members of <code>SEQ</code> while keeping all of its even-numbered members fixed.\n<p>\nNote that <code>PARTCOMRELN</code> must  have an arity (see arity) of at least three and <i>cannot</i> be an instance of CommutativeRelation (as any instance of the latter is commutative in <i>all</i> of its argument-places).\n<p>\nInstances of PartiallyCommutativeRelation include pathsJoinAt, formsBorderBetween, and BlockOfStreetBetweenFn.", 'UniversalVocabularyMt', vStrDef).
 7984exactlyAssertedEL_next(comment, 'October', "A specialization of CalendarMonth.  Each instance of October is the tenth month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7985exactlyAssertedEL_next(comment, 'November', "A specialization of CalendarMonth. Each instance of November is the eleventh month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 7986exactlyAssertedEL_next(comment, 'NonNegativeScalarInterval', "A specialization of ScalarInterval.  An instance INTERVAL of ScalarInterval is also an instance of NonNegativeScalarInterval just in case INTERVAL is a non-negative number or quantity.  Instances of NonNegativeScalarInterval include all instances of NonNegativeNumber (q.v.), as well as non-negative quantities such as (Meter 212), (Kilogram 5), and (SecondsDuration 0).", 'UniversalVocabularyMt', vStrDef).
 7987exactlyAssertedEL_next(comment, 'NonNegativeInteger', "NonNegativeInteger is the sub-collection of Integer that excludes the negative integers.  Each instance of NonNegativeInteger is a whole number greater than or equal to zero -- for example, 0, 1, 2, 3, ....", 'UniversalVocabularyMt', vStrDef).
 7988exactlyAssertedEL_next(comment, 'Multigraph', "An instance of PathSystemType-Structural and a subcollection of PathSystem.  Each instance of Multigraph is an instance of PathSystem in which the only points are nodes in the system and all paths are made of links (i.e., no intermediate points along links). Sometime such a system is called a graph or multi-graph in graph theory.  A Multigraph consists of nodes interconnected by links, with loops on single nodes allowed, and with multiple links between the same two nodes also allowed.  (For a graph with no parallel links and no loops, see SimpleGraph-GraphTheoretic.", 'UniversalVocabularyMt', vStrDef).
 7989exactlyAssertedEL_next(comment, 'MtUnionFn', "(MtUnionFn . MTS) denotes the ProblemSolvingCntxt where each of MTS and all of their genlMts are relevant.  This microtheory effectively contains all of the assertions from all of MTS, regardless of any contradictions.", 'UniversalVocabularyMt', vStrMon).
 7990exactlyAssertedEL_next(comment, 'MtTimeWithGranularityDimFn', "An unreifiable BinaryFunction that takes a TimeInterval and a TimeParameter and returns a TemporalMicrotheory.  <code>(ist (MtTimeWithGranularityDimFn INTERVAL PAR) ASSERTION)</code> holds just in case <code>ASSERTION</code> holds at <code>INTERVAL</code> to granularity <code>PAR</code>.  See also MtTimeDimFn.", 'UniversalVocabularyMt', vStrMon).
 7991exactlyAssertedEL_next(comment, 'MtTimeDimFn', "An unreifiable UnaryFunction that takes a TimeInterval and returns a TemporalMicrotheory.  <code>(ist (MtTimeDimFn INTERVAL) ASSERTION)</code> holds just in case <code>ASSERTION</code> holds at <code>INTERVAL</code> to granularity Null-TimeParameter.  See also MtTimeWithGranularityDimFn.", 'UniversalVocabularyMt', vStrMon).
 7992exactlyAssertedEL_next(comment, 'MtSpace', "(MtSpace MT-1 ... MT-N) denotes the microtheory whose set of domain assumptions is the union of the assertions true in each of MT-1 ... MT-N. Consequently, (MtSpace MT-1 ... MT-N) has each of MT-1 ... MT-N as one of its genlMts. Typically, but not always, there will be assertions true in (MtSpace MT-1 ... MT-N) that are not true in any of its genlMts. For example,\n<p>\n(MtSpace WorldHistoryMt (MtDim mtTimeIndex (YearFn 1790)))\n<p>\ndenotes the microtheory whose domain assumption are precisely those of the WorldHistoryMt (whose basic assumption is that we are in the context of actual world history) and those of the microtheory (MtDim mtTimeIndex (YearFn 1790)) (whose basic assumption is that 1790 is the present year -- see MtDim). The conjunction of these domain assumptions implies everything that is true in real world history in the year 1790. For example, these domain assumptions imply that (president UnitedStatesOfAmerica GeorgeWashington) is true. Consequently, this assertion is true in (MtSpace WorldHistoryMt (MtDim mtTimeIndex (YearFn 1790))).", 'UniversalVocabularyMt', vStrMon).
 7993exactlyAssertedEL_next(comment, 'MonthOfYearType', "A collection of Collections.\nInstances of MonthOfYearType are the canonical subcollections of CalendarMonth.  There are twelve of these in the JulianCalendar; for example, September is the collection of all Septembers.", 'UniversalVocabularyMt', vStrDef).
 7994exactlyAssertedEL_next(comment, 'MonotonicallyTrue', "An instance of CycHLTruthValue.  MonotonicallyTrue is the attribute of being indefeasibly true.", 'BaseKB', vStrDef).
 7995exactlyAssertedEL_next(comment, 'MonotonicallyFalse', "An instance of CycHLTruthValue.  MonotonicallyFalse is the attribute of being indefeasibly false.", 'BaseKB', vStrDef).
 7996exactlyAssertedEL_next(comment, 'Monday', "A collection of CalendarDays and an \ninstance of DayOfWeekType.  Monday is the collection of all \n(and only) mondays.", 'UniversalVocabularyMt', vStrMon).
 7997exactlyAssertedEL_next(comment, 'ModuloFn', "A binary function that takes a scalar and a comparable (non-null) point-value scalar to another comparable scalar, ModuloFn is a generalization of a basic notion of modular arithmetic, broadened to apply to ScalarIntervals of all sorts.\n<p>\n(ModuloFn <code>SCALAR BASE</code>) is the value of <code>SCALAR</code> modulo <code>BASE</code>, determined as follows.  (i) If <code>SCALAR</code> and <code>BASE</code> are both positive or both negative values, <code>SCALAR-MOD-BASE</code> is the remainder left when <code>BASE</code> is successively subtracted from <code>SCALAR</code> (zero or more times) until the result is a value that is closer to the comparable null-value (see ScalarNullValue) than <code>BASE</code> is.  (ii) If <code>SCALAR</code> and <code>BASE</code> differ in their numeric signs, <code>SCALAR-MOD-BASE</code> is the remainder left when <code>BASE</code> is successively <i>added</i> to <code>SCALAR</code> (zero or more times) until the result is a value <i>whose numeric sign agrees with that of</i> <code>BASE</code> or is null, and which is closer to the comparable null-value than <code>BASE</code> is.  (iii) If <code>SCALAR</code> is already a null-value, <code>SCALAR-MOD-BASE</code> is just <code>SCALAR</code> itself.  \n<p>\nFor example, (ModuloFn 8 3) = 2, (ModuloFn (Meter 9) (Meter -4)) = (Meter -3), and (ModuloFn (Inch -12) (Inch -4)) = (Inch 0).\n<p>\nNote that in case (i) above, if the absolute value of <code>SCALAR</code> is any value lessThan the absolute value of <code>BASE</code>, <code>SCALAR-MOD-BASE</code> is equal to <code>SCALAR</code>.  In all cases, if <code>SCALAR</code> numericallyEquals <code>BASE</code>, <code>SCALAR-MOD-BASE</code> is the comparable null-value.  In all cases, the numeric sign of the returned value <code>SCALAR-MOD-BASE</code> agrees with that of <code>BASE</code> (unless the returned value is null).  Also note that <code>(ModuloFn SCALAR BASE)</code> is undefined if <code>SCALAR</code> and <code>BASE</code> are not numericallyComparable (q.v.), or if <code>BASE</code> is null. \n<p>\nIn practice, <code>BASE</code> will usually be a positive integral value, and both <code>SCALAR</code> and the returned value will often be integral as well (see ScalarIntegralValue).  Note that if <code>SCALAR</code> and <code>BASE</code> are given in <i>different</i> (but comparable) UnitOfMeasures (e.g. Meter and (Centi Meter)), the result returned by Cyc will be given in the same units as <code>BASE</code>.", 'UniversalVocabularyMt', vStrMon).
 7998exactlyAssertedEL_next(comment, 'MinRangeFn', "An instance of both VariableArityRelation and EvaluatableFunction.  When applied to instances <code>QUANTITY1</code>, ..., <code>QUANTITYN</code>  of ScalarInterval, MinRangeFn yields an instance of ScalarInterval that is the largest interval subsumed by each of <code>QUANTITY1</code> through <code>QUANTITYN</code>.  \n<p>\nFor example, (MinRangeFn  (Meter 1 3) (Meter 2 4)) is (Meter 2 3). \n<p>\nNote that if one of the instances <code>QUANTITY1</code>, ..., <code>QUANTITYN</code> fails to intersect with at least one of the other instances, then the result of applying MinRangeFn to <code>QUANTITY1</code>, ..., <code>QUANTITYN</code> is undefined (for example, both (MinRangeFn (Meter 1 1.5) (Meter 2 4) (Meter 0 5)) and (MinRangeFn (SecondsDuration 3 5) (Meter 1 4)) are undefined).  See also MaxRangeFn.", 'UniversalVocabularyMt', vStrDef).
 7999exactlyAssertedEL_next(comment, 'Minimum', "Computes the minimum of a unary function's values over all elements in a given set or collection.  That is, (Minimum SETORCOL FUNC) denotes the value of FUNC for the element ELEM of SETORCOL taken as argument (if any) such that (FUNC ELEM) is less than or equal to (FUNC OTHER) for any element OTHER of SETORCOL other than ELEM.  Note that (Minimum SETORCOL IdentityFn) denotes the minimum element of SETORCOL itself.", 'UniversalVocabularyMt', vStrDef).
 8000exactlyAssertedEL_next(comment, 'MicrotheoryDesignatingRelation', "The collection of Relations which specify that a ELSentence-Assertible is to be interpreted in a given Microtheory.  It will be canonicalized and checked for well-formedness with respect to that microtheory. Each microtheory-designating relation has an argument which denotes a microtheory, and another argument which denotes a ELSentence-Assertible.  It may have other arguments as well. Use microtheoryDesignationArgnum and sentenceDesignationArgnum to specify these argument positions for each microtheory-designating relation.", 'UniversalVocabularyMt', vStrDef).
 8001exactlyAssertedEL_next(comment, 'Microtheory', "A specialization of AspatialInformationStore and AbstractIndividual (qq.v.).  Each instance of Microtheory is an atemporal, aspatial, informational thing that represents a context in Cyc.  Each microtheory (or 'mt') serves to group a set of assertions together that share some common assumptions; the assertions in an mt constitute the content of that mt.  Note that each assertion in the Cyc knowledge base must be explicitly stated to be true in at least one microtheory.  Assertions stated to be true in one mt will also be true  (by inference) in more specialized mts that depend on the content of that mt.  For example, if something is true in the HumanSocialLifeMt (q.v.), then it should by default be true in the more specialized UnitedStatesSocialLifeMt (q.v.).  Specialized microtheories are related to the more general microtheories on which they depend by the predicate genlMt (q.v.).  Note that every query is made in some mt, and the answer one gets to a query depends on the mt in which it is asked, since the only assertions which can be used to answer a query in an mt are those  explicitly stated to be true in that mt, or in some more general mt.  See also the predicate ist, which is used to relate an assertion to the microtheories in which it is true.", 'UniversalVocabularyMt', vStrDef).
 8002exactlyAssertedEL_next(comment, 'MeaningInSystemFn', "A reifiable BinaryFunction that returns the meaningful entities indexed by a particular character string in a Cyc-external information source. More precisely, (MeaningInSystemFn INFOSOURCE STRING), applied to the CharacterString STRING and the IndexedInformationSource INFOSOURCE, returns whatever is indexed by STRING in that system.  For example, (MeaningInSystemFn WordNet-1997Version \"N03585958\") returns the WordNet `synset' (`synonym set') represented by (rampart|bulwark|wall), meaning \"an embankment built around a space for defensive purposes\".\n<p>\nSTRING can have any format chosen by the person who builds the representation of the external system.  In addition, STRING may contain arbitrary further characters or information, depending on how the external information is selected and processed.  This function makes it possible to relate a concept in an external system to an arbitrarily complicated expression composed of Cyc concepts.  If the external concept has a direct, exact mapping to a single Cyc constant, then use the predicate synonymousExternalConcept rather than this function.  If there is correspondence only to one Cyc constant, but it is only approximate, use overlappingExternalConcept.", 'UniversalVocabularyMt', vStrDef).
 8003exactlyAssertedEL_next(comment, 'May', "A specialization of CalendarMonth. Each instance of May is the fifth month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8004exactlyAssertedEL_next(comment, 'MaxRangeFn', "<code>(MaxRangeFn QUANTITY<sub>1</sub> ... QUANTITY<sub>N</sub>)</code> denotes a quantity which subsumes each of <code>QUANTITY<sub>1</sub></code> through <code>QUANTITY<sub>N</sub></code>.  For example, <code>(MaxRangeFn (Meter 1 3) (Meter 2 4))</code> denotes (Meter 1 4).  See also MinRangeFn.", 'UniversalVocabularyMt', vStrDef).
 8005exactlyAssertedEL_next(comment, 'Maximum', "A NumericQuantifier.  Used to denote the maximum quantity which results from applying the function specified in the second argument to all of the elements of the set expression which appears in the first argument.--Rode 3/15/98", 'UniversalVocabularyMt', vStrDef).
 8006exactlyAssertedEL_next(comment, 'March', "A specialization of CalendarMonth. Each instance of March is the third month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8007exactlyAssertedEL_next(comment, 'LogicalTruthMt', "This is a microtheory which contains only the assertions required to represent the logical system used in the Cyc knowledge base.  In other words, these are the assertions in CycL which must be present in order to use CycL to represent logical truths.", 'BaseKB', vStrMon).
 8008exactlyAssertedEL_next(comment, 'LogicalTruthImplementationMt', "This is a microtheory which contains only the assertions required for the Cyc theorem prover and its underlying HL representation of the EL to function properly.  In other words, these are the assertions in CycL which are required by Cyc in order to perform any logical inferences using CycL formulas.", 'BaseKB', vStrMon).
 8009exactlyAssertedEL_next(comment, 'LogicalConnective', "A collection of mathematical objects, including the basic logical connectives.  Each instance of LogicalConnective is a Relation which takes one or more truth-valued expressions (sentences) as arguments and returns a truth-valued sentence.  The instances of LogicalConnective include and, or, not, and implies.", 'UniversalVocabularyMt', vStrDef).
 8010exactlyAssertedEL_next(comment, 'LogFn', "A unary EvaluatableFunction that returns the natural logarithm of the number taken as its argument.  (LogFn NUM) is the exponent to which e is raised to get NUM (where e is E-LogarithmBase). Its inverse (cf. inverseQuantFunctions-Nonsymmetric) is ExpFn.", 'UniversalVocabularyMt', vStrDef).
 8011exactlyAssertedEL_next(comment, 'List', "A specialization of Tuple.  Each instance of List is a  finite sequence of things with a first and last member-position, with each member-position other than the last having a successor member-position.   As with tuples generally, lists allow for repetition of their members, so that the same item can appear at multiple member-positions in the same list.  A list can be represented formally as a function from a finite index set of counting numbers, beginning with one, into the domain of all Things (but note that Lists are _not_ explicitly represented as functions in the Cyc ontology).  Unlike an instance of Series (q.v.), a list is purely abstract (i.e. both aspatial and atemporal), and the only implied relation between an item and its successor in a list is the successor relation of the list itself.  Technically, List is more specific than Tuple only in that the index set (see tupleIndexSet) for a given list must be the counting numbers in their usual order (or some initial segment thereof), whereas the index set for a tuple, generally speaking, might be any set whatsoever.", 'UniversalVocabularyMt', vStrDef).
 8012exactlyAssertedEL_next(comment, 'LeaveVariablesAtEL', "A CanonicalizerDirective (q.v.) that directs the canonicalizer to refrain from canonicalizing ELVariables into HLVariables.\nA consequence of this is that any CycLAssertion that contains no HL variables, regardless of its form, will be treated by the canonicalizer as if it were a GAF (see CycLClosedAtomicSentence) as opposed to a rule.  Note that this will inhibit nat reification if there are variables within the scope of the reifiable function.", 'CoreCycLImplementationMt', vStrMon).
 8013exactlyAssertedEL_next(comment, 'LeaveSomeTermsAtELAndAllowKeywordVariables', "A CanonicalizerDirective which combines the directives LeaveSomeTermsAtEL and AllowKeywordVariables.", 'CoreCycLImplementationMt', vStrMon).
 8014exactlyAssertedEL_next(comment, 'LeaveSomeTermsAtELAndAllowKeywordVariables', "A  CanonicalizerDirective (q.v.) that is a specialization (see  genlCanonicalizerDirectives) of both LeaveSomeTermsAtEL and  AllowKeywordVariables (qq.v.), and thus combines the commands of both of those directives.", 'CoreCycLImplementationMt', vStrMon).
 8015exactlyAssertedEL_next(comment, 'LeaveSomeTermsAtEL', "A CanonicalizerDirective (q.v.) that combines the following three commands:\n<p>\n(1) Do not canonicalize ELVariables into HLVariables.\n(2) Do not expand CycLFormulas whose operators are instances of ELRelation.\n(3) Do not reify CycLReifiableNonAtomicTerms.\n<p>\nA consequence of (1) is that any CycLAssertion that contains no HL variables, regardless of its form, will be treated by the canonicalizer as if it were a GAF (see CycLClosedAtomicSentence) as opposed to a rule.", 'CoreCycLImplementationMt', vStrMon).
 8016exactlyAssertedEL_next(comment, 'KnowledgeBase', "A specialization of Database-AbstractContent. Each instance of KnowledgeBase is a database (considered as an abstract repository of information rather than a physical storage device) containing knowledge about at least part of the world.  A notable specialization of KnowledgeBase is CycKB, the collection of all Cyc knowledge bases.", 'UniversalVocabularyMt', vStrMon).
 8017exactlyAssertedEL_next(comment, 'Kappa', "A binary PredicateDenotingFunction and a ScopingRelation (qq.v.), Kappa is used to define a predicate on the basis of a sentence (see CycLSentence-Assertible) and a list of variables (see CycLVariableList) some or all of which typically occur free in the sentence.  The resulting predicate holds of just those sequences that would make the sentence true.\n<p>\nMore precisely, if <code>VAR1,...,VAR<sub>N</sub></code> include all of the CycLVariables that occur free in <code>SENT</code>, then the term\n<pre>\n  (Kappa (VAR1 ... VAR<sub>N</sub>) SENT)\n</pre>\ndenotes the <code>N</code>-ary relation (i.e. the Predicate) that holds of any admitted sequence of arguments <code>ARG1...ARG<sub>N</sub></code> if and only if <code>SENT[ARG<sub>I</sub>/VAR<sub>I</sub>]</code> is true, where <code>SENT[ARG<sub>I</sub>/VAR<sub>I</sub>]</code> is the result of simultaneously replacing each free occurrence of <code>VAR<sub>I</sub></code> in <code>SENT</code> with a CycL name of the corresponding <code>ARG<sub>I</sub></code> (for 1 <= <code>I</code> <= <code>N</code>). \n<p>\n(With respect to the above, <code>ARG1...ARG<sub>N</sub></code> is an <i>admitted sequence of arguments</i> to <code>(Kappa (VAR1 ... VAR<sub>N</sub>) SENT)</code> just in case (i) each <code>ARG<sub>I</sub></code> satisfies any argument-type constraints applicable to the position(s) occupied by <code>VAR<sub>I</sub></code> in <code>SENT</code> and (ii) if any two variables <code>VAR<sub>I</sub></code> and <code>VAR<sub>J</sub></code> are the same then the corresponding sequence-members <code>ARG<sub>I</sub></code> and <code>ARG<sub>J</sub></code> are identical.)\n<p>\nA few examples.  (Kappa (<code>?X</code>) (greaterThan <code>?X</code> 1)) is a unary predicate that holds of all numbers greater than 1. (Kappa (<code>?X ?Y</code>) (greaterThan <code>?X</code> 1)) is a binary predicate that holds of any ordered pair of argument values whose first member is a number greater than 1. (Kappa (<code>?X</code>) (greaterThan 2 1)) is a unary predicate that holds of any thing.  (Kappa (<code>?X</code>) (greaterThan 1 2)) is a unary predicate that holds of no thing.  (Kappa (<code>?X ?X</code>) (greaterThan <code>?X 1</code>)) is a binary predicate that holds of any ordered pair of numbers whose first and second members are the same number <b>K</b>, where <b>K</b> is greater than 1.\n<p>\nMost of the above examples are uses of Kappa that have little utility.  The first example, however, is an example of a common and important use of Kappa, which is to reduce the arity of a predicate by fixing the value for one or more of its arguments. For example, (Kappa (<code>?COUNTRY ?RATE</code>) (exportRate <code>?COUNTRY</code> Oil <code>?RATE</code>)) defines a binary predicate that relates a country to its export rate of oil, whereas (Kappa (<code>?COUNTRY</code>) (exportRate <code>?COUNTRY</code> Oil (MillionBarrelsPerDay 2)))</code> defines a unary predicate that holds of any country that exports oil at the rate of two million barrels per day.\n<p>\nThe sentence that is an argument to Kappa may be arbitrarily complex.  For example, it may be an existentially quantified conjunction.  Thus,\n<pre>\n   (Kappa (?PERSON ?NAME)\n    (thereExists ?FATHER\n      (and\n        (isa ?PERSON Person)\n        (father ?PERSON ?FATHER)\n        (lastName ?FATHER ?NAME))\n</pre>\n<p>\nreturns a predicate that holds of any ordered pair <b><PERSON, NAME></b>, such that <b>PERSON</b> is a person whose father's last name is <b>NAME</b>.\n<p>\nSometimes it is useful to construct an expression of the form <code>(Kappa LIST SENT)</code> where some variables that occur free in <code>SENT</code> do <i>not</i> occur in <code>LIST</code>.  For example, <code>(Kappa (?X) (greaterThan ?X ?Y))</code> might be used in a context where the <code>?Y</code> appears within the scope of a quantifier that occurs outside of the Kappa expression.\n<p>\nKappa is a cousin of the function Lambda (q.v.), which is used to define a <i>function</i> on the basis of a list of variables and a non-logical term.", 'UniversalVocabularyMt', vStrDef).
 8018exactlyAssertedEL_next(comment, 'June', "A specialization of CalendarMonth.  Each instance of June is the sixth month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8019exactlyAssertedEL_next(comment, 'July', "The collection of all Julys,\n the seventh month of the year in the GregorianCalendar.", 'UniversalVocabularyMt', vStrDef).
 8020exactlyAssertedEL_next(comment, 'January', "A specialization of CalendarMonth.  Each instance of January is the first month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8021exactlyAssertedEL_next(comment, 'ist-Asserted', "A MicrotheoryDesignatingPredicate that is used to relate CycL sentences to microtheories in which they are explicitly asserted. (ist-Asserted MT SENT) states that there is a CycLAssertion for SENT in the Microtheory MT.  This predicate is therefore a more specialized form of ist (q.v.) with the additional requirement that there be an actual assertion for SENT in MT.\n<p>\nNote that the above is also more precise than (ist MT (knownSentence SENT)), which states that there is an assertion for SENT in some microtheory visible from (see genlMt) MT.", 'UniversalVocabularyMt', vStrMon).
 8022exactlyAssertedEL_next(comment, 'IrreflexiveBinaryPredicate', "The collection of BinaryPredicates that are irreflexive.  A binary predicate <code>PRED</code> is an instance of IrreflexiveBinaryPredicate only if, for every <code>THING</code> that satisfies the single-argument type-constraints (i.e. argIsa and argGenls; see admittedArgument) on both of <code>PRED</code>'s argument-places, <code>(not (PRED THING THING))</code> holds.\n<p>\nTo rule out \"vacuous\" cases, there is an additional necessary condition for irreflexivity:  the constraints on <code>PRED</code>'s two argument-places must be co-satisfiable (see cosatisfiableInArgs).  Without this requirement, any binary predicate whose arguments were constrained in mutually-disjoint ways would trivially (and counterintuitively) count as irreflexive.  See NoteOnArgumentCosatisfiabilityRequirement\n<p>\nExamples of irreflexive binary predicates include spouse, causes-ThingProp, northOf, and temporallyDisjoint.", 'UniversalVocabularyMt', vStrDef).
 8023exactlyAssertedEL_next(comment, 'IntervalMinFn', "<code>(IntervalMinFn SCALAR)</code> returns an interval of the same type as <code>SCALAR</code> whose minimum value is the minimum value of <code>SCALAR</code> and whose maximum value is PlusInfinity.  For example, (IntervalMinFn (Mile 3)) is the same as `the interval from three miles to an infinite number of miles', in other words, `at least three miles'.", 'UniversalVocabularyMt', vStrDef).
 8024exactlyAssertedEL_next(comment, 'IntervalMaxFn', "<code>(IntervalMaxFn SCALAR)</code> returns an interval of the same type as <code>SCALAR</code> whose maximum value is the maximum value of <code>SCALAR</code> and whose minimum value is minus infinity.  For example, (IntervalMaxFn (Mile 3)) is the same as `the interval from negative infinity miles to three miles'. [Technical Note: if that expression were to denote a strictly absolute, as opposed to a relative-or-absolute, distance, then it would mean `the interval from 0 miles to 3 miles'.]   (IntervalMaxFn (Unity 1)) is the same as `the interval from negative infinity to 1', in other words, `no greater than one'.", 'UniversalVocabularyMt', vStrDef).
 8025exactlyAssertedEL_next(comment, 'IntervalEntry', "An instance of Format (q.v.) that can be specified to hold of a given predicate with respect to a given argument-place (see argFormat), where the argument-place in question is one constrained (via argIsa) to instances of ScalarInterval.   (argFormat PRED N IntervalEntry) means that, for any particular way of fixing the other arguments to PRED besides the Nth, there may be more than one instance of ScalarInterval such that, if taken as the Nth argument, PRED holds of those arguments.  However, if there is more than one instance of ScalarInterval taken as the Nth argument in such a situation, it must be the case that each of the instances of ScalarInterval intersect one another (see quantityIntersects).  That is, if the sequences <... ARGN-1 ...>, <... ARGN-2 ...>, ..., <... ARGN-M ...> differ at most in their Nth items and each of (PRED ... ARGN-1 ...), (PRED ... ARGN-2 ...), ..., (PRED ... ARGN-M ...) holds, then for any distinct ARGN-K and ARGN-L, where K and L are greater than or equal to 1, and less than or equal to M, (quantityIntersects ARGN-K ARGN-L). For example, the format of volumeOfObject's second argument-place is IntervalEntry.", 'BaseKB', vStrDef).
 8026exactlyAssertedEL_next(comment, 'InterArgIsaPredicate', "The subcollection of both InterArgTypePredicate and ArgIsaPredicate (qq.v.) whose instances are used to put conditional isa based argument-type constraints on polyadic relations in regards to two of their argument-places.  Each instance of InterArgIsaPredicate specifies, with respect to a given Relation, that one of its arguments (the \"dependent\" one) must be an instance of (isa) a certain collection, contingent upon another of its argument's (the \"independent\" one's) being an instance of a certain (possibly different) collection.  An inter-argument-isa predicate PRED has argument-places for designating the relation and the two collections serving as argument-types; the (numerically-specified) identities of the relation's corresponding dependent and independent arguments is in most cases fixed (as in interArgIsa1-2), but is in some cases variable and specified via two additional argument-places of PRED's (as in interArgIsa).  In cases of the former sort, where the relation's argument-places are fixed, PRED is a TernaryPredicate that takes as it first argument (or \"arg1\") a relation, as its arg2 the type specified for the relation's independent argument, and as its arg3 the type specified (contingently) for the dependent argument.", 'UniversalVocabularyMt', vStrDef).
 8027exactlyAssertedEL_next(comment, 'interArgIsa5-4', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa5-4 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the fifth argument to RELN,  a necessary condition for semantic well-formedness is that the fourth argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 ARG3 ARG4 INST ... ARGN) is semantically  well-formed only if ARG4 is an instance of DEPENDENT-ARG-COL.  For an explanation  of semantic well-formedness, see CycLExpression-Assertible and its direct  specializations.", 'UniversalVocabularyMt', vStrMon).
 8028exactlyAssertedEL_next(comment, 'interArgIsa5-3', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa5-3 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the fifth argument to RELN,  a necessary condition for semantic well-formedness is that the third argument  must be an instance of DEPENDENT-ARG-COL.  That is, if ARG-INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 ARG3 ARG4 INST ... ARGN) is semantically well-formed  only if ARG3 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic  well-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8029exactlyAssertedEL_next(comment, 'interArgIsa5-2', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa5-2 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the fifth argument to RELN,  a necessary condition for semantic well-formedness is that the second argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 ARG3 ARG4 INST ... ARGN) is semantically well-formed  only if ARG2 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic  well-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8030exactlyAssertedEL_next(comment, 'interArgIsa5-1', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa5-1 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the fifth argument to RELN,  a necessary condition for semantic well-formedness is that the first argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 ARG3 ARG4 INST ... ARGN) is semantically  well-formed only if ARG1 is an instance of DEPENDENT-ARG-COL.  For an explanation  of semantic well-formedness, see CycLExpression-Assertible and its direct  specializations.", 'UniversalVocabularyMt', vStrMon).
 8031exactlyAssertedEL_next(comment, 'interArgIsa4-5', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa4-5 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the fourth argument to RELN, \na necessary condition for semantic well-formedness is that the fifth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 ARG2 ARG3 INST ARG5 ... ARGN) is semantically \nwell-formed only if ARG5 is an instance of DEPENDENT-ARG-COL.  For an explanation \nof semantic well-formedness, see CycLExpression-Assertible and its direct \nspecializations.", 'UniversalVocabularyMt', vStrMon).
 8032exactlyAssertedEL_next(comment, 'interArgIsa4-3', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa4-3 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the fourth argument to RELN, \na necessary condition for semantic well-formedness is that the third argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 ARG2 ARG3 INST ... ARGN) is semantically well-formed only \nif ARG3 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8033exactlyAssertedEL_next(comment, 'interArgIsa4-2', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa4-2 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the fourth argument to RELN,  a necessary condition for semantic well-formedness is that the second argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 ARG3 INST ... ARGN) is semantically well-formed only  if ARG2 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic  well-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8034exactlyAssertedEL_next(comment, 'interArgIsa4-1', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa4-1 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the fourth argument to RELN, \na necessary condition for semantic well-formedness is that the first argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 ARG2 ARG3 INST ... ARGN) is semantically well-formed only \nif ARG1 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8035exactlyAssertedEL_next(comment, 'interArgIsa3-5', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa3-5 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the third argument to RELN, \na necessary condition for semantic well-formedness is that the fifth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 ARG2 INST ARG4 ARG5 ... ARGN) is semantically \nwell-formed only if ARG5 is an instance of DEPENDENT-ARG-COL.  For an explanation \nof semantic well-formedness, see CycLExpression-Assertible and its direct \nspecializations.", 'UniversalVocabularyMt', vStrMon).
 8036exactlyAssertedEL_next(comment, 'interArgIsa3-4', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa3-4 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the third argument to RELN, \na necessary condition for semantic well-formedness is that the fourth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 ARG2 INST ARG4 ... ARGN) is semantically well-formed only \nif ARG4 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8037exactlyAssertedEL_next(comment, 'interArgIsa3-2', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa3-2 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the third argument to RELN,  a necessary condition for semantic well-formedness is that the second argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 INST ... ARGN) is semantically well-formed only  if ARG2 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic  well-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8038exactlyAssertedEL_next(comment, 'interArgIsa3-1', "A ternary instance of InterArgIsaPredicate (q.v.).   (interArgIsa3-1 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that,  when an instance of INDEPENDENT-ARG-COL appears as the third argument to RELN,  a necessary condition for semantic well-formedness is that the first argument  must be an instance of DEPENDENT-ARG-COL.  That is, if INST is an instance of INDEPENDENT-ARG-COL, then  (RELN ARG1 ARG2 INST ... ARGN) is semantically well-formed only  if ARG1 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic  well-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8039exactlyAssertedEL_next(comment, 'interArgIsa2-5', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa2-5 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the second argument to RELN, \na necessary condition for semantic well-formedness is that the fifth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 INST ARG3 ARG4 ARG5 ... ARGN) is semantically \nwell-formed only if ARG5 is an instance of DEPENDENT-ARG-COL.  For an explanation \nof semantic well-formedness, see CycLExpression-Assertible and its direct \nspecializations.", 'UniversalVocabularyMt', vStrMon).
 8040exactlyAssertedEL_next(comment, 'interArgIsa2-4', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa2-4 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the second argument to RELN, \na necessary condition for semantic well-formedness is that the fourth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 INST ARG3 ARG4 ... ARGN) is semantically well-formed only \nif ARG4 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8041exactlyAssertedEL_next(comment, 'interArgIsa2-3', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa2-3 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the second argument to RELN, \na necessary condition for semantic well-formedness is that the third argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN ARG1 INST ARG3 ... ARGN) is semantically well-formed only \nif ARG3 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8042exactlyAssertedEL_next(comment, 'interArgIsa2-1', "A ternary instance of InterArgIsaPredicate (q.v.).   <code>(interArgIsa2-1 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL)</code> means that,  when an instance of <code>INDEPENDENT-ARG-COL</code> appears as the second argument to <code>RELN</code>,  a necessary condition for semantic well-formedness is that the first argument  must be an instance of <code>DEPENDENT-ARG-COL</code>.  That is, if <code>INST</code> is an instance of <code>INDEPENDENT-ARG-COL</code>, then <code>(RELN ARG1 INST ... ARGN)</code>  is semantically well-formed only if <code>ARG1</code> is an instance of <code>DEPENDENT-ARG-COL</code>. For an explanation of semantic well-formedness, see CycLExpression-Assertible  and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8043exactlyAssertedEL_next(comment, 'interArgIsa1-5', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa1-5 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the first argument to RELN, \na necessary condition for semantic well-formedness is that the fifth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN INST ARG2 ARG3 ARG4 ARG5 ... ARGN) is semantically \nwell-formed only if ARG5 is an instance of DEPENDENT-ARG-COL.  For an explanation \nof semantic well-formedness, see CycLExpression-Assertible and its direct \nspecializations.", 'UniversalVocabularyMt', vStrMon).
 8044exactlyAssertedEL_next(comment, 'interArgIsa1-4', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa1-4 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the first argument to RELN, \na necessary condition for semantic well-formedness is that the fourth argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN INST ARG2 ARG3 ARG4 ... ARGN) is semantically well-formed only \nif ARG4 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8045exactlyAssertedEL_next(comment, 'interArgIsa1-3', "A ternary instance of InterArgIsaPredicate (q.v.).  \n(interArgIsa1-3 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL) means that, \nwhen an instance of INDEPENDENT-ARG-COL appears as the first argument to RELN, \na necessary condition for semantic well-formedness is that the third argument \nmust be an instance of DEPENDENT-ARG-COL.  That is, if INST is\nan instance of INDEPENDENT-ARG-COL, then \n(RELN INST ARG2 ARG3 ... ARGN) is semantically well-formed only \nif ARG3 is an instance of DEPENDENT-ARG-COL.  For an explanation of semantic \nwell-formedness, see CycLExpression-Assertible and its direct specializations.", 'UniversalVocabularyMt', vStrMon).
 8046exactlyAssertedEL_next(comment, 'interArgIsa1-2', "A ternary instance of InterArgIsaPredicate (q.v.).  <code>(interArgIsa1-2 RELN INDEPENDENT-ARG-COL DEPENDENT-ARG-COL)</code> means that, when an instance of <code>INDEPENDENT-ARG-COL</code> appears as the first argument to <code>RELN</code>, a necessary condition for semantic well-formedness is that the second argument must be an instance of <code>DEPENDENT-ARG-COL</code>.  That is, if <code>INST</code> is an instance of <code>INDEPENDENT-ARG-COL</code>, then <code>(RELN INST ARG2 ... ARGN)</code> is semantically well-formed only if <code>ARG2</code> is an instance of <code>DEPENDENT-ARG-COL</code>.\n<p>\nFor example, (interArgIsa1-2 performedBy PurposefulAction IntelligentAgent) means that, if <code>ACT</code> is a purposeful action, then (performedBy <code>ACT AGENT</code>) is semantically well-formed only if <code>AGENT</code> is an intelligent agent.  For an explanation of semantic well-formedness, see  CycLExpression-Assertible and its direct specializations.  See interArgIsa for a similar but more general predicate that is quintary, allowing the user to specify the positions of the independent and dependent arguments.\n<p>\nUse interArgCondIsa1-2 to conclude that arg2 is an instance of <code>DEPENDENT-ARG-COL</code> instead of having that as a constraint.", 'UniversalVocabularyMt', vStrMon).
 8047exactlyAssertedEL_next(comment, 'interArgGenl1-2', "(interArgGenl1-2 REL INDEPENDENT-COL DEPENDENT-COL) means that, when a spec of INDEPENDENT-COL appears as the first argument to REL, the second argument is constrained to be a spec of DEPENDENT-COL.", 'UniversalVocabularyMt', vStrDef).
 8048exactlyAssertedEL_next(comment, 'InterArgFormatPredicate', "The subcollection of both InterArgConstraintPredicate and ArgFormatPredicate (qq.v.) whose instances are used to specify, for a given predicate PRED, a certain Format requirement on one of PRED's arguments (the \"dependent\" one), contingent upon one (usually, but not always, a different one) of PRED's arguments (the \"independent\" one) being an instance of (isa) a certain collection.  Currently, each instance of InterArgFormatPredicate is ternary, where its first argument (or \"arg1\") is the predicate PRED upon which the constraint is being placed, its arg2 the collection serving as the isa condition on PRED's independent argument, and its arg3 the Format that PRED's dependent argument is (conditionally) constrained to have.  The (numerically-specified) identities of the arguments of PRED's that are to serve as the independent and dependent arguments are fixed for each instance of \nInterArgFormatPredicate.", 'UniversalVocabularyMt', vStrDef).
 8049exactlyAssertedEL_next(comment, 'interArgFormat1-2', "An instance of InterArgFormatPredicate (q.v.).\n(interArgFormat1-2 PRED COL FORMAT) means that FORMAT is a Format (q.v.)\nrequirement for the second argument-place of PRED when PRED's first argument\nis an instance of COL.  That is, with respect to a sentence of the form \n(PRED ARG1 ARG2 ... ARGN) in which ARG1 is an instance of COL, PRED's arg2\nposition (i.e. the position occupied by the metavariable `ARG2' in the \npreceding sentence-form) is subject to FORMAT.  See Format and its instances \nfor further explanation.", 'UniversalVocabularyMt', vStrMon).
 8050exactlyAssertedEL_next(comment, 'Integer', "A specialization of RationalNumber.  Each instance of Integer is a whole number with no fractional remainder.  An integer may be positive (e.g. 42), zero, or negative (e.g. -42).\n<p>\nNote that, in the KB browser, a fixed- or floating-point number representation such as `42.00' should not be assumed to refer to the integer 42. For it might only appear to correspond to that integer within the tolerance of its representation, and might in fact be an approximation to a non-integer number such as 42.0003.\n<p>\nAlso note that, unlike Integer, SubLInteger (q.v.) is a collection of integer-denoting expressions in the SubL programming language rather than a collection of integers themselves. Still, (genls SubLInteger Integer) holds, but only under a special interpretation of genls forced by the fact that SubLInteger is a quotedCollection (q.v).)", 'UniversalVocabularyMt', vStrDef).
 8051exactlyAssertedEL_next(comment, 'InferenceSupportedTerm', "The collection of all CycLTerms that are supported in some way by the CycInferenceEngine.  This support may be provided by, for example, a CycHLModule or an evaluationDefn.", 'UniversalVocabularyMt', vStrMon).
 8052exactlyAssertedEL_next(comment, 'InferenceSupportedPredicate', "The collection of all Predicates that are supported in some way by the CycInferenceEngine.  This support may be provided by, for example, a CycHLModule or an evaluationDefn.", 'UniversalVocabularyMt', vStrMon).
 8053exactlyAssertedEL_next(comment, 'InferenceSupportedFunction', "The collection of all Function-Denotationals that are supported in some way by the CycInferenceEngine.  This support may be provided by, for example, an evaluationDefn.", 'UniversalVocabularyMt', vStrMon).
 8054exactlyAssertedEL_next(comment, 'InferenceSupportedCollection', "The collection of all CycL terms that denote collections, where these terms are supported in some way by the CycInferenceEngine.  If a term T denoting the collection COL is an InferenceSupportedCollection, this means that the inference engine treats instances of COL specially.", 'UniversalVocabularyMt', vStrMon).
 8055exactlyAssertedEL_next(comment, 'InferenceRelatedBookkeepingPredicate', "A collection of predicates.  Each instance of InferenceRelatedBookkeepingPredicate is a predicate involved in assertions used by the Cyc application to direct inferencing.  Examples: defnIff, defnSufficient, termOfUnit, afterAdding.", 'UniversalVocabularyMt', vStrDef).
 8056exactlyAssertedEL_next(comment, 'InferencePSC', "A problem solving context in which all assertions in the entire KB are initially visible.  However, down each inference path, the chain of microtheories used is required to have some common descendent microtheory which is capable of inheriting all of the microtheories in the chain.  Thus, queries made in InferencePSC in effect compute locations in the space of microtheories in which the query is satisfiable.  This context is used internally by the inference engine for certain recursive calls to itself, including forward inference.  See also EverythingPSC.", 'BaseKB', vStrMon).
 8057exactlyAssertedEL_next(comment, 'Individual', "Individual is the collection of all individuals:  things that are <i>not</i> sets or collections.  Individuals might be concrete or abstract, and include (among other things) physical objects, events, numbers,  relations, and groups.  An instance of Individual might have parts or  structure (including discontinuous parts); but <i>no</i> individual has elements  or subsets (see elementOf and subsetOf). Thus, an individual that has parts (e.g. physicalParts or groupMembers) is <i>not</i> the same thing as either the set or the collection containing those same parts.  For example, your car is an individual, but the collection of all the parts of your car is not an individual but an instance of Collection.  This collection (unlike the car itself) is abstract: it doesn't have a location, mass, or a top speed; but it does have instances, subcollections, and supercollections.  In partial contrast, the Group (q.v.) of parts of your car (while also not the same thing as the car itself) <i>is</i> an individual that has location and mass.  Another example: A given company, the group consisting of all the company's employees, the collection of those employees, and the set of those employees are four distinct things, and only the first two are individuals.", 'UniversalVocabularyMt', vStrDef).
 8058exactlyAssertedEL_next(comment, 'IndeterminateTermDenotingFunction', "IndeterminateTermDenotingFunction is the collection of all functions that denote indeterminate terms.  See also IndeterminateTerm, SkolemTerm, and SkolemFunction.", 'UniversalVocabularyMt', vStrMon).
 8059exactlyAssertedEL_next(comment, 'IndeterminateTerm', "A specialization of CycLClosedDenotationalTerm.  Each instance of IndeterminateTerm is a CycL symbol for which, in oreder to establish its denotation, it is not sufficient to establish every aspect of the context of its use.\n<p>\nIn other words, instances of this collection are terms used to denote something which is known or assumed to exist, but whose precise identity -- i.e. which particular thing or things it is -- is unknown (unless, of course, the term is known to satisfy equals with another term whose precise identity is known).\n<p>\nFor instance, if Cyc knows (relationAllExists physicalExtent University SchoolCampus), and (isa MelbourneUniversity University), then Cyc knows that there is at least one instance of SchoolCampus, <i>IndeterminateCampus</i>, for which (physicalExtent MelbourneUniversity <i>IndeterminateCampus</i>) is true. This campus (or these campuses, if there happens to be more than one) would be denoted in CycL using the IndeterminateTerm:\n<p>\n(RelationAllExistsFn MelbourneUniversity physicalExtent University SchoolCampus).\n<p>\nAnalogously, instances of SkolemTerm are also instances of IndeterminateTerm, as are terms built from SomeFn, GenericInstanceFn, ArbitraryInstanceFn, et al (see the specialization NonSkolemIndeterminateTerm).", 'BaseKB', vStrMon).
 8060exactlyAssertedEL_next(comment, 'HypotheticalContext', "A MicrotheoryType.  Each instance of  HypotheticalContext consists of assertions that are posited strictly for the purpose of exploring their consequences, without alleging their actual truth.   A hypothetical context can be used to analyze hypothetical outcomes of actions or to examine the hypothetical consequences of assuming some theory to be true.  Also, various alternative choices might be asserted, each in its own hypothetical context, so their ramifications can be generated and compared.", 'UniversalVocabularyMt', vStrDef).
 8061exactlyAssertedEL_next(comment, 'HumanCyclist', "A specialization of Cyclist and Person.  Each instance of  HumanCyclist is a person who is entitled to inspect and modify the Cyc knowledge base.", 'UniversalVocabularyMt', vStrDef).
 8062exactlyAssertedEL_next(comment, 'HLPrototypicalTerm', "The collection of all CycLTerms that are the hlPrototypicalInstance of some collection.  All HLPrototypicalTerms are IndeterminateTerms.", 'UniversalVocabularyMt', vStrDef).
 8063exactlyAssertedEL_next(comment, 'HLExternalIDString', "HLExternalIDString is the collection of all SubLStrings\nwhich represent valid external ID strings for CycLExpressions.\nMembership in this collection is determined for given strings by\nevaluation of the underlying SubL code which implements the object to\nID mapping.", 'UniversalVocabularyMt', vStrMon).
 8064exactlyAssertedEL_next(comment, 'Guest', "An instance of HumanCyclist.  A Cyc user logged in                            \nas `Guest' will be able to browse the Cyc knowledge base to some extent, but will not have full rights to inspect and modify it.", 'BaseKB', vStrDef).
 8065exactlyAssertedEL_next(comment, 'genls-SpecDenotesGenlInstances', "An instance of TaxonomicSlotForCollections (q.v.) and a specialization of generalizations. genls-SpecDenotesGenlInstances relates a collection (see Collection) to those collections which denote instances of it. More precisely, (genls-SpecDenotesGenlInstances SUBCOL SUPERCOL) means that SUPERCOL is a quoted supercollection of SUBCOL: anything that is quoted instance of (see quotedIsa) SUBCOL is an instance (see isa) of SUPERCOL. For example, (genls-SpecDenotesGenlInstances List-Extensional List) holds.", 'UniversalVocabularyMt', vStrMon).
 8066exactlyAssertedEL_next(comment, 'genls-GenlDenotesSpecInstances', "A instance of TaxonomicSlotForCollections (q.v.) and a specialization of generalizations. genls-GenlDenotesSpecInstances relates a given SubLExpressionType collection (see Collection) to those collections whose instances it denotes. More precisely, (genls-GenlDenotesSpecInstances SUBCOL SUPERCOL) means that SUBCOL is a quoted subcollection of SUPERCOL: anything that is an instance of (see quotedIsa) SUBCOL is a quoted instance (see isa) of SUPERCOL.", 'UniversalVocabularyMt', vStrMon).
 8067exactlyAssertedEL_next(comment, 'FunctionToArg', "A binary FunctionDenotingFunction (q.v.) that takes as argument a FunctionalPredicate (and an integer indicating an argument-place in which that predicate is functional) and returns the corresponding function (whose value is always equal to the predicate's corresponding argument in the indicated place).\n<p>\nMore precisely: if <code>PRED</code> is an <code>N</code>-ary functional predicate that is functional in its <code>M</code>th argument (see functionalInArgs), then <code>(FunctionToArg M PRED)</code> is the (<code>N</code>-1)-ary function <code>FUNC-TO-ARGM</code> such that <code>(PRED ARG(1) ... ARG(N))</code> holds if and only if <code>(FUNC-TO-ARGM ARG(1) ... ARG(M-1) ARG(M+1) ... ARG(N)) = ARG(M)</code>.  If <code>PRED</code> is not functional in its <code>M</code>th argument, then <code>(FunctionToArg PRED M)</code> is undefined.\n<p>\nFor example, (FunctionToArg 2 age) is the function that returns the age of a given person.  Thus ((FunctionToArg 2 age) GeorgeWBush) = (YearsDuration 50) just in case (age GeorgeWBush (YearsDuration 50)) is true.\n<p>\nSee also Lambda and Kappa.", 'UniversalVocabularyMt', vStrDef).
 8068exactlyAssertedEL_next(comment, tFunction, "A specialization of Relation (q.v.) and the collection of all functions.  Each instance of Function-Denotational is a many-one relation that represents, with respect to any given context, a mapping from one set of things (the function's relationDomain) to another set of things (its relationRange).  As a many-one relation, a function maps each thing in its domain to exactly one thing in its range.  A function might be unary, binary, ternary, etc. (see arity; but cf. relationalArity), depending on whether the members of its domain are singletons, ordered pairs, ordered triples, etc.  In general, the domain of an N-ary function with respect to a given context is a set of ordered N-tuples (construed in CycL as Lists of length N).  The function is said to take the items from any of these N-tuples as its N <i>arguments</i> and to return a member of its range as its corresponding <i>value</i> (see valueOfFunctionForArgs).  There are also functions that are not of any particular fixed arity; see VariableArityFunction.\n<p>\nFor example, GovernmentFn is the unary function that takes each GeopoliticalEntity to its RegionalGovernment, and PlusFn is the variable-arity function that takes any sequence of two or more ScalarIntervals\n(q.v.) to their arithmetic sum.\n<p>\nNote that the domain and range (i.e. the extension) of a given function might vary from context to context.  For example, as the government of a country can change over time, GovernmentFn will in such cases map the same country to different governments with respect to different times.  Thus, an instance of Function-Denotational is closer to what is sometimes called a \"function-in-intension\" than to the purely set-theoretical notion of a \"function-in-extension\".\n<p>\nCycL terms that denote functions can be used to form non-atomic terms (or \"NATs\"; see CycLClosedNonAtomicTerm).  Specifically, when such a function-denoting expression is appropriately combined with other expressions (i.e. the former is in the 0th argument position and the latter are of the correct number and type) the resulting expression is a new CycL term (a NAT) that may then freely appear as a component in other CycL expressions.  The NAT will itself denote the value (if any) of the function denoted by the former expression for the sequence of arguments denoted, respectively, by the latter expressions.  For example, GovernmentFn is a unary function, and so the CycL constant 'GovernmentFn' requires one syntactic argument (such as the constant 'France') to form a NAT (in this case, the expression '(GovernmentFn France)').  This NAT, which denotes the government of France, can in turn serve as a syntactic argument in any CycL expression in which a term for an instance of RegionalGovernment can legally occur.\n<p>\nImportant subcollections of Function-Denotational include IndividualDenotingFunction (whose instances always return instances of Individual), CollectionDenotingFunction, SetDenotingFunction, and FunctionDenotingFunction (which is itself a subcollection of the first).  NATs formed using terms that denote instances of FunctionDenotingFunction denote instances of Function-Denotational themselves.  Thus, like most other things, functions can be denoted in CycL either by constants  (e.g. 'GovernmentFn') or -- although this is less common -- by NATs (e.g.  '(FunctionToArg 2 biologicalMother)').\n<p>\nAn important partition of Function-Denotational is into TotalFunction and PartialFunction (qq.v.).\n<p>\nNote that Function-Denotational does not include any of the so-called TruthFunctions (q.v.): Predicates, Quantifiers, or LogicalConnectives. For these relations (as construed in CycL) are not really functions at all, even though it can be heuristically useful to think of them as if they were functions from sequences of arguments to truth values.", 'UniversalVocabularyMt', vStrDef).
 8069exactlyAssertedEL_next(comment, 'Friday', "A collection of CalendarDays and an \ninstance of DayOfWeekType.  Friday is the collection of all \n(and only) fridays.", 'UniversalVocabularyMt', vStrMon).
 8070exactlyAssertedEL_next(comment, 'Forward-AssertionDirection', "An instance of CycLAssertionDirection (q.v.).  A CycL assertion that\nhas the Forward-AssertionDirection can be used in inferences carried \nout at the time the assertion is added to the Knowlege Base as well as \nthose carried out at when a query is asked.  This is the default direction \nfor ground atomic assertions (see CycLClosedAtomicSentence).  Contrast \nwith Backward-AssertionDirection and Code-AssertionDirection.  Also \nsee assertionDirection.", 'UniversalVocabularyMt', vStrMon).
 8071exactlyAssertedEL_next(comment, 'FormulaArityFn', "An instance of EvaluatableFunction.  When applied to a CycLFormula FORM, FormulaArityFn returns the number of arguments given to the relation (an instance of Relation (q.v.)) appearing in the initial (\"arg0\") argument place of FORM.", 'UniversalVocabularyMt', vStrDef).
 8072exactlyAssertedEL_next(comment, 'FormulaArgSetFn', "(FormulaArgSetFn RELATION-EXPRESSION) denotes\na set of the arguments of the given CycLFormula RELATION-EXPRESSION.  For example, (FormulaArgSetFn (genls Dog Animal)) denotes (TheSet Dog Animal).  See also FormulaArgFn and FormulaArityFn.", 'UniversalVocabularyMt', vStrMon).
 8073exactlyAssertedEL_next(comment, 'FormulaArgListFn', "(FormulaArgListFn RELATION-EXPRESSION) denotes a list of the arguments in RELATION-EXPRESSION.  For example, (FormulaArgListFn (genls Dog Animal)) denotes (TheList Dog Animal).  See also FormulaArgFn and FormulaArityFn.", 'UniversalVocabularyMt', vStrMon).
 8074exactlyAssertedEL_next(comment, 'FormulaArgFn', "A binary function that returns an instance of CycLTerm when given an instance of NonNegativeInteger and an instance of CycLFormula as arguments.  (FormulaArgFn N RELATION-EXPRESSION) denotes the term appearing as the Nth argument within RELATION-EXPRESSION. (Note that RELATION-EXPRESSION may be a sentence or a NAT). For example:\n<p>\n(FormulaArgFn 2 (loves Gilbert Muffet)) and\n(FormulaArgFn 1 (BirthFn Muffet))\n<p>\nboth denote Muffet. Cf. ArgPositionFn.", 'UniversalVocabularyMt', vStrDef).
 8075exactlyAssertedEL_next(comment, 'Format', "A collection of argument entry-formats that can be  specified for Predicates with respect to particular argument-places (see argFormat).  An argument entry-format is a kind of restriction on  a predicate regarding how many things, or the range of things, that the  predicate holds of with respect to a given one of its argument-places.  More  precisely: given any particular way of fixing the arguments in the rest of  the predicate's argument-places, the entry-format tells us something about  the number of different things, or the range of things, that can occupy the  given argument-place such that the relation holds of those arguments.  That is, supposing the given argument-place is the Nth, the entry-format tells us  something about the number or range of different sequences of arguments  of which the predicate holds and that differ from each other only in their Nth items.  For example, the format SingleEntry (q.v.) is used to state  that in every case there is at most only one such sequence, the format  SetTheFormat (q.v.) to state that there is no particular (upper or lower)  limit to the number of such sequences that applies to every case, and the  format IntervalEntry (q.v.) to state that the Nth items of any two such  sequences must be ScalarIntervals that \"intersect\" (see quantityIntersects). Thus, the first argument-place of biologicalMother has the format (see  arg1Format) SetTheFormat, since a given female animal might have any  number (including zero) of offspring; but the second argument-place of  this predicate has (see arg2Format) SingleEntry format, since any  given animal has at most (in fact, exactly) one biological mother.  And  the format of the second argument-place of bodyTemperature is IntervalEntry because, while a given creature (at a given moment in time) has a single  exact (see ScalarPointValue) body temperature, we want the predicate bodyTemperature to be flexible enough to allow us to specify this  temperature with varying degrees of precision (e.g. as \"98.6 degrees Fahrenheit\" or as \"between 98 and 99 degrees\" or as \"less than 100 degrees\").  See the various instances of Format for further details.  See also ArgFormatPredicate.  Note that, in contrast with what ArgTypePredicates  are used for, specifying an argument entry-format for a predicate does  _not_ impose any sort of necessary condition for semantic well-formedness.   A violation of a legitimate entry-format constraint necessarily involves  two or more statements, and at least one them must be _untrue_;  but there is no implication that any of them is malformed.", 'UniversalVocabularyMt', vStrDef).
 8076exactlyAssertedEL_next(comment, 'FOL-TermFn', "(FOL-TermFn TERM) denotes a first-order constant symbol\nbased on the CycL term TERM.  For example, (FOL-TermFn Dog)\ndenotes a first-order term based on the collection Dog,\n(FOL-TermFn 212) denotes a first-order term based on the integer\n212, and (FOL-TermFn isa) denotes a first-order term based on the\npredicate isa.  See also (FOL-PredicateFn isa 2) for the\nfirst-order binary predicate based on isa.", 'UniversalVocabularyMt', vStrMon).
 8077exactlyAssertedEL_next(comment, 'FOL-PredicateFn', "(FOL-PredicateFn TERM ARITY) denotes a predicate that has\narity ARITY in the first-order projection of CycL based on the CycL\nterm TERM, which must be either a predicate or a collection.  For\nexample, (FOL-PredicateFn eventOccursAt 2) denotes the binary\nfirst-order predicate associated with eventOccursAt,\n(FOL-PredicateFn different 2) denotes the first-order binary\nversion of the predicate different, and (FOL-PredicateFn Date 1)\ndenotes the unary first-order predicate associated with Date", 'UniversalVocabularyMt', vStrMon).
 8078exactlyAssertedEL_next(comment, 'FOL-FunctionFn', "(FOL-FunctionFn FUNC ARITY) denotes a function that has\narity ARITY in the first-order projection of CycL based on the CycL\nfunction FUNC.  For example, (FOL-FunctionFn YearFn 1) denotes the\nunary first-order function associated with YearFn, and\n(FOL-FunctionFn PlusFn 2) denotes the first-order binary function\nassociated with PlusFn", 'UniversalVocabularyMt', vStrMon).
 8079exactlyAssertedEL_next(comment, 'FixedAritySkolemFunction', "The subcollection of SkolemFunctions whose arity is fixed. This is the most common type of skolem function, since variable- arity skolem functions are only created when a sequence variable is in the scope of the skolem.", 'UniversalVocabularyMt', vStrDef).
 8080exactlyAssertedEL_next(comment, 'FixedAritySkolemFuncN', "The collection of SkolemFuncNs (q.v.) whose arity is fixed.", 'UniversalVocabularyMt', vStrDef).
 8081exactlyAssertedEL_next(comment, 'FixedArityRelation', "A specialization of Relation.  A Relation is an instance  of FixedArityRelation just in case it takes a fixed number  of arguments.  Most relations reified in the Cyc ontology are  of fixed arity.  For example, likesAsFriend always takes two  arguments and pointOfContact three.  This collection is  disjoint with VariableArityRelation.", 'UniversalVocabularyMt', vStrDef).
 8082exactlyAssertedEL_next(comment, 'February', "The collection of all Februaries,  the second month of the year in the GregorianCalendar.", 'UniversalVocabularyMt', vStrDef).
 8083exactlyAssertedEL_next(comment, 'False', "An instance of TruthValue (q.v.).  False is the logical notion of falsehood.  That is, the term 'False' is used as a sentential constant of CycL that is false under every model theoretic interpretation.  For example, (booleanResult T/F False) means that the result obtained from the true-or-false test T/F is False.  Cf. True.", 'BaseKB', vStrDef).
 8084exactlyAssertedEL_next(comment, 'ExpFn', "A unary EvaluatableFunction that is the CycL version of the exponential operator. It takes instances of ComplexNumber and returns instances of ComplexNumber. (ExpFn NUM) is e^NUM, i.e. e raised to the power of NUM (where e is E-LogarithmBase).  When NUM is a RealNumber, (ExpFn NUM) is necessarily a PositiveNumber. In particular, (ExpFn 1) is e.  The inverse of this function (cf. inverseQuantFunctions-Nonsymmetric\n) is LogFn. Note that although the arg constraint for ExpFn is ComplexNumber, its evaluationDefn only evaluates to a value when NUM is a RealNumber. See also ExponentFn, a binary function which returns the result of raising a specified number to a specified exponent.", 'UniversalVocabularyMt', vStrMon).
 8085exactlyAssertedEL_next(comment, 'ExpandSubLFn', "<code>(ExpandSubLFn PARAMETERS SUBL-TEMPLATE)</code> denotes the SubL expression resulting from expanding the SubL template <code>SUBL-TEMPLATE</code> once all <code>PARAMETERS</code> are known.  For example, <code>(ExpandSubLFn (?X) (+ 1 ?X))</code> will denote the SubL expression <code>(+ 1 2)</code> when the parameter <code>?X</code> is bound to 2.  See also EvaluateSubLFn, trueSubL and performSubL.", 'UniversalVocabularyMt', vStrMon).
 8086exactlyAssertedEL_next(comment, 'ExistentialQuantifier-Bounded', "A specialization of ExistentialQuantifier (q.v.).  Each instance of ExistentialQuantifier-Bounded is a ternary relation that can be used to make a certain kind of statement about the existence of a given bounded quantity of things meeting a given criterion.  For example, '(thereExistAtLeast 9 ?X (isa ?X Cat))' means that there exist at least nine cats.  What distinguishes _bounded_ existential quantifiers from existential quantifiers generally is that the former require one to specify explicitly (at least a boundary for) how many things exist that meet the specified criterion.", 'UniversalVocabularyMt', vStrDef).
 8087exactlyAssertedEL_next(comment, 'ExistentialQuantifier', "A specialization of Quantifier (q.v.).  Each instance of ExistentialQuantifier can be used to make a certain kind of assertion regarding the existence of some thing(s) meeting a specified criterion.  For example, `(thereExistAtLeast 9 ?X (isa ?X Cat))' means that there exist at least nine cats.  Other instances of this collection are thereExists and thereExistExactly.  Cf. forAll.", 'UniversalVocabularyMt', vStrDef).
 8088exactlyAssertedEL_next(comment, 'ExceptionPredicate', "A collection of mathematical objects, which are the LogicalConnectives used to express exceptions to rules.  Elements include exceptWhen and exceptFor.", 'UniversalVocabularyMt', vStrMon).
 8089exactlyAssertedEL_next(comment, 'EverythingPSC', "A problem solving context in which all assertions in the entire KB are visible.  This context is only appropriate for use in queries which do not care about the consequences of possible contradictions due to conflicting information from mutually inconsistent microtheories.  See also InferencePSC.", 'BaseKB', vStrMon).
 8090exactlyAssertedEL_next(comment, 'EvaluateSubLFn', "<code>(EvaluateSubLFn SUBL)</code> denotes the SubL term resulting from the invocation of the SubL EVAL facility on the expression <code>SUBL</code>.  For example, <code>(EvaluateSubLFn (ExpandSubLFn () (+ 1 2)))</code> evaluates to 3.  See ExpandSubLFn for a way to denote SubL within CycL.  See also trueSubL.", 'UniversalVocabularyMt', vStrMon).
 8091exactlyAssertedEL_next(comment, 'EvaluatableRelation', "A specialization of Relation.  Each instance of EvaluatableRelation is\na function or predicate for which there is some piece of system code that \ncan be invoked to evaluate (i.e. to determine the denotation or truth-value\nof) a closed expression built from that function or predicate (i.e. a closed \nexpression that has the constant that denotes that function or predicate in \nits initial or \"0th\" argument-place).  An evaluation of this sort is carried \nout, for example, when the system is queried using an evaluate (q.v.) \nsentence.  As one might expect, most evaluatable relations are mathematical \nor syntactic in nature; for numbers, sets, lists, and strings are the sorts \nof things that are related in various ways that can be calculated \nalgorithmically.  Examples include PlusFn, greaterThan, JoinListsFn, \nand substring.  In the case of a function that is evaluatable (see \nEvaluatableFunction), the practical result of evaluating the relevant \nexpression is another _term_ -- one that has the same denotatum as the \noriginal expression, but that is syntactically simpler and constitutes a \nmore straightforward way of referring to that denotatum.  For example, \nthe term `(PlusFn (Inch 3) (Inch 1))', when evaluated, results in \nthe term `(Inch 4)'.  So if a query using the open sentence\n`(evaluate ?X (PlusFn (Inch 3) (Inch 1)))' is asked, the answer \n(or \"binding\" for the variable `?X') returned will be the term `(Inch 4)'.  \nEvaluating a sentence built from (a constant that denotes) an \nEvaluatablePredicate, on the other hand, yields a _truth-value_.  For \nexample, the sentence `(greaterThan (Inch 3) (Inch 1))' evaluates \nto (and so if used to ask a query will return the answer) `True'.  The \npredicate evaluationDefn (q.v.) is used to specify the name of the piece \nof system code used to evaluate expressions formed with a given \nevaluatable relation.", 'UniversalVocabularyMt', vStrDef).
 8092exactlyAssertedEL_next(comment, 'EvaluatablePredicate', "A specialization of both EvaluatableRelation and Predicate (qq.v.).   Each instance of EvaluatablePredicate is a  predicate associated (via evaluationDefn) with a piece of HL (\"heuristic level\") code that computes the resulting truth-value when the predicate is applied to legal \narguments. These truth-values can, of course, be computed only when all of the predicate's argument positions are bound: thus Cyc inference will not generate viable inference tactics for non-fully-bound literals with evaluatable predicates in the arg 0 position.  As one might expect, most evaluatable predicates are mathematical or syntactic in nature; for numbers, sets, lists, and strings are the sorts of things that are related in various ways that can be calculated \nalgorithmically.  Examples include greaterThan and substring. Thus the sentence `(greaterThan 3 1)' evaluates to (and so if used to ask a query will return the answer) `True'.", 'UniversalVocabularyMt', vStrMon).
 8093exactlyAssertedEL_next(comment, 'EvaluatableFunction', "A specialization of both EvaluatableRelation and Function-Denotational (qq.v.).  Each instance of EvaluatableFunction is a function that is associated (via evaluationDefn) with a piece of HL (\"heuristic level\") code that computes the result of applying the function to arguments for which that function is defined.  An evaluation of this sort is carried out, for example, when the system is queried using an evaluate (q.v.) sentence.  As one might expect, most evaluatable functions are mathematical or syntactic in nature; for, unlike with functions generally, operations on numbers, sets, lists, and strings can in many cases be calculated algorithmically.  Examples include PlusFn and JoinListsFn.  The practical result of evaluating a term built from (a constant that denotes) an evaluatable function is another _term_ -- one that has the same denotatum as the former term, but that is syntactically simpler and constitutes a more straightforward way of referring to that denotatum.  For example, the term '(PlusFn 2 3 4)', when evaluated, results in the term '9'.  So if a query using the open sentence '(evaluate ?X (PlusFn 2 3 4))' is asked, the answer (or \"binding\" for the free variable '?X') returned will be the term `9'.  By way of contrast, consider the non-evaluatable function BorderBetweenFn and the following arbitrarily-chosen non-atomic term built with its CycL name: '(BorderBetweenFn France Germany)'.  As there is no general algorithm for finding simpler or \"standard\" terms for given geographical borders, it is not possible for the Cyc system to \"evaluate\" non-atomic terms like this one.", 'UniversalVocabularyMt', vStrDef).
 8094exactlyAssertedEL_next(comment, 'EscapeQuote', "A quotation-related device for making general statements about CycL expressions.  EscapeQuote is used to allow certain free variables occurring inside an expression that is quoted to \"escape\" (i.e. remain free with respect to) the quotation.  It is thus similar in function to, though more flexible than, QuasiQuote (q.v.).\n<p>\nTo be more precise: the syncategorematic symbol <code>EscapeQuote</code> is used in conjunction with the special quotation symbol <code>Quote</code> (q.v.) as a device for allowing genuinely free variables to occur inside quoted expressions, in order that one may meaningfully \"quantify into\" such expressions and thereby generalize over them.  Thus, <code>EscapeQuote</code> is used to indicate that the free variables occurring within its scope (which is itself inside the wider scope of an occurrence of <code>Quote</code>) are <i>not</i> themselves to be interpreted as being quoted.\n<p>\nThe syntax of <code>EscapeQuote</code> is such that it can only be used in conjunction with <code>Quote</code>.  For any CycL expression <code>EXPR</code>, <code>(EscapeQuote EXPR)</code> is not by itself a syntactically well-formed CycL expression; but the latter can appear as <i>part of</i> a well-formed expression, subject to the following restrictions.  (i) Any occurrence of <code>EscapeQuote</code> in a CycL expression must itself be inside the scope of an occurrence of <code>Quote</code>.  (ii) One occurrence of <code>EscapeQuote</code> can be inside the scope of another only if there is an intermediate occurrence of <code>Quote</code> (i.e. one whose scope subsumes that of the former and is subsumed by that of the latter).\n<p>\nThe semantics of <code>EscapeQuote</code> is such that a formula <code>(Quote ... (EscapeQuote EXPR) ...)</code> that contains only one occurrence of <code>EscapeQuote</code> means just what the corresponding formula <code>(Quote ... EXPR ...)</code> means, except that any free occurrence of a variable in <code>EXPR</code> is to be interpreted as still being genuinely free with respect to <code>(Quote ... (EscapeQuote EXPR) ...)</code>.  In <code>(Quote ... EXPR ...)</code>, by contrast, any such variables are taken to be regular quoted constituents of a quoted compound expression; thus they do not function there as variables, but as <i>quoted-names of</i> variables -- i.e. as terms that denote variables.  \n<p>\nFor example, while the term <code>(Quote (isa ?X Cat))</code> simply denotes the open sentence <code>(isa ?X Cat)</code>, the expression\n<pre>\n  (Quote (EscapeQuote (isa ?X Cat)))\n</pre>\nis itself an open term in which <code>?X</code> occurs free; it thus does not denote in its own right, though many <i>instantiations</i> of it do denote.  E.g. the instantiation <code>(Quote (EscapeQuote (isa Patches-Cat Cat)))</code> denotes the sentence <code>(isa Patches-Cat Cat)</code>).\n<p>\nThe foregoing explanation generalizes to cases where multiple occurrences of <code>EscapeQuote</code> are within the scope of the same <code>Quote</code>.  For example, in the expression\n<pre>\n  (Quote (loves (EscapeQuote ?X) (EscapeQuote ?Y)))\n</pre>\n-- which is equivalent to <code>(Quote (EscapeQuote (loves ?X ?Y)))</code> -- both <code>?X</code> and <code>?Y</code> occur free.\n<p>\nAs mentioned above, the purpose of the <code>EscapeQuote</code> device is to enable \"quantifying into\" quoted contexts: to provide a coherent interpretation of formulas in which an occurrence of a Quantifier (or other ScopingRelation) that is outside the scope of a given occurrence of <code>Quote</code> can be viewed as binding occurrences of variables that are <i>inside</i> the scope of that <code>Quote</code>.  For example, the sentence\n<pre>\n  (thereExists ?X\n    (and\n      (isa ?X Cat)\n      (isa (Quote (EscapeQuote ?X)) CycLAtomicTerm)))\n</pre>\nsays that there is at least one cat that is denoted by a CycL atomic term.  Without the <code>EscapeQuote</code> wrapper, the second conjunct of the above would be a <i>closed</i> sentence, and the entire quantified sentence would express the far less interesting claim that there exists at least one cat and the expression <code>?X</code> is an atomic term of CycL.\n<p>\nNote that the above (interesting) existential claim could be expressed more tersely using QuasiQuote.  EscapeQuote is indispensible only in cases where one wants to allow <i>some but not all</i> of the free variables in a given expression to escape quotation.  For example, in the (implicitly quantified) rule\n<pre>\n  (isa\n    (Quote (loves ?X (EscapeQuote ?Y))) \n    CycLOpenSentence)\n</pre>\nonly the variable <code>?Y</code> occurs free; the <code>?X</code> is part of what gets quoted (and thus functions like a closed term that <i>denotes</i> the CycL variable <code>?X</code>).  What the rule says, in effect, is that any well-formed expression built with the predicate-expression <code>loves</code> followed by the variable <code>?X</code> followed by a CycL term is an open sentence of CycL.\n<p>\nFor more on the use of EscapeQuote and Quote for quantifying into quoted contexts, see the shared NoteAboutQuotingInCycL. See also denotes, quotedIsa, quotedArgument, and NoteAboutSyncategorematicSymbols.", 'UniversalVocabularyMt', vStrDef).
 8095exactlyAssertedEL_next(comment, 'equalStrings-CaseInsensitive', "(equalStrings-CaseInsensitive STRING1 STRING2) means that the CharacterStrings STRING1 and STRING2 contain the same characters in the same order, although some of the characters in STRING1 may differ in case from some of the characters in STRING2.  For example, (equalStrings-CaseInsensitive \"Foo\" \"fOo\") holds.", 'UniversalVocabularyMt', vStrDef).
 8096exactlyAssertedEL_next(comment, 'EnglishParaphraseMt', "An instance of both ParaphraseDataMicrotheory and GeneralMicrotheory.  EnglishParaphraseMt is the default context used for generating English paraphrases for CycL expressions.  Many of the assertions required for English paraphrase generation, including those with the predicates genFormat and genPhrase (qq.v.), can be found in this context.", 'BaseKB', vStrDef).
 8097exactlyAssertedEL_next(comment, 'ELRelation-Reversible', "A specialization of ELRelation (q.v.) instances of which appear only at the \"epistemological level\" (or EL) of the Cyc system, but whose original forms, or logically equivalent variants thereof, are retrievable via the CycUncanonicalizer.  Each instance of ELRelation-Reversible is associated, via the expansion (q.v.) or expansionDefn relation, to a sentence template to which the former is essentially equivalent and for which the former serves as a convenient alternative.  Furthermore, each instance of ELRelation-Reversible is also associated with a piece of code which can perform the inverse transformation.  Since each instance of ELRelation-Reversible requires special code support, this is a notAssertibleCollection.  More precisely:  A GAF (see CycLClosedAtomicSentence) whose main functor (or \"0th argument\") is a term that denotes a reversible EL relation can occur only at the EL, and not at the underlying HL (\"heuristic level\") of the system.  Thus, although one can use an EL-relation-based GAF to make an assertion to the system, the GAF that actually gets stored as an assertion in the Cyc Knowledge Base is a different (though logically equivalent) one that is related to the first via the expansion or expansionDefn assertion on the EL relation.  Upon assertion, the first GAF is transformed into the second GAF by the CycCanonicalizer.  Upon presentation to the user, the second GAF is transformed back into the first GAF, or a GAF which is logically equivalent, by the CycUncanonicalizer.  For example, willAlwaysBe is a reversible EL relation whose expansionDefn and associated piece of uncanonicalization code perform the following transformation:\n<p>\n(ist (MtSpace (MtTimeDimFn TIME) OTHER-DIMS) (willAlwaysBe P)\n<==>\n(ist (MtSpace (MtTimeDimFn (IntervalStartedByFn TIME)) OTHER-DIMS) P)\n<p>\nSo if one makes an assertion into an MT with time index T using the sentence `(willAlwaysBe P)', the assertion that actually shows up in the KB is `P' in an MT with time index (IntervalStartedByFn T).", 'UniversalVocabularyMt', vStrDef).
 8098exactlyAssertedEL_next(comment, 'ELRelation-OneWay', "A specialization of ELRelation (q.v.) instances of which appear only when input at the \"epistemological level\" (or EL) of the Cyc system, and whose original EL form is thereafter irretrievable.  Each instance of ELRelation-OneWay is associated, via the expansion or expansionDefn relation, to a sentence template to which the former is essentially equivalent and for which the former serves as a convenient alternative.  More precisely: A GAF (see CycLClosedAtomicSentence) whose main  functor (or \"0th argument\") is a term that denotes a one-way EL relation can  occur only at the EL, and not at the underlying HL (\"heuristic level\") of the system.  Thus, although one can use a one-way-EL-relation-based GAF to make an assertion to the system, the GAF that actually gets stored as an assertion in the Cyc Knowledge Base is a different (though logically  equivalent) one that is related to the first via the expansion assertion  on the EL relation.  Upon assertion, the first GAF is \"transformed into\" the second GAF by the CycCanonicalizer.  For example, lessThan is a one-way EL relation whose expansion correlate is the template (greaterThan :ARG2 :ARG1).  So if one makes an assertion using the sentence `(lessThan 1 2)', the assertion that actually shows up in the KB is `(greaterThan 2 1)'.  Note that terms for one-way EL relations _do_ appear in stored assertions in which  they occur in argument places other than the 0th; e.g. the sentence `(isa lessThan OrderingPredicate)' is in the KB.  One-way EL relations afford cyclists the convenience of having alternative forms of expression, while their expansions serve to minimize redundancy in the types of GAFs that the system has to store and reason with.", 'UniversalVocabularyMt', vStrDef).
 8099exactlyAssertedEL_next(comment, 'ELRelation', "A specialization of MacroRelation (q.v.) instances of which appear only at the \"epistemological level\" (or EL) of the Cyc system.  Each instance of ELRelation is associated, via the expansion or expansionDefn relation, to a sentence template to which the former is essentially equivalent and for which the former serves as a convenient alternative.  Some assertions using instances of ELRelation are irretrievable after being input to the Cyc System (ELRelation-OneWay), and others' EL forms are reconstructed dynamically by the system (ELRelation-Reversible).", 'UniversalVocabularyMt', vStrDef).
 8100exactlyAssertedEL_next(comment, 'DontReOrderCommutativeTerms', "A CanonicalizerDirective (q.v.) that directs the CycCanonicalizer not to re-order commutative terms that appear in the CycL assertions.", 'CoreCycLImplementationMt', vStrMon).
 8101exactlyAssertedEL_next(comment, 'DocumentationPredicate', "A PredicateType whose instances are Predicates specifically designed for in-KB documentation purposes, such as  facilitating Cyclists in their understanding of the Cyc system, tracking knowledge representation work being done in the Cyc Knowledge Base, or noting cleanup work to be done.  \n<p>\nNote that documentation predicates are usually not involved in inference.  They may be excluded from knowledge bases in which available memory is a premium without affecting the performance of applications. DocumentationPredicate is used in code to determine which documentation to show to the user when they request to see documentation for a first-order reified term (or \"FORT\").", 'UniversalVocabularyMt', vStrDef).
 8102exactlyAssertedEL_next(comment, 'DocumentationConstant', "A collection of CycL constants whose purpose is to facilitate users in their understanding of the system, tracking knowledge representation work being done, noting cleanup work to be done, etc. Documentation constants are usually not involved in inference.  Instances may be excluded from versions of the knowledge base in which available memory is a premium without affecting the performance of applications.", 'UniversalVocabularyMt', vStrDef).
 8103exactlyAssertedEL_next(comment, 'DistributingMetaKnowledgePredicate', "A subcollection of MetaKnowledgePredicate (q.v.).  Each instance of DistributingMetaKnowledgePredicate is a meta-knowledge predicate that can be used to make meta-assertions (i.e it can take a CycLAssertion as an argument) and is such that, when applied to an EL-level assertion that polycanonicalizes (i.e. gets transformed by the Cyc canonicalizer into multiple HL-level assertions), it is automatically \"distributed\" over each of the multiple assertions resulting from the polycanonicalization.\n<p>\nLet METAPRED be an instance of DistributingMetaKnowledgePredicate. Suppose that one asserts <code>(METAPRED ASSERTION FOO)</code> and that <code>ASSERTION</code> polycanonicalizes into <code>ASSERTION1</code> and <code>ASSERTION2</code>.  Then <code>(METAPRED ASSERTION1 FOO)</code> and <code>(METAPRED ASSERTION2 FOO)</code> will both be asserted to the Knowledge Base automatically.\n<p>\nFor example, if I assert this at the EL-level:\n<pre>\n  (comment\n    (and (isa Muffet Dog) (likesAsFriend Muffet Patches-Cat))\n    \"Muffet digs Patches.\"),\n</pre>\n<p>\nboth of these will automatically be asserted a the HL-level:\n<p>\n\t<code>(comment (isa Muffet Dog) \"Muffet digs Patches.\")</code>\n<p>\n\t<code>(comment (likesAsFriend Muffet Patches-Cat) \"Muffet digs Patches.\")</code> .\n<p>\nSee also the shared note MetaAssertionsForPolycanonicalizingAssertions.", 'UniversalVocabularyMt', vStrDef).
 8104exactlyAssertedEL_next(comment, 'DisjointCollectionType', "A collection of collections of collections and a specialization of SiblingDisjointCollectionType (q.v.).  A disjoint collection type is such that its instances are collections that are all disjoint from one another.  That is, each instance <code>DISCOLTYPE</code> of DisjointCollectionType is a collection whose instances are mutually disjoint collections: no two instances of <code>DISCOLTYPE</code> have any instances in common.  Instances of DisjointCollectionType include BiologicalSpecies and SportsTeamTypeBySport.", 'UniversalVocabularyMt', vStrDef).
 8105exactlyAssertedEL_next(comment, 'DirectedMultigraph', "A specialization of both DirectedPathSystem and Multigraph.  Each instance of DirectedMultigraph is a multigraph in which every link has one direction.  Note that there can be loops and multiple links between a pair of nodes in a given instance of DirectedMultigraph.", 'UniversalVocabularyMt', vStrDef).
 8106exactlyAssertedEL_next(comment, 'DifferenceFn', "A binary MathematicalFunctionOnScalars and an extension of the arithmetic subtraction operation to ScalarIntervals (q.v.) generally.  When applied to two arithmetically-comparable scalars, MINUEND and SUBTRAHEND, DifferenceFn yields the scalar that is the result of subtracting SUBTRAHEND from MINUEND.  For example, (DifferenceFn 88 11) is 77 and (DifferenceFn (Kilogram 4.2) (Kilogram 3)) is (Kilogram 1.2).\n<p>\nNote that when MINUEND and SUBTRAHEND are not arithmetically-comparable, (DifferenceFn MINUEND SUBTRAHEND) is undefined.  For example, (DifferenceFn (MinutesDuration 1) (Meter 3)) is undefined, since (MinutesDuration 1) is a Time-Quantity and (Meter 3) is a Distance, and time-quantities are not comparable with distances.\n<p>\nFor addition, see PlusFn.", 'UniversalVocabularyMt', vStrDef).
 8107exactlyAssertedEL_next(comment, 'DefaultTrue', "An instance of CycHLTruthValue.  DefaultTrue is the attribute of being assumed true unless otherwise known to be false.", 'BaseKB', vStrDef).
 8108exactlyAssertedEL_next(comment, 'DefaultMonotonicPredicate', "A collection of predicates.  Each instance of DefaultMonotonicPredicate is a predicate whose use as the predicate of a locally asserted ground formula causes that formula to be entered, by default, as :MONOTONIC.  Examples: isa, genls, disjointWith, equals, arity, arg1Isa.", 'UniversalVocabularyMt', vStrDef).
 8109exactlyAssertedEL_next(comment, 'DefaultFalse', "An instance of CycHLTruthValue.  DefaultFalse is the attribute of being assumed false unless otherwise known to be true.", 'BaseKB', vStrDef).
 8110exactlyAssertedEL_next(comment, 'December', "A specialization of CalendarMonth.  Each instance of December is the twelth and final month of a particular year in the GregorianCalendar (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8111exactlyAssertedEL_next(comment, 'DayOfWeekType', "A collection of collections and a specialization of WeeklyTemporalObjectType.\nEach instance of DayOfWeekType is a collection of CalendarDays, all of\nwhose instances correspond to the same particular \"day of the week\" in \nthe respective weeks in which they occur.  For example, Monday -- the \ncollection of all mondays -- is an instance of DayOfWeekType.", 'UniversalVocabularyMt', vStrDef).
 8112exactlyAssertedEL_next(comment, 'DateEncodeStringFn', "(DateEncodeStringFn TEMPLATE DATE) returns a string encoding of DATE (an instance of Date) in the format described by the TEMPLATE string.  For example,    (DateEncodeStringFn 'MM/DD/YYYY'      (DayFn 20 (MonthFn July (YearFn 1969))))  would return '07/20/1969'.  See also DateDecodeStringFn.", 'UniversalVocabularyMt', vStrMon).
 8113exactlyAssertedEL_next(comment, 'DateDecodeStringFn', "(DateDecodeStringFn TEMPLATE DATE-STRING) returns a Date which is the result of decoding DATE-STRING by the format described by the TEMPLATE string.  For example,   (DateDecodeStringFn 'MM/DD/YYYY' '07/20/1969') would return (DayFn 20 (MonthFn July (YearFn 1969))).   See also DateEncodeStringFn.", 'UniversalVocabularyMt', vStrMon).
 8114exactlyAssertedEL_next(comment, 'CycTransformationProof', "The nearestGenls of CycProof each of whose instances uses a CycLRuleAssertion to prove a query.", 'UniversalVocabularyMt', vStrMon).
 8115exactlyAssertedEL_next(comment, ftVar, "The collection of all variables in the CycL language.\nA CycLVariable is a character string consisting of a question mark '?' (as its initial character) followed by one or more characters, where each of these latter characters is either an (upper- or lower-case) Roman letter, an Arabic numeral (i.e. '0' through '9'), a hyphen ('-'), an underscore ('_'), or another question mark.  (The letters occurring in a CycL variable used in an actual assertion will typically be all uppercase; but this convention is not enforced in any formal way.)  Examples: '?WHAT', '?OBJ-TYPE', and '?var0'.", 'UniversalVocabularyMt', vStrDef).
 8116exactlyAssertedEL_next(comment, 'CycLTruthValueSentence', "A collection of CycL sentences containing only the CycL sentences <code>True</code> and <code>False</code>, both of which are sentential constants.", 'UniversalVocabularyMt', vStrMon).
 8117exactlyAssertedEL_next(comment, 'CycLTerm', "The collection of all syntactically well-formed   expressions in the CycL language that can be used as terms, i.e. that can be combined with other expressions to form non-atomic terms or formulas.  Since the grammar of the CycL language allows any CycL expression to be used as a term, CycLTerm and CycLExpression are coextensional collections.", 'UniversalVocabularyMt', vStrDef).
 8118exactlyAssertedEL_next(comment, 'CycLSentence-ClosedPredicate', "The subcollection of CycLSentences whose arg0 does not contain a free variable although free variables may occupy other argument positions.", 'UniversalVocabularyMt', vStrMon).
 8119exactlyAssertedEL_next(comment, 'CycLSentence-Assertible', "An instance of CycLExpressionType and a specialization of CycLExpression-Assertible and CycLSentence-Askable.  This is the collection of all CycL sentences that could be asserted to the Cyc Knowledge Base.  More precisely, each instance of CycLSentence-Assertible is a CycL sentence that is both syntactically and semantically well-formed.  By definition, any CycL sentence is syntactically well-formed.  To be semantically well-formed, a CycL sentence must be constructible via the syntax of CycL without violating any applicable arity or argument-type constraints (see arity and ArgTypePredicate).  A CycL sentence must be semantically well-formed in order to be interpretable as having a \"semantic value\", which for sentences means having a truth value.  Note that being \"assertible\" in the present sense does not require a sentences's actually being asserted in the KB.", 'UniversalVocabularyMt', vStrDef).
 8120exactlyAssertedEL_next(comment, 'CycLSentence-Askable', "The collection of CycLSentences that are askable as queries to the Cyc system.  More precisely, each  instance of CycLSentence-Askable is a CycL sentence that is  constructible via the syntax of CycL without violating any applicable  arity constraints (see arity).  Note that askable CycL sentences do  not necessarily obey other semantic constraints beyond arity, such as  argument-type constraints (see ArgTypePredicate); thus they are  not always semantically well-formed in the fullest sense (cf.  CycLSentence-Assertible).  The idea behind this criterion of  \"askability\" is that such a sentence, even if it isn't true or false (which it can't be unless it also obeys all argument-type  constraints), at least \"makes enough sense\" to be asked as a query  to the Cyc system.", 'UniversalVocabularyMt', vStrDef).
 8121exactlyAssertedEL_next(comment, 'CycLSentence', "The collection of syntactically well-formed sentences of the CycL language.  Each instance of CycLSentence consists of a CycL expression denoting an instance of TruthFunction (e.g. an instance of Predicate or SententialRelation) followed by one or more CycL terms (see CycLTerm), with the entire sequence enclosed in parentheses.  \n<p>\nFor example, (isa Collection Thing) and (genls ?FOO SpatialThing) are both CycL sentences.  Note that CycLSentences <i>need not</i> obey arity constraints (see arity) or other semantic constraints (such as argument type constraints; see ArgTypePredicate).  Thus, for example, (genls ?FOO SpatialThing EiffelTower) is a CycL sentence.\n<p>\nCycLSentences are also called \"logical formulas\", and are to be distinguished from \"denotational formulas\" (which are also known as \"NAT\"s; see CycLNonAtomicTerms).  Note that this notion of a CycL sentence is broader than the notion of \"sentence\" standardly used in formal logic, where a sentence is defined as a <i>closed</i> well-formed formula: CycL sentences may be <i>open</i> (i.e. they may contain free variables; see the specialization CycLOpenSentence).", 'UniversalVocabularyMt', vStrDef).
 8122exactlyAssertedEL_next(comment, 'CycLRuleAssertion', "The subcollection of semantically well-formed CycLAssertions whose formulas are rules.\nMore precisely, the formulas are not\nGAFs (see CycLGAFAssertion), so they either have more than one literal (and therefore are\nnon-atomic) or they quantify over some free variables (and therefore are non-ground).\nAny free variables are implicitly universally quantified.", 'UniversalVocabularyMt', vStrDef).
 8123exactlyAssertedEL_next(comment, 'CycLRepresentedTerm', "The collection of all denotational terms that are represented in the CycL language, instead of being defined in SubL, the underlying implementation language used by Cyc.  That is, each instance of CycLRepresentedTerm is either (i) an atomic term, and thus also an instance of CycLRepresentedAtomicTerm (q.v.), or (ii) a non-atomic term (or \"NAT\"), and has a CycLRepresentedTerm as its arg0 functor (the other arguments in the NAT\nneed not be CycL represented terms).  Thus CycLRepresentedTerm has as instances all CycLConstants, all CycLVariables, and all CycLNonAtomicTerms.", 'UniversalVocabularyMt', vStrDef).
 8124exactlyAssertedEL_next(comment, 'CycLRepresentedAtomicTerm', "A specialization of CycLAtomicTerm.  An instance ATOM of CycLAtomicTerm is also an instance of CycLRepresentedAtomicTerm just in case ATOM is explicitly represented in the CycL language (as opposed to being represented in SubL, the underlying implementation language of the Cyc system).  Important specializations of CycLRepresentedAtomicTerm include CycLVariable and CycLConstant.", 'UniversalVocabularyMt', vStrDef).
 8125exactlyAssertedEL_next(comment, 'CycLReifiedDenotationalTerm', "The collection of denotational terms in the CycL language which are\nreified in the KB.  Examples include Muffet and (JuvenileFn Dog); a\ncounterexample would be (JuvenileFn Platypus) because that term is not\ncurrently reified in the KB.  These are often called 'FORTs', which stands for\n'first-order reified terms'", 'UniversalVocabularyMt', vStrDef).
 8126exactlyAssertedEL_next(comment, 'CycLReifiableNonAtomicTerm', "A collection of Cyc terms that are NATs (CycLNonAtomicTerms; see\nFunction-Denotational) whose functor is an instance of\nReifiableFunction. E.g., since GovernmentFn is an instance of\nReifiableFunction, it is true that (GovernmentFn France) is a\nCycLReifiableNonAtomicTerm.", 'UniversalVocabularyMt', vStrDef).
 8127exactlyAssertedEL_next(comment, 'CycLReifiableDenotationalTerm', "A subcollection of both CycLClosedDenotationalTerm and CycLIndexedTerm (qq.v.).  CycLReifiableDenotationalTerm is the collection of all CycL terms that both may be reified and may denote something in the universe of discourse. It thus includes all instances of CycLConstant as well as any NAT (see CycLNonAtomicTerm) whose main functor denotes an instance of ReifiableFunction.\n<p>\nFor example, the NAT '(GovernmentFn France)' is a CycLReifiableDenotationalTerm, since GovernmentFn is a ReifiableFunction.  Similarly,  '(JuvenileFn Platypus)' is a CycL reifiable denotational term; although it is not currently reified in the KB, it is reifiable and denotational (see CycLClosedDenotationalTerm).  Finally, '(BorderBetweenFn Canada Mexico)' is a CycL reifiable denotational term; although it happens not to denote anything in the universe of discourse, it is nonetheless the kind of NAT that can and usually does denote.\n<p>\nNote that CycLVariables are not considered reifiable terms.", 'UniversalVocabularyMt', vStrDef).
 8128exactlyAssertedEL_next(comment, 'CycLReformulationRulePredicate', "The collection of Predicates which may appear as the operator in a CycLReformulatorRule.", 'UniversalVocabularyMt', vStrDef).
 8129exactlyAssertedEL_next(comment, 'CycLPropositionalSentence', "The collection of CycL sentences that express propositions (see Proposition).  Two necessary conditions for a CycL sentence's expressing a proposition is that it be closed (see CycLClosedSentence) and not violate any applicable arity constraints (see CycLSentence-Askable).", 'UniversalVocabularyMt', vStrDef).
 8130exactlyAssertedEL_next(comment, 'CycLOpenSentence', "A specialization of both CycLOpenExpression and CycLSentence. The collection of CycL sentences that contain one or more free variables.  Note that those CycL sentences that are treated (in the context of representing assertions in the Cyc Knowledge Base) as implicitly containing initial universal quantifiers are in fact CycLOpenSentences.", 'UniversalVocabularyMt', vStrDef).
 8131exactlyAssertedEL_next(comment, 'CycLOpenNonAtomicTerm', "The collection of denotational CycLNonAtomicTerms that have free variables. Examples: `(JuvenileFn ?X)', `(JuvenileFn ?X ?Y ?Z)'.  Counterexample: `(TheSetOf ?X (objectHasColor ?X GreenColor))'.", 'UniversalVocabularyMt', vStrDef).
 8132exactlyAssertedEL_next(comment, 'CycLOpenFormula', "A specialization of both CycLOpenExpression and CycLFormula (qq.v.).  The collection of compound CycL expressions that contain one or more free variables.", 'UniversalVocabularyMt', vStrDef).
 8133exactlyAssertedEL_next(comment, 'CycLOpenExpression', "A specialization of CycLExpression.  The collection of CycL expressions that contain one or more free variables.  A CycLVariable VAR occurs _free_ in an expression EXPR if and only if there is an occurrence of VAR in EXPR that is not bound by another term in EXPR that denotes a Quantifier or other ScopingRelation (q.v.).  For example, the expression `(isa ?X Cat)' is open, but `(thereExists ?X (isa ?X Cat))' is not.", 'UniversalVocabularyMt', vStrDef).
 8134exactlyAssertedEL_next(comment, 'CycLOpenDenotationalTerm', "The collection of all open denotational terms in the CycL language.  An expression is \"open\" if it contains one or more free variables (see CycLOpenExpression).  A CycL term is said to be \"denotational\" if it is the right sort of term to have a denotation (or value) in the universe of discourse (see CycLDenotationalTerm).  Each instance of CycLOpenDenotationalTerm is either a CycLOpenNonAtomicTerm (i.e. a \"NAT\" with a free variable) or a CycLVariable itself.  Examples include `?X', `(JuvenileFn ?X)', and `(JuvenileFn isa ?X genls JuvenileFn)' (even though the latter is semantically ill-formed).", 'UniversalVocabularyMt', vStrDef).
 8135exactlyAssertedEL_next(comment, 'CycLNonAtomicTerm-ClosedFunctor', "The subcollection of denotational CycLNonAtomicTerms which have no free variable in the arg0 position.\nExamples: (JuvenileFn Platypus), (JuvenileFn isa genls), (TheSetOf ?X (colorOfType ?X GreenColor)), (JuvenileFn ?X).  Counterexample: (?SOMEFN Gold) ((USDollarFn ?YEAR) 5).", 'UniversalVocabularyMt', vStrMon).
 8136exactlyAssertedEL_next(comment, 'CycLNonAtomicTerm-Assertible', "A CycLExpressionType and a specialization of both CycLExpression-Assertible and CycLNonAtomicTerm (qq.v.).  The collection of all CycL non-atomic terms that could appear within a sentence that could be asserted to the Cyc Knowledge Base.  More precisely, each instance of CycLNonAtomicTerm-Assertible is a non-atomic term that is both syntactically and semantically well-formed.  By definition, any CycL non-atomic term is syntactically well-formed.  To be semantically well-formed, a non-atomic term sentence must be constructible via the syntax of CycL without violating any applicable arity or argument-type constraints (see arity and ArgTypePredicate).  A CycL term must be semantically well-formed in order to be interpretable as having a \"semantic value\", which for terms means having a denotation.  Note that being \"assertible\" in the present sense does not require a sentence's actually being asserted in the KB.", 'UniversalVocabularyMt', vStrDef).
 8137exactlyAssertedEL_next(comment, 'CycLNonAtomicTerm-Askable', "The collection of CycLNonAtomicTerms\nthat can appear within sentences that are askable as queries to the Cyc system\n(see CycLSentence-Askable).  More precisely, each instance of \nCycLNonAtomicTerm-Askable is a CycL non-atomic term that is constructible via \nthe syntax of CycL without violating any applicable arity constraints (see \narity).  Note that askable CycL non-atomic terms do not necesarily obey other \nsemantic constraints beyond arity, such as argument-type constraints (see \nArgTypePredicate); thus they are not always semantically well-formed in \nthe fullest sense (cf. CycLNonAtomicTerm-Assertible).", 'UniversalVocabularyMt', vStrDef).
 8138exactlyAssertedEL_next(comment, 'CycLNonAtomicTerm', "A CycLExpressionType and a specialization of both CycLFormula \nand CycLRepresentedTerm (qq.v.).  CycLNonAtomicTerm is the \ncollection of non-atomic denotational terms in the CycL language.  \nA CycL term is _non-atomic_ if it is constructible from other CycL \nterms via the syntax of CycL.  A CycL term is said to be \n\"denotational\" if it is the type of term that can have a \ndenotatum (or assigned value; see CycLDenotationalTerm).  \nCycLNonAtomicTerm thus includes all CycL denotational terms \nexcept constants and variables.  A CycL non-atomic term (or \"NAT\") \nconsists of a CycL expression denoting a Function-Denotational \nfollowed by one or more CycL terms, with the entire sequence \nenclosed in parentheses.  The NAT itself denotes the value (if any) \nof this function for the denotations of the other terms taken as \narguments.  (If there is no such value then the NAT has no denotatum;\nsee undefined.)  NATs are also known as \"denotational formulas\", \nin contrast to \"logical formulas\" (i.e. sentences).  Currently, \nthere are two main types of NAT: (i) HLNonAtomicReifiedTerms (or \n\"NART\"s), which are a type of HLReifiedDenotationalTerm and are \nimplemented with data structures that have indexing that enables all \nuses of the NAT to be retrieved, and (ii) ELNonAtomicTerms (or \n\"NAUT\"s), which have no such indexing and remain in the \nform of an EL expression in the assertions in which\nthey occur.", 'UniversalVocabularyMt', vStrDef).
 8139exactlyAssertedEL_next(comment, 'CycLNonAtomicReifiedTerm', "The subcollection of CycLReifiableNonAtomicTerms that are reified in the KB. Example: (JuvenileFn Dog).  Counterexample: (JuvenileFn Platypus), because that term is not currently reified in the KB.  These are often called NARTs, which stands for 'non-atomic reified term'.", 'UniversalVocabularyMt', vStrDef).
 8140exactlyAssertedEL_next(comment, 'CyclistDefinitionalMt', "The microtheory in which instances of Cyclist are defined.  Assertions about them belong in CyclistsMt.", 'BaseKB', vStrMon).
 8141exactlyAssertedEL_next(comment, 'Cyclist', "A specialization of IndividualAgent. Each instance of Cyclist is an agent (usually a person) entitled to inspect and modify the Cyc knowledge base.", 'UniversalVocabularyMt', vStrDef).
 8142exactlyAssertedEL_next(comment, 'CycLIndexedTerm', "The collection of indexed or indexable terms in the CycL language.\nThis includes reified HL terms as well as reifiable EL NATs and assertions.", 'UniversalVocabularyMt', vStrDef).
 8143exactlyAssertedEL_next(comment, 'CycLGenericRelationFormula', "A subcollection of CycLFormula (q.v.).  Each instance of that CycLGenericRelationFormula is a CycL formula that begins (immediately after the opening parenthesis) with a variable or other open expression (see CycLOpenExpression); i.e. it has an open expression in its \"0th\" or \"arg0\" position.  A CycL generic relation formula thus consists \nof an open expression followed by some number of terms, with the entire sequence \nenclosed in parentheses.  But note that the open expression in the formula's \narg0 position must be such that, given the syntax and intended semantics of CycL, it could conceivably have a Relation -- i.e. a Function-Denotational or a TruthFunction (such as a Predicate or LogicalConnective) -- as its semantic value.  Hence the arg0 open expression might be a variable, as in the generic relation formula `(?RELATION Muffet Dog)'; or it might be an appropriate open non-atomic term (or \"NAT\"; see CycLNonAtomicTerm), as in \n`((Kappa (?ARG1) (knows ?ARG1 ?ARG2)) Muffet)'; or it might itself be \na generic relation formula, as in `((?REL ?ARG1 Dog) Muffet)'.  On the \nother hand, `((BorderBetweenFn ?ARG1 ?ARG2) Muffet Dog)' is not a \nCycLGenericRelationFormula, since BorderBetweenFn only returns instances \nof Border, which is disjoint with Relation; thus the open NAT \n`(BorderBetweenFn ?ARG1 ?ARG2)' couldn't possibly have a Relation as its \nsemantic value, no matter what values were assigned to the variables `?ARG1' \nand `?ARG2'.", 'UniversalVocabularyMt', vStrDef).
 8144exactlyAssertedEL_next(comment, 'CycLGAFAssertion', "A CycLExpressionType and a specialization of both CycLAtomicAssertion and CycLClosedAtomicSentence (qq.v.).  This is the collection of all and only the closed atomic CycL sentences that have been asserted to the Knowledge Base or deduced there by the inference engine.  GAF assertions typically express particular facts (as opposed to general rules) about the world.  The acronym `GAF' stands for \"ground atomic formula\"; see CycLClosedAtomicSentence.\n<p>\nAt the epistemological level (see ELExpression), a GAF assertion contains no free variables and is thus (at least) \"ground\".  At the heuristic level (see HLExpression), however, the HLAssertion(s) representing the GAF assertion -- the sentence(s) that are actually stored in the KB -- contain no variables whatsoever and are thus \"_fully_ ground\" (see CycLFullyGroundAtomicSentence).  For example, if the ground atomic sentence\n<p>\n(isa (TheSetOf ?X (objectHasColor ?X GreenColor)) Thing)\n<p>\nwere asserted it would be a GAF assertion, and it would be represented in the KB by some fully ground atomic sentence(s) containing no variables at all.", 'UniversalVocabularyMt', vStrDef).
 8145exactlyAssertedEL_next(comment, 'CycLFormulaicSentence', "A subcollection of syntactically well-formed sentences of the CycL language. Each instance of CycLFormulaicSentence consists of a CycL expression denoting an instance of TruthFunction (e.g., an instance of Predicate or SententialRelation) followed by one or more CycL terms (see CycLTerm), with the entire sequence enclosed in parentheses. For example, (isa Collection Thing) and (genls ?FOO SpatialThing) are both formulaic CycL sentences. The only two CycL sentences that are not formulaic are True and False. Note that CycLFormulaicSentences need not obey arity constraints (see arity) or other semantic constraints (such as argument type constraints ; see ArgTypePredicate). CycLFormulaicSentences are also called \"logical formulas\", and are to be distinguished from \"denotational formulas\" (which are also known as \"NAT\"s; see CycLNonAtomicTerms). Note that this notion of a formulaic CycL sentence is broader than the notion of \"sentence\" standardly used in formal logic, where a sentence is defined as a _closed_ well-formed formula: formulaic CycL sentences may be _open_ (i.e., contain free variables; see CycLOpenSentence).", 'UniversalVocabularyMt', vStrMon).
 8146exactlyAssertedEL_next(comment, 'CycLFormula', "The collection of compound CycL expressions.  Each instance of CycLFormula consists of a CycL expression that denotes a relation (e.g. a Predicate, Function-Denotational, or TruthFunction) -- or at least an expression that could be interpreted as having a relation as its semantic value (see CycLGenericRelationFormula) -- followed by one or more CycL terms (see CycLTerm), with the entire sequence enclosed in parentheses.  For example, (isa Muffet Poodle) and (BirthFn Muffet) are both CycL formulas.  Two important specializations of CycLFormula are CycLNonAtomicTerm (whose instances are also called \"denotational formulas\") and CycLSentences (whose instances are also called \"logical formulas\").  Note that this notion of \"formula\" differs somewhat from that used in formal logic, where a formula is normally defined as an (atomic or non-atomic, quantificationally closed or open) sentence.", 'UniversalVocabularyMt', vStrDef).
 8147exactlyAssertedEL_next(comment, ttExpressionType, "A collection of collections.  Each instance of CycLExpressionType is a type (i.e. a subcollection) of CycLExpression.  Note that, while CycLExpressionType is not itself a quotedCollection (q.v.), most of its reified instances are quoted-collections.", 'UniversalVocabularyMt', vStrDef).
 8148exactlyAssertedEL_next(comment, 'CycLExpression-Assertible', "A CycLExpressionType.  The collection  of all compound CycL expressions that either could themselves be asserted to the  Cyc Knowledge Base (see CycLSentence-Assertible) or could appear as denotational terms within sentences that could be so asserted (see CycLDenotationalTerm-Assertible).  More precisely, each instance of CycLExpression-Assertible is a CycL expression that is both syntactically and semantically well-formed.  By definition, any compound CycL expression is  syntactically well-formed.  To be semantically well-formed, a CycL expression  must be constructible via the syntax of CycL without violating any applicable arity or argument-type constraints (see arity and ArgTypePredicate).  A CycL expression must be semantically well-formed in order to be interpretable as having a \"semantic value\", such as a truth-value (if the expression is a sentence) or a denotation (if it's a CycLDenotationalTerm).  Note that being \"assertible\" in the present sense does not require an expression's actually being asserted in (or being a component of something asserted in) the KB.", 'UniversalVocabularyMt', vStrDef).
 8149exactlyAssertedEL_next(comment, 'CycLExpression-Askable', "The collection of CycLExpressions\nthat are either themselves askable as queries to the Cyc system (see \nCycLSentence-Askable) or could appear as non-atomic terms within \nsentences that could be so asked (see CycLNonAtomicTerm-Askable). \nMore precisely, each instance of CycLExpression-Askable is a CycL \nexpression that is constructible via the syntax of CycL without \nviolating any applicable arity constraints (see arity).  Note that \naskable CycL expressions do not necesarily obey other semantic \nconstraints beyond arity, such as argument-type constraints (see \nArgTypePredicate); thus they are not always semantically \nwell-formed in the fullest sense (cf. CycLExpression-Assertible).", 'UniversalVocabularyMt', vStrDef).
 8150exactlyAssertedEL_next(comment, 'CycLExpression', "The collection of all (and only) expressions in the CycL language.  This includes all constants, variables, and formulas (i.e. non-atomic terms and sentences).  Each CycL expression is, trivially, a <i>syntactically</i> well-formed expression of CycL; but note that it might or might not be \"<i>semantically</i> well-formed\" (see CycLExpression-Assertible).  Also note that, since the CycL syntax allows any CycL expression to be used as a term, CycLExpression is coextensional with CycLTerm (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8151exactlyAssertedEL_next(comment, 'CycLDenotationalTerm-Assertible', "A CycLExpressionType and a specialization of both CycLDenotationalTerm and CycLExpression-Assertible (qq.v.).  This is the collection of all CycL denotational terms that could appear within a sentence that could be asserted to the Cyc Knowledge Base.  More precisely, each instance of CycLDenotationalTerm-Assertible is a denotational (i.e. non-logical) term that is both syntactically and semantically well-formed.  By definition, any CycL term is syntactically well-formed.  To be semantically well-formed, denotational term sentence must be either be atomic (see CycLAtomicTerm) or constructible via the syntax of CycL (see CycLNonAtomicTerm-Assertible) without violating any applicable arity or argument-type constraints (see arity and ArgTypePredicate).  A CycL term must be semantically well-formed in order to be interpretable as having a \"semantic value\", which for denotational terms means having a denotation.  Note that being \"assertible\" in the present sense does not require a sentence's actually being asserted in the KB.", 'UniversalVocabularyMt', vStrDef).
 8152exactlyAssertedEL_next(comment, 'CycLDenotationalTerm', "The collection of all CycL terms that are not sentences (cf. CycLSentence), and thus are either CycLAtomicTerms (such as constants or variables) or CycLNonAtomicTerms (also known as \"NAT\"s).   CycLDenotationalTerms are so-called, not because they all have denotations (not all of them do), but because they are in a certain sense the right kind of term for having a denotation.  That is, an instance of CycLDenotationalTerm -- if it is semantically well-formed and closed (i.e. contains no free variables) -- might denote something in the universe of discourse.  (Even so, it will not _necessarily_ denote something, considering (e.g.) the fact that a function need not be defined for every (sequence of) thing(s) satisfying its argument type constraints; see PartialFunction.)  But note that neither semantic well-formedness nor being closed is a requirement for being a CycL denotational term: `(JuvenileFn isa ?X genls JuvenileFn)', for example, is a NAT and thus a denotational term.  Other examples of denotational terms are the expressions: `Muffet', `?X', `(JuvenileFn ?X)', `(TheSetOf ?X (objectHasColor ?X GreenColor))', and `212'.  Note also that, like most instances of CycLExpressionType, CycLDenotationalTerm is a quotedCollection (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8153exactlyAssertedEL_next(comment, 'CycLDeducedAssertion', "The subcollection of semantically well-formed CycLAssertions that are supported by at least one argument which is a deduction by Cyc's inference engine, as opposed to having been explicitly asserted to Cyc. A given assertion can have more than one argument, and can therefore be both a CycLAssertedAssertion and a CycLDeducedAssertion.", 'UniversalVocabularyMt', vStrDef).
 8154exactlyAssertedEL_next(comment, 'CycLConstant', "The collection of all constants in the CycL language. CycLConstant has as instances all CycLAtomicTerms other than CycLVariables and SubLAtomicTerms (qq.v.).  Orthographically, CycL constants are those atomic terms (i.e. terms not constructable from other terms via CycL syntax) that are prefixed by '' in their printed (as opposed to their HTML-displayed) representations.  For example, 'Dog' and 'isa' are CycL constants, while other CycL terms like '?X', '42', and  '(GovernmentFn France)' are not.", 'UniversalVocabularyMt', vStrDef).
 8155exactlyAssertedEL_next(comment, 'CycLClosedSentence', "A specialization of both CycLSentence and CycLClosedExpression.  The collection of CycL sentences that contain no free variables.  Note that those CycL sentences that are treated (in the context of representing assertions in the Cyc Knowledge Base) as implicitly containing universal quantifiers are <i>not</i> closed sentences (cf. CycLOpenSentence).", 'UniversalVocabularyMt', vStrDef).
 8156exactlyAssertedEL_next(comment, 'CycLClosedNonAtomicTerm', "The collection of closed, non-atomic denotational terms of the CycL language.  Each instance of CycLClosedNonAtomicTerm is a CycL term that contains no free variables, is constructible from other CycL terms via the syntax of CycL, and can have a denotatum (this last requirement excludes closed CycL sentences from CycLClosedNonAtomicTerm).  Examples: `(JuvenileFn Platypus)', `(JuvenileFn isa genls)', and `(TheSetOf ?X (objectHasColor ?X GreenColor))'.  Non-example: `(JuvenileFn ?X)'.", 'UniversalVocabularyMt', vStrDef).
 8157exactlyAssertedEL_next(comment, 'CycLClosedFormula', "A specialization of both CycLFormula and CycLClosedExpression.  The collection of compound expressions of CycL that contain no free variables.", 'UniversalVocabularyMt', vStrDef).
 8158exactlyAssertedEL_next(comment, 'CycLClosedExpression', "The collection of CycLExpressions that contain no free variables.  (A variable VAR occurs _free_ in an expression EXPR if and only if there is an occurrence of VAR in EXPR that is not bound by a quantifier or other ScopingRelation (q.v.) in EXPR.)  Note that those CycL sentences that are treated (in the context of representing assertions in the Cyc Knowledge Base) as implicitly containing universal quantifiers are _not_ closed expressions (see CycLClosedSentence). Also cf. CycLOpenExpression.", 'UniversalVocabularyMt', vStrDef).
 8159exactlyAssertedEL_next(comment, 'CycLClosedDenotationalTerm', "The collection of all closed denotational terms in the CycL language.  An expression is said to be \"closed\" if it contains no free variables (see CycLClosedExpression).  A CycL term is said to be \"denotational\" if it is the right sort of term to have a denotation (or value) in the universe of discourse (see CycLDenotationalTerm).  CycL sentences, while terms of CycL, are not considered denotational terms.  Each instance of CycLClosedDenotationalTerm is either a CycLClosedAtomicTerm (i.e. a CycLConstant or SubLAtomicTerm) or a CycLClosedNonAtomicTerm (i.e. a \"NAT\" with no free variables).  Examples of closed denotational terms include `Muffet', `(JuvenileFn Dog)', `(TheSetOf ?X (objectHasColor ?X GreenColor))', and `212'.  Note that these are also examples: `(BorderBetweenFn Canada Mexico)' (despite the fact that it fails actually to denote anything) and `(JuvenileFn isa genls JuvenileFn)'\n(despite the fact that it is not semantically well-formed).", 'UniversalVocabularyMt', vStrDef).
 8160exactlyAssertedEL_next(comment, 'CycLClosedAtomicTerm', "The collection of all closed CycLAtomicTerms.  \"Closed\" here means not containing any free (i.e. unbound) variables.  Since a variable itself is the only type of _atomic_ term that contains a variable (and contains it _free_, moreover, as a single occurrence of a variable can't bind itself), CycLClosedAtomicTerm has as instances all CycLAtomicTerms except CycLVariables.  Like all CycL atomic terms, Cycl closed atomic terms are \"denotational\" (see CycLDenotationalTerm).  Note that this collection, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 8161exactlyAssertedEL_next(comment, 'CycLClosedAtomicSentence', "A CycLExpressionType and a specialization of both CycLAtomicSentence and CycLClosedSentence (qq.v.).  This is the collection of all and only the syntactically well-formed atomic sentences in the CycL language that contain no free variables.  Syntactically, each instance of CycLClosedAtomicSentence consists of a CycL expression denoting a Predicate followed by one or more (closed) CycL terms, with the entire sequence enclosed in parentheses.  Such sentences are sometimes called \"GAFs\" (an acronym for \"ground atomic formulas\"); see also the specialization CycLFullyGroundAtomicSentence.", 'UniversalVocabularyMt', vStrDef).
 8162exactlyAssertedEL_next(comment, 'CycLAtomicTerm', "The collection of all atomic CycLDenotationalTerms (q.v.).  \"Atomic\" here means not constructible  from other CycL terms via the syntax of CycL.  Thus, subcollections  of CycLAtomicTerm include CycLConstant, CycLVariable, and SubLAtomicTerm.  Note that CycLAtomicTerm, like most instances of CycLExpressionType, is \"quoted\" (see quotedCollection).", 'UniversalVocabularyMt', vStrDef).
 8163exactlyAssertedEL_next(comment, 'CycLAtomicSentence', "The collection of syntactically well-formed atomic sentences in the CycL language. Each instance of CycLAtomicSentence consists of a CycL constant denoting a Predicate followed by one or more (closed or open) CycL terms, with the entire sequence enclosed in parentheses.  Thus CycL atomic sentences never contain other sentences as truth-functional components (see TruthFunction).  Note that \"atomic\" as used here specifically in connection with _sentences_, has a less strict meaning than it does when applied to terms generally, where it means \"not constructible from other terms via CycL syntax\" (see CycLAtomicTerm).", 'UniversalVocabularyMt', vStrDef).
 8164exactlyAssertedEL_next(comment, 'CycLAtomicAssertion', "A specialization of CycLAtomicSentence.  An instance ATOM of CycLAtomicSentence is also an instance of CycLAtomicAssertion just in case ATOM has been explicitly asserted to the Cyc Knowledge Base (see CycLAssertedAssertion), or deduced in the Knowledge Base by the Cyc inference engine (see CycLDeducedAssertion).", 'UniversalVocabularyMt', vStrDef).
 8165exactlyAssertedEL_next(comment, 'CycLAssertionDirection', "The collection of possible inference \"directions\" that a CycLAssertion\ncan have.  A given CycL assertion's direction (see assertionDirection) \nindicates something about how and when the assertion can be used in inferences\nby the Cyc system.  More precisely: Backward-AssertionDirection indicates\nthat the assertion can only be used in inferences carried out when a query\nis asked; Forward-AssertionDirection indicates that the assertion can be used \nin inferences carried out at the time the assertion is added to the Knowledge \nBase as well as those carried out at ask-time; and Code-AssertionDirection\nindicates that the assertion itself cannot be used in either backward \n(ask-time) or forward (assert-time) inferences, but is instead implemented \nin the underlying code of the Cyc system.  Each CycL assertion has exactly \none of the above three directions; the default direction is Forward for \nground atomic assertions (see CycLClosedAtomicSentence) and Backward for \nrule assertions.  Note that a CycL sentence is given a direction at the time \nof its assertion to the system, and this fact _need_not_ be reflected in \nanother, assertionDirection assertion's being added to the system (as\nthat would of course lead to an infinite regress).", 'UniversalVocabularyMt', vStrMon).
 8166exactlyAssertedEL_next(comment, 'CycLAssertion', "The collection of semantically well-formed CycLSentences asserted to the Cyc Knowledge Base.  Each instance of CycLAssertion is either (1) an HL assertion, i.e. a CycL sentence that corresponds to a data structure actually in the Cyc KB), or (2) an EL assertion : an Epistemological Level CycL sentence that can be canonicalized into one or more already extant HL assertions.  CycLAssertion is used as a quoted argument type constraint for certain meta-predicates, such as overrides.", 'UniversalVocabularyMt', vStrDef).
 8167exactlyAssertedEL_next(comment, 'CycLAssertedAssertion', "A specialization of CycLAssertion.  An instance ASSERT of CycLAssertion is also an instance of CycLAssertedAssertion  just in case ASSERT was explicitly asserted to the Cyc Knowledge Base by one of its users (see the collection Cyclist), as opposed to having been deduced by Cyc's inference engine (in which case it would be an instance of CycLDeducedAssertion (q.v.)).  Note that since a single assertion can be both explicitly asserted to the knowledge base and also deduced by the inference engine, the collections CycLAssertedAssertion and CycLDeducedAssertion are not disjoint.", 'UniversalVocabularyMt', vStrDef).
 8168exactlyAssertedEL_next(comment, 'CycInferenceBindingsDataStructure', "A specialization of CycInferenceDataStructure.  Each\ninstance of CycInferenceBindingsDataStructure is a component of one\nor more CycInferenceAnswers, and encodes an assignment of bindings\nto the free variables in the query which yielded that answer\n(i.e., the query which triggered the CycInference of which that\nanswer is a part).  If the triggering query is closed, the binding\nlist value is NIL.", 'UniversalVocabularyMt', vStrMon).
 8169exactlyAssertedEL_next(comment, 'CycInferenceAnswerJustification', "A specialization of CycInferenceDataStructure.  Each\ninstance of CycInferenceAnswerJustification is a component of one or\nmore CycInferenceAnswers, and, in each case, encodes a complete set\nof supports (cf., CycSupportDatastructure) for that answer's binding\nlist.  See also CycInferenceBindingsDataStructure.", 'UniversalVocabularyMt', vStrMon).
 8170exactlyAssertedEL_next(comment, 'CycInferenceAnswer', "A specialization of CycInferenceDataStructure.  Each\ninstance of CycInferenceAnswer is a complex data structure that is a\ncomponent of one or more CycInferences (specifically, of certain\ninferences whose root problem is proven).  A CycInferenceAnswer has\ntwo components: an assigment of bindings to query variables and sets of justifications for those bindings.  For information about the components, see the predicates inferenceAnswerBindings and inferenceAnswerJustification.", 'UniversalVocabularyMt', vStrMon).
 8171exactlyAssertedEL_next(comment, 'CycHLTruthValue', "The truth/strength combinations used in the Cyc HL implementation of CycLAssertions and arguments.", 'UniversalVocabularyMt', vStrMon).
 8172exactlyAssertedEL_next(comment, 'CycHLSupportDatastructure', "A specialization of both CycHLDatastructure and\nCycSupportDatastructure (qq.v.) instances of which\nare Cyc HL datastructures that can be used as supports\nwithin a CycDeductionDatastructure (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8173exactlyAssertedEL_next(comment, 'CycAdministrator', "This constant is for use by Cyc administrators responsible for installation, setup and maintenance of Cyc images.", 'BaseKB', vStrMon).
 8174exactlyAssertedEL_next(comment, 'CurrentWorldDataCollectorMt-NonHomocentric', "The Microtheory which collects together all of the instances of GeneralMicrotheory (including instances of DataMicrotheory) as genlMts (excepting HomoCentricNaturalismMt), so that any scenario or project microtheory which needs wide access to the KB but needs to accept either non-human Persons or supernatural things can use this as a genlMt and be assured that all generally defined terms are available.  If no need exists to access instances of TemporalThing, WorldLikeOursCollectorMt-NonHomocentric should be used instead.  If for the purposes of the project all persons are human and no supernatural things are being reasoned about use the CollectorMicrotheory CurrentWorldDataCollectorMt or WorldLikeOursCollectorMt.", 'BaseKB', vStrMon).
 8175exactlyAssertedEL_next(comment, 'CoreCycLMt', "This is a microtheory which contains only the assertions required to represent useful logical truths in CycL.  It extends the LogicalTruthMt with additional assertions which are so useful as to be considered `core' to the CycL language.", 'BaseKB', vStrMon).
 8176exactlyAssertedEL_next(comment, 'CoreCycLImplementationMt', "This is a microtheory which contains only the `core' assertions required for the Cyc theorem prover and its underlying HL representation of the EL to conclude useful inferences.  It extends the LogicalTruthImplementationMt with assertions necessary for Cyc's implementation to make use of the terms defined in the CoreCycLMt.", 'BaseKB', vStrMon).
 8177exactlyAssertedEL_next(comment, 'CommutativeRelation', "An instance of RelationTypeByLogicalFeature (q.v.) and a specialization of AtLeastPartiallyCommutativeRelation (q.v.).  Each instance of CommutativeRelation <code>COMRELN</code> is a predicate or function that is commutative in all of its argument-places.  That is, if <code>COMRELN</code> is a predicate (function) that holds among (has a value <code>VAL</code> for) a given sequence of arguments, then <code>COMRELN</code> also holds among (has the same value <code>VAL</code> for) any permutation of that  sequence.  \n<p>\nExamples of commutative relations include PlusFn, or, bordersOn, temporallyIntersects, and teammates.  Specialization include SymmetricBinaryPredicate.  \n<p>\nNote that most relations are <i>not</i> commutative.  Cf. the disjoint collection  PartiallyCommutativeRelation.", 'UniversalVocabularyMt', vStrDef).
 8178exactlyAssertedEL_next(comment, 'CollectionRuleTemplateFn', "(CollectionRuleTemplateFn COL) denotes the rule template unique to collection COL.", 'UniversalVocabularyMt', vStrMon).
 8179exactlyAssertedEL_next(comment, 'CollectionDenotingFunction', "The subcollection of Function-Denotational whose instances return instances of Collection.  Examples include SwimmingEventFn, GroupFn, and MoleculeFn.  For example, (MoleculeFn Oxygen) denotes the collection of all oxygen molecules.  See also the collections IndividualDenotingFunction and SetDenotingFunction.", 'UniversalVocabularyMt', vStrMon).
 8180exactlyAssertedEL_next(comment, tCol, "A specialization of SetOrCollection (q.v.).  This is the collection of all collections of things.  Each Collection is a kind or type of thing whose instances share a certain property, attribute, or feature.  For example, Cat is the collection of all and only cats, and BinaryFunction is the collection of all and only functions taking two arguments.\n<p>\nThe notion of collection is fundamental to the Cyc ontology, and is thus difficult to define in a precise and substantive way.  But it is instructive to compare it to the mathematical notion of a set (see Set-Mathematical).  Like a set, a collection is an AbstractThing (i.e. aspatial and atemporal) that is not an Individual (cf.), but instead has elements (see elementOf).  Unlike a set, however, the elements or \"instances\" (see isa) of a given collection can vary from context to context, and it is possible for distinct collections to have exactly the same elements (i.e. to have the same extent) with respect to a given context. For example, the (non-reified) collections \"Chordate\" and \"Renate\" are co-extensional in the context of the present-day actual world, but have differring extents with respect to hypothetical contexts in which there exist creatures having hearts but not kidneys.  This difference is sometimes summarized by saying that sets are \"extensional\" things and collections are \"intensional\" things.\n<p>\nMany, though by no means all, of the collections reified in the Cyc ontology correspond to natural kinds or classes.  It is particulary useful to reify collections that are difficult to define precisely, but about which there are many common-sense rules and other things to state.  For example, it would not be worthwile to introduce a constant 'WhiteCat', both because it's easy to define the collection of white cats in terms of more general, already-reified notions (e.g. '(CollectionIntersection2Fn Cat WhiteColor)'), and because there's not much to say about that particular collection.  WhiteCollarWorker, on the other hand, is a good collection to have reified, as it is hard to define precisely, yet is a collection about which there are many things to say.\n<p>\nSome of the many reified specializations of Collection are FirstOrderCollection, TimeDependentCollection, and ObjectType.", 'UniversalVocabularyMt', vStrDef).
 8181exactlyAssertedEL_next(comment, 'Code-AssertionDirection', "An instance of CycLAssertionDirection (q.v.).  A CycL assertion that\nhas the Code-AssertionDirection cannot itself be used in either \nbackward (ask-time) or forward (assert-time) inferences, but is instead \nimplemented in the underlying code of the Cyc system.  Contrast with \nBackward-AssertionDirection and Forward-AssertionDirection.  Also \nsee assertionDirection.", 'UniversalVocabularyMt', vStrMon).
 8182exactlyAssertedEL_next(comment, 'CharacterString', "A specialization of AbstractInformationStructure.  Each instance of CharacterString is a string of characters or an abstract sequence of symbols.  Note that an instance of CharacterString is <i>not</i> any particular physical, tangible representation, since different encodings may represent the same string of characters.  An instance of CharacterString is a list (see the collection List) of characters (instances of Character-Abstract) from some fixed character set. An instance of CharacterString may be any finite length, including zero (the zero-length string is the empty string, which has no characters).  Notable specializations of CharacterString include EMailAddress, AreaCode, PhoneNumber, and TelephoneCountryCode.  Note that a CharacterString is ordered formally as a List (rather than physically left-to-right or top-to-bottom); thus the 'first' character in the CharacterString for an Arabic word happens to be the rightmost (first pronounced) character, not the leftmost character, due to the letter-order and word-order convention for Arabic writing.", 'UniversalVocabularyMt', vStrMon).
 8183exactlyAssertedEL_next(comment, 'CanonicalizerDirective', "A specialization of AspatialInformationStore.  Instances  of CanonicalizerDirective are directives (or \"commands\") that can be  given to the CycCanonicalizer (via certain CanonicalizerDirectivePredicates) in order to control its behavior in certain ways during asserts and queries.   Examples include AllowGenericArgVariables and LeaveSomeTermsAtEL. See e.g. the directive predicate canonicalizerDirectiveForArg for more  information on how to use these directives.", 'CoreCycLImplementationMt', vStrMon).
 8184exactlyAssertedEL_next(comment, 'BroadMicrotheory', "The collection of those microtheories that contain so many assertions that they are not useful for `relevance' focusing during inference.  (A BroadMicrotheory is not used internally in Cyc's indexing scheme during inference.)  Examples: BaseKB and EnglishMt.", 'UniversalVocabularyMt', vStrDef).
 8185exactlyAssertedEL_next(comment, 'BookkeepingPredicate', "A PredicateType whose instances are predicates used to make assertions about the reification (or \"creation\") and internal representation of particular CycL terms (usually constants) in the Cyc system.  Bookkeeping predicates neither specify nor constrain the semantics of CycL terms.  Examples include  myCreator, myCreationTime, termOfUnit, and defnSufficient.  Many (but not all) bookkeeping predicates are also MetaKnowledgePredicates (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8186exactlyAssertedEL_next(comment, 'BookkeepingMt', "A Microtheory for stating basic bookkeeping information regarding the Cyc Knowledge Base, such as assertions using myCreator or myCreationTime.", 'BaseKB', vStrDef).
 8187exactlyAssertedEL_next(comment, 'BinaryRelation', "The collection of all fixed-arity relations of arity 2 (see arity).  The most notable specializations of BinaryRelation are BinaryPredicate and BinaryFunction (qq.v.).", 'UniversalVocabularyMt', vStrMon).
 8188exactlyAssertedEL_next(comment, 'BinaryPredicate', "A specialization of both BinaryRelation and Predicate.  BinaryPredicate is the collection of all predicates whose arity (see arity) is 2.", 'UniversalVocabularyMt', vStrDef).
 8189exactlyAssertedEL_next(comment, 'BinaryFunction', "A specialization of both BinaryRelation and Function-Denotational.  An instance of Function-Denotational FUNC is an instance of BinaryFunction if and only if FUNC has an arity of 2.", 'UniversalVocabularyMt', vStrDef).
 8190exactlyAssertedEL_next(comment, 'BaseKB', "BaseKB is the most general Microtheory currently in use.  Assertions in this context are `accessible' from any other Microtheory via the genlMt relation.  In the partial order of microtheories, all microtheories have access to BaseKB.  An assertion which is true here will by default be true in every context.  The `content' of BaseKB consists of very general assertions which are expected to be usable in most or all applications of Cyc, as well as Cyc's most fundamental assertions that it uses in inference, and all completely universal, timeless truths.", 'BaseKB', vStrDef).
 8191exactlyAssertedEL_next(comment, 'Backward-AssertionDirection', "An instance of CycLAssertionDirection (q.v.).  A CycL assertion that\nhas the Backward-AssertionDirection can only be used in inferences that \nare carried out when a query is asked. This is the default direction for \nrule assertions.  Contrast with Forward-AssertionDirection and Code-AssertionDirection.  Also see assertionDirection.", 'UniversalVocabularyMt', vStrMon).
 8192exactlyAssertedEL_next(comment, 'Average', "Computes the average of the function values over all elements in the Set.", 'UniversalVocabularyMt', vStrDef).
 8193exactlyAssertedEL_next(comment, 'August', "The collection of all Augusts,\n the eighth month of the year in the GregorianCalendar.", 'UniversalVocabularyMt', vStrDef).
 8194exactlyAssertedEL_next(comment, 'AtemporalNecessarilyEssentialCollectionType', "A collection of collections.  Each instance <code>COL</code> of AtemporalNecessarilyEssentialCollectionType (<i>ANECT</i>) is a collection satisfying three conditions: (1) <code>COL</code> is disjoint with (see disjointWith) TemporalThing, (2) every instance <code>INST</code> of <code>COL</code> is an instance of <code>COL</code> essentially (i.e. <code>INST</code> is an instance of <code>COL</code>, and could not exist without being an instance of <code>COL</code>), and (3) condition (2) is a necessary truth about <code>COL</code>.\n<p>\nPositive examples of ANECTs include Collection, Integer, and Relation (each of which is a collection of atemporals and is such that, necessarily, all of its instances are in it essentially).  Negative examples include SpatialThing (though arguably it is necessary that all of its instances are essentially instances of it, it is not disjoint with TemporalThing) and UniqueAnatomicalPartType (which, though disjoint with TemporalThing, has instances, such as Heart, that could exist even if they weren't instances of it; e.g. it might have been the case that every creature with a heart had at least two hearts).  There are no known examples of Cyc-reified collections satisfying conditions (1) and (2) but not (3), but one can be contrived.  Suppose that all of today's winning lottery numbers were primes.  Now consider the collection:\n<p>\n (CollectionUnionFn \n   (TheSet PrimeNumber <i>TodaysWinningLotteryNumbers</i>))\n<p>\nThis collection is clearly disjoint with TemporalThing and, by hypothesis, all of its instances are in it essentially (as each prime number is essentially a prime number).  But this last fact is not <i>necessarily</i> true of this collection: the collection might have had instances that belonged to it only contingently (i.e. not essentially), as it might have been the case that one of today's winning lottery numbers was non-prime, and no number is such that it is essentially one of today's winning lottery numbers.\n<p>\nWhen asserting that something is an instance or specialization of a given instance of ANECT, it is appropriate to do so in the UniversalVocabularyMt (q.v.).  Indeed, ANECT was specially defined to facilitate the movement of appropriate assertions to that microtheory.\n<p>\nCf. PragmaticallyDecontextualizedCollection.", 'UniversalVocabularyMt', vStrMon).
 8195exactlyAssertedEL_next(comment, 'AsymmetricBinaryPredicate', "An instance of BinaryPredicateTypeByLogicalFeature and a specialization of AntiSymmetricBinaryPredicate (q.v.).  A binary predicate <code>BINPRED</code> is an instance of AsymmetricBinaryPredicate if and only if (i) for any <code>THING1</code> and <code>THING2</code>, <code>(BINPRED THING1 THING2)</code> implies <code>(not (BINPRED THING2 THING1))</code> and (ii) the single-argument argument type (i.e. argIsa and argGenl) constraints on <code>BINPRED</code>'s two respective argument-places are \"co-satisfiable\" (see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement).\n<p>\nExamples of asymmetric binary predicates include northOf, children, greaterThan, and overrides.  Cf. SymmetricBinaryPredicate.", 'UniversalVocabularyMt', vStrDef).
 8196exactlyAssertedEL_next(comment, 'AssociativeRelation', "The collection of polyadic Relations having the property of <i>associativity</i>.  Roughly speaking, a relation is associative if certain different sequences of recursive applications of it lead to the same final result.\n<p>\nMore precisely:  If <b>RELN</b> is binary, it is an instance of AssociativeRelation if and only if (for any appropriate arguments <b>A</b>, <b>B</b>, and <b>C</b>) the corresponding formulas <b>(RELN A (RELN B C))</b> and <b>(RELN (RELN A B) C)</b> are (extensionally) equivalent: if <b>RELN</b> is a Function-Denotational both formulas have the same denotatum (or both have no denotatum), while if <b>RELN</b> is a Predicate or LogicalConnective both formulas have the same truth value.  If <b>RELN</b> has a higher arity than two, the definition is similar, but with the relevant formula schemata appropriately rewritten.  If <b>RELN</b> is variable-arity (see VariableArityRelation), it is an AssociativeRelation if and only of it behaves associatively with respect to each of the particular arities it subsumes (its arityMin to arityMax).  No unary relation is associative. \n<p>\nIt follows from the above definition that that each argument-place of an associative relation must admit exactly the same class of arguments (see admittedArgument), and that its results must also be of that same class (so that it can be applied recursively).\n<p>\nExamples of associative relations include PlusFn, TimesFn, JoinListsFn, SpatialSumFn, or, and and.\n<p>\nNote that, while many AssociativeRelations are CommutativeRelations (q.v.), this is not always the case.  Consider for example ConcatenateStringsFn.  Since it is associative, (('c'^'a')^'t') = ('c'^('a'^'t')) = 'cat'.  But it is certainly <i>not</i> commutative: 'cat' =/ 'act'.", 'UniversalVocabularyMt', vStrMon).
 8197exactlyAssertedEL_next(comment, 'assertionUtility-1', "A CycInferenceHeuristicRelevancePredicate. (assertionUtility ASSERTION NUM) states that the CycLAssertion ASSERTION should be heuristically considered of utility NUM to inferences made in the current Microtheory. NUM should be a RealNumber between 1 and -1, with 1 indicating maximum utility, -1 indicating minimum utility, and 0 being agnostic with respect to utility.  (assertionUtility ASSERTION 1) is equivalent to (highlyRelevantAssertion ASSERTION). (assertionUtility ASSERTION -1) is equivalent to (irrelevantAssertion ASSERTION).  See also other instances of CycInferenceHeuristicRelevancePredicate.", 'UniversalVocabularyMt', vStrMon).
 8198exactlyAssertedEL_next(comment, 'ArgTypeTernaryPredicate', "Those instances of both TernaryPredicate and ArgTypePredicate used to specify the required isa or genls or quotedIsa of an argument of a Relation; the arg1 is the Relation; the arg2 is the argument constrained; the arg3 is the required type: a Collection.", 'UniversalVocabularyMt', vStrDef).
 8199exactlyAssertedEL_next(comment, 'ArgTypePredicate', "The collection of ArgConstraintPredicates used to put semantic well-formedness constraints on the type of argument(s) appropriate for a given argument-place (or -places) of a given relation.  A \"type\" of argument can be specified in terms of isa or genls; see the various specializations of ArgTypePredicate for more detail. Violation of such a constraint results in an expression that is semantically malformed.  For a general explanation of semantic well-formedness, see CycLExpression-Assertible and its specializations.", 'UniversalVocabularyMt', vStrDef).
 8200exactlyAssertedEL_next(comment, 'ArgTypeBinaryPredicate', "Those instances of both BinaryPredicate and ArgTypePredicate used to specify the required isa or genls or quotedIsa of an argument of a Relation; the arg1 is the Relation; the arg2 is the required type, a Collection.", 'UniversalVocabularyMt', vStrDef).
 8201exactlyAssertedEL_next(comment, 'ArgSometimesIsaPredicate', "The collection of ArgTypePredicates (q.v.) that specify argument-types\ndirectly (by referencing certain collections) and impose constraints that\nrequire an argument of a predicate being an instance of a SubLExpressionType\ncollection at some time.  More precisely, each instance\nof ArgSometimesIsaPredicate PRED takes a Relation RELN as its first argument (or\n\"arg1\"), and has at least one other argument-place (say the Mth) for\nspecifying an argument-type for one of RELN's argument-places (say the\nNth). (The value of N might be fixed or might be given by yet another of PRED's\narguments.) Suppose M=2 and N=1. PRED then takes a SubLExpressionType Collection\nas its second argument, and a closed atomic sentence (or \"GAF\") of the form\n(PRED RELN COL ..) puts a \"sometimes isa\" constraint on RELN's first\nargument-place that is based on COL. If PRED is a \"single-argument\" constraint\npredicate, the GAF entails that a closed formula of the form (RELN ARG1 ..) is\nsemantically well-formed only if ARG1 is an instance of \nSubLExpressionType COL in some time interval\n(including Always-TimeInterval).", 'UniversalVocabularyMt', vStrMon).
 8202exactlyAssertedEL_next(comment, 'ArgQuotedIsaTernaryPredicate', "A specialization of ArgQuotedIsaPredicate (q.v.). Each instance of ArgQuotedIsaTernaryPredicate. is a ternary predicate used to place an \"quoted isa\" constraint on (and thereby specify an argument-type for) one or more argument-places of a relation. To be more precise, each instance PRED of ArgQuotedIsaTernaryPredicate takes a Relation RELN as its first argument, a NonNegativeInteger N as its second argument, and a SubLExpressionType collection COL as its third argument. PRED places an \"quoted isa\" constraint on RELN's Nth argument-place that is based on COL, so that a ground atomic sentence (GAF) of the form (RELN ARG1..ARGN..) is semantically well-formed only if ARGN is a quoted instance of COL. (Note that if N = 0 then this same constraint is placed on _all_ of RELN's argument-places. An important instance of ArgQuotedIsaTernaryPredicate is argQuotedIsa.", 'UniversalVocabularyMt', vStrMon).
 8203exactlyAssertedEL_next(comment, 'ArgQuotedIsaPredicate', "The collection of ArgTypePredicates (q.v.) that specify argument-types directly (by referencing certain collections) and impose constraints that require a thing's being an instance of a SubLExpressionType collection thus specified. More precisely, each instance of ArgQuotedIsaPredicate PRED takes a Relation RELN as its first argument (or \"arg1\"), and has at least one other argument-place (say the Mth) for specifying an argument-type for one of RELN's argument-places (say the Nth). (The value of N might be fixed or might be given by yet another of PRED's arguments.) Suppose M=2 and N=1. PRED then takes a SubLExpressionType Collection as its second argument, and a closed atomic sentence (or \"GAF\") of the form (PRED RELN COL ..) puts an \"quoted isa\" constraint on RELN's first argument-place that is based on COL. If PRED is a \"single-argument\" constraint predicate, the GAF entails that a closed formula of the form (RELN ARG1 ..) is semantically well-formed only if ARG1 is an instance of (i.e. quotedIsa) SubLExpressionType COL.", 'UniversalVocabularyMt', vStrMon).
 8204exactlyAssertedEL_next(comment, 'ArgQuotedIsaBinaryPredicate', "A specialization of ArgQuotedIsaPredicate . Each instance of ArgQuotedIsaBinaryPredicate takes a Relation RELN as its first argument, and a SubLExpressionType Collection COL as its second argument, and places a constraint based on COL on at least one of the argument-places of RELN. To be more precise, suppose that PRED is an ArgIsaBinaryPredicate that specifies an argument-type for the Nth argument-place of RELN. Then a sentence of the form (PRED RELN COL) entails that a closed formula of the form (RELN ... ARGN ...) is semantically well-formed only if ARGN is an instance (i.e. quotedIsa) of COL.", 'UniversalVocabularyMt', vStrMon).
 8205exactlyAssertedEL_next(comment, 'ArgIsaTernaryPredicate', "A specialization of both ArgTypeTernaryPredicate and ArgIsaPredicate (q.v.).  Each instance of ArgIsaTernaryPredicate is a ternary predicate used to place an \"isa\" constraint on (and thereby specify an argument-type for) one or more argument-places of a relation.  To be more precise, each instance PRED of ArgIsaTernaryPredicate takes a Relation RELN as its first argument, a NonNegativeInteger N as its second argument, and a Collection COL as its third argument.  PRED places an \"isa\" constraint on RELN's Nth argument-place that is based on COL, so that a ground atomic sentence (GAF) of the form (RELN ARG1..ARGN..) is semantically well-formed only if ARGN is an instance of COL. (Note that (i) if N = 0 then this same constraint is placed on _all_ of RELN's argument-places and (ii) if PRED is argAndRestIsa then this constraint is placed on all of RELN's argument-places whose ordinal positions are greater than or equal to the Nth.)  An important instance of ArgIsaTernaryPredicate is argIsa.", 'UniversalVocabularyMt', vStrDef).
 8206exactlyAssertedEL_next(comment, 'ArgIsaPredicate', "The collection of ArgTypePredicates (q.v.) that specify argument-types directly (by referencing certain collections) and impose constraints that require a thing's being an instance of a collection thus specified.  More precisely, each instance of ArgIsaPredicate PRED takes a Relation RELN as its first argument (or \"arg1\"), and has at least one other argument-place (say the Mth) for specifying an argument-type for one of RELN's argument-places (say the Nth).  (The value of N might be fixed or might be given by yet another of PRED's arguments.)  Suppose M=2 and N=1.  PRED then takes a Collection as its second argument, and a closed atomic sentence (or \"GAF\") of the form (PRED RELN COL ..) puts an \"isa\" constraint on RELN's first argument-place that is based on COL.  If PRED is a \"single-argument\" constraint predicate, the GAF entails that a closed formula of the form (RELN ARG1 ..) is semantically well-formed only if ARG1 is an instance of (i.e. isa) COL.  If PRED is an \"inter-argument\" constraint predicate, the GAF expresses a slightly more complicated, conditional isa constraint on a pair of RELN's argument-places (see InterArgIsaPredicate).", 'UniversalVocabularyMt', vStrDef).
 8207exactlyAssertedEL_next(comment, 'ArgIsaBinaryPredicate', "A specialization of both ArgTypeBinaryPredicate and ArgIsaPredicate.  Each instance of ArgIsaBinaryPredicate takes a Relation RELN as its first argument, and a Collection COL as its second argument, and places a constraint based on COL on at least one of the argument-places of RELN.  To be more precise, suppose that PRED is an ArgIsaBinaryPredicate that specifies an argument-type for the Nth argument-place of RELN.  Then a sentence of the form (PRED RELN COL) entails that a closed formula of the form (RELN ... ARGN ...) is semantically well-formed only if  ARGN is an instance of COL.", 'UniversalVocabularyMt', vStrDef).
 8208exactlyAssertedEL_next(comment, 'ArgGenlTernaryPredicate', "A specialization of ArgTypeTernaryPredicate and ArgGenlPredicate.  Each instance of ArgGenlTernaryPredicate is used to specify that a certain collection is required to stand in the genls relation to anything that is acceptable in a particular argument slot of a given instance of Relation.  With each instance of ArgGenlTernaryPredicate, the first argument is the relation constrained; the second argument is the argument constrained; and the third argument is the required collection that the relation's specified argument is required to be a specialization of.", 'UniversalVocabularyMt', vStrDef).
 8209exactlyAssertedEL_next(comment, 'ArgGenlQuantityTernaryPredicate', "A specialization of both ArgTypeTernaryPredicate and ArgGenlAttributePredicate.  Each instance of ArgGenlAttributeTernaryPredicate is a ternary predicate used to place a \"quantitySubsumes\" constraint on (and thereby specify an argument-type for) one or more argument-places of a relation.  To be more precise, each instance PRED of ArgGenlAttributeTernaryPredicate takes a Relation RELN as its first argument, a NonNegativeInteger N as its second argument, and an Quantity QUANT as its third argument. PRED places a \"quantitySubsumes\" constraint on RELN's Nth argument-place that is based on QUANT, so that a ground atomic sentence (GAF) of the form (RELN ARG1..ARGN..) is semantically well-formed only if ARGN is subsumed by QUANT (in the sense that (quantitySubsumes QUANT ARGN) holds).  An important instance of ArgGenlAttributeTernaryPredicate is argGenlAttribute.", 'UniversalVocabularyMt', vStrDef).
 8210exactlyAssertedEL_next(comment, 'ArgGenlQuantityBinaryPredicate', "Those instances of both ArgTypeBinaryPredicate and ArgGenlAttributePredicate used to specify the required quantity of an argument of Relation.  Each instance PRED of this collection is a binary predicate with the following properties: ARG1 is an instance of Relation, and ARG2 is an instance of Quantity.  (PRED ARG1 ARG2) means that some argument of ARG1 is constrained to be subsumed by (via quantitySubsumes) ARG2, where PRED determines the argument place in question.", 'UniversalVocabularyMt', vStrDef).
 8211exactlyAssertedEL_next(comment, 'ArgGenlBinaryPredicate', "Those instances of both BinaryPredicate and ArgGenlPredicate used to specify the required genls of an argument of a Relation; the arg1 is the Relation; the arg2 is the required genls Collection.", 'UniversalVocabularyMt', vStrDef).
 8212exactlyAssertedEL_next(comment, 'ArgConstraintPredicate', "The collection of MetaRelations whose instances are used to put semantic well-formedness or entry-format constraints on one or more argument-places of a given Relation.  Such a constraint might concern an argument's <i>type</i>, an argument-place's Format (q.v.), a conditional relationship between two argument(-place)s' types or formats, or some other sort of relationship between two arguments.  For a fuller account, see the various specializations of ArgConstraintPredicate.", 'UniversalVocabularyMt', vStrDef).
 8213exactlyAssertedEL_next(comment, 'April', "The collection of all Aprils, \nthe fourth month of the year in the GregorianCalendar.", 'UniversalVocabularyMt', vStrDef).
 8214exactlyAssertedEL_next(comment, 'AntiTransitiveBinaryPredicate', "A BinaryPredicateTypeByLogicalFeature and a specialization of  IrreflexiveBinaryPredicate (q.v.).  A binary predicate PRED is an instance of  AntiTransitiveBinaryPredicate only if it has this property: for any THING1, THING2, and THING3 such that both (PRED THING1 THING2) and (PRED THING2 THING3) hold, (not (PRED THING1 THING3)) holds.  Equivalently: for every X, Y, and Z that satisfy the (single-argument) argument-type constraints  (see admittedArgument) for the relevant argument positions of PRED,  (not (and (PRED X Y)(PRED Y Z)(PRED X Z))) holds.  Note that  PRED's two agument-positions must also be \"co-satisfiable\" with respect to their type constraints; see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement.\n<p>\nFor example, divorcedFrom is an instance of AntiTransitiveBinaryPredicate.\n<p>\nNote also that, while not strictly disjoint with TransitiveBinaryPredicate (q.v.), in practice few if any reified predicates should be instances of both of these collections. An important specialization of AntiTransitiveBinaryPredicate is DirectBinaryPredicate (q.v.).", 'UniversalVocabularyMt', vStrDef).
 8215exactlyAssertedEL_next(comment, 'AntiSymmetricBinaryPredicate', "A BinaryPredicateTypeByLogicalFeature and thus a specialization of BinaryPredicate.  A binary predicate <code>PRED</code> is an AntiSymmetricBinaryPredicate if and only if it has the following two properties.  (i) For any <code>THING1</code> and <code>THING2</code> such that both <code>(PRED THING1 THING2)</code> and <code>(PRED THING2 THING1)</code> hold, <code>THING1</code>  = <code>THING2</code>.  (ii) <code>PRED</code>'s two argument-places must be \"co-satisfiable\" with respect to their (single-argument) type constraints (see cosatisfiableInArgs and NoteOnArgumentCosatisfiabilityRequirement).\n<p>\nInstances of AntiSymmetricBinaryPredicate include greaterThanOrEqualTo, parts, and subEvents.  See also the specialization AsymmetricBinaryPredicate; and cf. SymmetricBinaryPredicate.", 'UniversalVocabularyMt', vStrDef).
 8216exactlyAssertedEL_next(comment, 'AllowKeywordVariables', "A CanonicalizerDirective (q.v.)  that is a specialization (see genlCanonicalizerDirectives) of  AllowGenericArgVariables.  AllowKeywordVariables directs the  CycCanonicalizer to allow all \"keyword variables\" (e.g. `:NOUN'  and `:ARG1') to appear in CycL assertions and to treat them as if they  were CycLVariables.", 'CoreCycLImplementationMt', vStrDef).
 8217exactlyAssertedEL_next(comment, 'AllowGenericArgVariables', "A CanonicalizerDirective (q.v.) that directs the CycCanonicalizer to allow \"generic argument keyword variables\" (e.g. `:ARG1' and `:ARG2') to appear in CycL assertions and  to treat them as if they were CycLVariables.  For a specialization (see genlCanonicalizerDirectives) of this directive that is used to  direct the canonicalizer to allow _all_ keyword variables, see AllowKeywordVariables.", 'CoreCycLImplementationMt', vStrDef).
 8218exactlyAssertedEL_next(comment, 'AbsoluteValueFn', "AbsoluteValueFn is the unary mathematical function that returns the absolute value of its argument; e.g., (AbsoluteValueFn -2) returns 2, and (AbsoluteValueFn 2) returns 2.", 'UniversalVocabularyMt', vStrDef).
 8219exactlyAssertedEL_next(collectionConventionMt, 'VariableAritySkolemFunction', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8220exactlyAssertedEL_next(collectionConventionMt, 'VariableArityRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8221exactlyAssertedEL_next(collectionConventionMt, 'UnreifiableFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8222exactlyAssertedEL_next(collectionConventionMt, 'UnitOfMeasure', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8223exactlyAssertedEL_next(collectionConventionMt, 'UnaryRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8224exactlyAssertedEL_next(collectionConventionMt, 'UnaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8225exactlyAssertedEL_next(collectionConventionMt, 'UnaryFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8226exactlyAssertedEL_next(collectionConventionMt, 'TruthFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8227exactlyAssertedEL_next(collectionConventionMt, 'TransitiveBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8228exactlyAssertedEL_next(collectionConventionMt, 'Thing', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8229exactlyAssertedEL_next(collectionConventionMt, 'TheTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8230exactlyAssertedEL_next(collectionConventionMt, 'TernaryRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8231exactlyAssertedEL_next(collectionConventionMt, 'TernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8232exactlyAssertedEL_next(collectionConventionMt, 'TernaryFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8233exactlyAssertedEL_next(collectionConventionMt, 'SymmetricBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8234exactlyAssertedEL_next(collectionConventionMt, 'SubLSymbol', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8235exactlyAssertedEL_next(collectionConventionMt, 'SubLString', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8236exactlyAssertedEL_next(collectionConventionMt, 'SubLSExpression', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8237exactlyAssertedEL_next(collectionConventionMt, 'SubLRealNumber', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8238exactlyAssertedEL_next(collectionConventionMt, 'SubLPositiveInteger', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8239exactlyAssertedEL_next(collectionConventionMt, 'SubLNonVariableSymbol', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8240exactlyAssertedEL_next(collectionConventionMt, 'SubLNonVariableNonKeywordSymbol', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8241exactlyAssertedEL_next(collectionConventionMt, 'SubLNonNegativeInteger', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8242exactlyAssertedEL_next(collectionConventionMt, 'SubLList', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8243exactlyAssertedEL_next(collectionConventionMt, 'SubLKeyword', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8244exactlyAssertedEL_next(collectionConventionMt, 'SubLInteger', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8245exactlyAssertedEL_next(collectionConventionMt, 'SubLExpressionType', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8246exactlyAssertedEL_next(collectionConventionMt, 'SubLCharacter', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8247exactlyAssertedEL_next(collectionConventionMt, 'SubLAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8248exactlyAssertedEL_next(collectionConventionMt, 'SubLAtom', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8249exactlyAssertedEL_next(collectionConventionMt, 'SkolemFunction', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8250exactlyAssertedEL_next(collectionConventionMt, 'SiblingDisjointCollectionType', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8251exactlyAssertedEL_next(collectionConventionMt, 'SiblingDisjointAttributeType', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8252exactlyAssertedEL_next(collectionConventionMt, 'SetOrCollection', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8253exactlyAssertedEL_next(collectionConventionMt, 'Set-Mathematical', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8254exactlyAssertedEL_next(collectionConventionMt, 'SententialRelation', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8255exactlyAssertedEL_next(collectionConventionMt, 'ScopingRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8256exactlyAssertedEL_next(collectionConventionMt, 'ScalarPointValue', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8257exactlyAssertedEL_next(collectionConventionMt, 'ScalarInterval', 'UniversalVocabularyMt', 'BaseKB', vSthrDef).
 8258exactlyAssertedEL_next(collectionConventionMt, 'ScalarIntegralValue', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8259exactlyAssertedEL_next(collectionConventionMt, tRelation, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8260exactlyAssertedEL_next(collectionConventionMt, 'ReifiableFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8261exactlyAssertedEL_next(collectionConventionMt, 'ReformulatorDirectivePredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8262exactlyAssertedEL_next(collectionConventionMt, 'ReflexiveBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8263exactlyAssertedEL_next(collectionConventionMt, 'RealNumber', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8264exactlyAssertedEL_next(collectionConventionMt, 'QuintaryRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8265exactlyAssertedEL_next(collectionConventionMt, 'QuintaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8266exactlyAssertedEL_next(collectionConventionMt, 'QuintaryFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8267exactlyAssertedEL_next(collectionConventionMt, 'QuaternaryRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8268exactlyAssertedEL_next(collectionConventionMt, 'QuaternaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8269exactlyAssertedEL_next(collectionConventionMt, 'QuaternaryFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8270exactlyAssertedEL_next(collectionConventionMt, 'Quantifier', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8271exactlyAssertedEL_next(collectionConventionMt, 'ProblemSolvingCntxt', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8272exactlyAssertedEL_next(collectionConventionMt, tPred, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8273exactlyAssertedEL_next(collectionConventionMt, 'PositiveInteger', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8274exactlyAssertedEL_next(collectionConventionMt, 'PartiallyCommutativeRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8275exactlyAssertedEL_next(collectionConventionMt, 'NonNegativeScalarInterval', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8276exactlyAssertedEL_next(collectionConventionMt, 'NonNegativeInteger', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8277exactlyAssertedEL_next(collectionConventionMt, 'Multigraph', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8278exactlyAssertedEL_next(collectionConventionMt, 'MonthOfYearType', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8279exactlyAssertedEL_next(collectionConventionMt, 'MicrotheoryDesignatingRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8280exactlyAssertedEL_next(collectionConventionMt, 'Microtheory', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8281exactlyAssertedEL_next(collectionConventionMt, 'LogicalConnective', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8282exactlyAssertedEL_next(collectionConventionMt, 'List', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8283exactlyAssertedEL_next(collectionConventionMt, 'IrreflexiveBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8284exactlyAssertedEL_next(collectionConventionMt, 'InterArgIsaPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8285exactlyAssertedEL_next(collectionConventionMt, 'InterArgFormatPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8286exactlyAssertedEL_next(collectionConventionMt, 'Integer', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8287exactlyAssertedEL_next(collectionConventionMt, 'InferenceRelatedBookkeepingPredicate', 'BaseKB', 'BaseKB', vStrMon).
 8288exactlyAssertedEL_next(collectionConventionMt, 'Individual', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8289exactlyAssertedEL_next(collectionConventionMt, 'HypotheticalContext', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8290exactlyAssertedEL_next(collectionConventionMt, 'HLExternalIDString', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8291exactlyAssertedEL_next(collectionConventionMt, tFunction, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8292exactlyAssertedEL_next(collectionConventionMt, 'Format', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8293exactlyAssertedEL_next(collectionConventionMt, 'FixedAritySkolemFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8294exactlyAssertedEL_next(collectionConventionMt, 'FixedAritySkolemFuncN', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8295exactlyAssertedEL_next(collectionConventionMt, 'FixedArityRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8296exactlyAssertedEL_next(collectionConventionMt, 'ExistentialQuantifier-Bounded', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8297exactlyAssertedEL_next(collectionConventionMt, 'ExistentialQuantifier', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8298exactlyAssertedEL_next(collectionConventionMt, 'ExceptionPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8299exactlyAssertedEL_next(collectionConventionMt, 'EvaluatableRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8300exactlyAssertedEL_next(collectionConventionMt, 'EvaluatableFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8301exactlyAssertedEL_next(collectionConventionMt, 'ELRelation-Reversible', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8302exactlyAssertedEL_next(collectionConventionMt, 'ELRelation-OneWay', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8303exactlyAssertedEL_next(collectionConventionMt, 'ELRelation', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8304exactlyAssertedEL_next(collectionConventionMt, 'DistributingMetaKnowledgePredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8305exactlyAssertedEL_next(collectionConventionMt, 'DisjointCollectionType', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8306exactlyAssertedEL_next(collectionConventionMt, 'DirectedMultigraph', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8307exactlyAssertedEL_next(collectionConventionMt, 'DefaultMonotonicPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8308exactlyAssertedEL_next(collectionConventionMt, ftVar, 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8309exactlyAssertedEL_next(collectionConventionMt, 'CycLTruthValueSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8310exactlyAssertedEL_next(collectionConventionMt, 'CycLTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8311exactlyAssertedEL_next(collectionConventionMt, 'CycLSentence-Assertible', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8312exactlyAssertedEL_next(collectionConventionMt, 'CycLSentence-Askable', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8313exactlyAssertedEL_next(collectionConventionMt, 'CycLSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8314exactlyAssertedEL_next(collectionConventionMt, 'CycLRuleAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8315exactlyAssertedEL_next(collectionConventionMt, 'CycLRepresentedTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8316exactlyAssertedEL_next(collectionConventionMt, 'CycLRepresentedAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8317exactlyAssertedEL_next(collectionConventionMt, 'CycLReifiedDenotationalTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8318exactlyAssertedEL_next(collectionConventionMt, 'CycLReifiableNonAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8319exactlyAssertedEL_next(collectionConventionMt, 'CycLReifiableDenotationalTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8320exactlyAssertedEL_next(collectionConventionMt, 'CycLPropositionalSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8321exactlyAssertedEL_next(collectionConventionMt, 'CycLOpenSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8322exactlyAssertedEL_next(collectionConventionMt, 'CycLOpenNonAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8323exactlyAssertedEL_next(collectionConventionMt, 'CycLOpenFormula', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8324exactlyAssertedEL_next(collectionConventionMt, 'CycLOpenExpression', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8325exactlyAssertedEL_next(collectionConventionMt, 'CycLOpenDenotationalTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8326exactlyAssertedEL_next(collectionConventionMt, 'CycLNonAtomicTerm-Assertible', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8327exactlyAssertedEL_next(collectionConventionMt, 'CycLNonAtomicTerm-Askable', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8328exactlyAssertedEL_next(collectionConventionMt, 'CycLNonAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8329exactlyAssertedEL_next(collectionConventionMt, 'CycLNonAtomicReifiedTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8330exactlyAssertedEL_next(collectionConventionMt, 'CycLIndexedTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8331exactlyAssertedEL_next(collectionConventionMt, 'CycLGenericRelationFormula', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8332exactlyAssertedEL_next(collectionConventionMt, 'CycLGAFAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8333exactlyAssertedEL_next(collectionConventionMt, 'CycLFormulaicSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8334exactlyAssertedEL_next(collectionConventionMt, 'CycLFormula', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8335exactlyAssertedEL_next(collectionConventionMt, ttExpressionType, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8336exactlyAssertedEL_next(collectionConventionMt, 'CycLExpression-Assertible', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8337exactlyAssertedEL_next(collectionConventionMt, 'CycLExpression-Askable', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8338exactlyAssertedEL_next(collectionConventionMt, 'CycLExpression', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8339exactlyAssertedEL_next(collectionConventionMt, 'CycLDenotationalTerm-Assertible', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8340exactlyAssertedEL_next(collectionConventionMt, 'CycLDenotationalTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8341exactlyAssertedEL_next(collectionConventionMt, 'CycLDeducedAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8342exactlyAssertedEL_next(collectionConventionMt, 'CycLConstant', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8343exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8344exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedNonAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8345exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedFormula', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8346exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedExpression', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8347exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedDenotationalTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8348exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8349exactlyAssertedEL_next(collectionConventionMt, 'CycLClosedAtomicSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8350exactlyAssertedEL_next(collectionConventionMt, 'CycLAtomicTerm', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8351exactlyAssertedEL_next(collectionConventionMt, 'CycLAtomicSentence', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8352exactlyAssertedEL_next(collectionConventionMt, 'CycLAtomicAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8353exactlyAssertedEL_next(collectionConventionMt, 'CycLAssertionDirection', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8354exactlyAssertedEL_next(collectionConventionMt, 'CycLAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8355exactlyAssertedEL_next(collectionConventionMt, 'CycLAssertedAssertion', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8356exactlyAssertedEL_next(collectionConventionMt, 'CommutativeRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8357exactlyAssertedEL_next(collectionConventionMt, 'CollectionDenotingFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8358exactlyAssertedEL_next(collectionConventionMt, tCol, 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8359exactlyAssertedEL_next(collectionConventionMt, 'CanonicalizerDirective', 'CoreCycLImplementationMt', 'BaseKB', vStrMon).
 8360exactlyAssertedEL_next(collectionConventionMt, 'BroadMicrotheory', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8361exactlyAssertedEL_next(collectionConventionMt, 'BroadMicrotheory', 'BaseKB', 'BaseKB', vStrMon).
 8362exactlyAssertedEL_next(collectionConventionMt, 'BookkeepingPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8363exactlyAssertedEL_next(collectionConventionMt, 'BinaryRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8364exactlyAssertedEL_next(collectionConventionMt, 'BinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8365exactlyAssertedEL_next(collectionConventionMt, 'BinaryFunction', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8366exactlyAssertedEL_next(collectionConventionMt, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8367exactlyAssertedEL_next(collectionConventionMt, 'AsymmetricBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8368exactlyAssertedEL_next(collectionConventionMt, 'AssociativeRelation', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8369exactlyAssertedEL_next(collectionConventionMt, 'ArgTypeTernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8370exactlyAssertedEL_next(collectionConventionMt, 'ArgTypePredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8371exactlyAssertedEL_next(collectionConventionMt, 'ArgTypeBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8372exactlyAssertedEL_next(collectionConventionMt, 'ArgQuotedIsaTernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrMon).
 8373exactlyAssertedEL_next(collectionConventionMt, 'ArgIsaTernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8374exactlyAssertedEL_next(collectionConventionMt, 'ArgIsaBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8375exactlyAssertedEL_next(collectionConventionMt, 'ArgGenlTernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8376exactlyAssertedEL_next(collectionConventionMt, 'ArgGenlQuantityTernaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8377exactlyAssertedEL_next(collectionConventionMt, 'ArgGenlQuantityBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8378exactlyAssertedEL_next(collectionConventionMt, 'ArgGenlBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8379exactlyAssertedEL_next(collectionConventionMt, 'ArgConstraintPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8380exactlyAssertedEL_next(collectionConventionMt, 'AntiTransitiveBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8381exactlyAssertedEL_next(collectionConventionMt, 'AntiSymmetricBinaryPredicate', 'UniversalVocabularyMt', 'BaseKB', vStrDef).
 8382
 8383exactlyAssertedEL_next(canonicalizerDirectiveForArg, 'FormulaArgSetFn', 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8384exactlyAssertedEL_next(canonicalizerDirectiveForArg, 'FormulaArityFn', 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8385exactlyAssertedEL_next(canonicalizerDirectiveForArg, collectionExpansion, 2, 'AllowGenericArgVariables', 'UniversalVocabularyImplementationMt', vStrDef).
 8386exactlyAssertedEL_next(canonicalizerDirectiveForArg, collectionExpansion, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrDef).
 8387exactlyAssertedEL_next(canonicalizerDirectiveForArg, expansion, 2, 'AllowGenericArgVariables', 'UniversalVocabularyImplementationMt', vStrMon).
 8388exactlyAssertedEL_next(canonicalizerDirectiveForArg, expansion, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8389exactlyAssertedEL_next(canonicalizerDirectiveForArg, formulaArity, 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrDef).
 8390exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulationPrecondition, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8391exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorEquals, 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8392exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorEquals, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8393exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorEquiv, 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8394exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorEquiv, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8395exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorRule, 1, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8396exactlyAssertedEL_next(canonicalizerDirectiveForArg, reformulatorRule, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8397exactlyAssertedEL_next(canonicalizerDirectiveForArg, trueRule, 2, 'LeaveSomeTermsAtEL', 'UniversalVocabularyImplementationMt', vStrMon).
 8398exactlyAssertedEL_next(relationAll, knownSentence, 'CycLAssertion', 'UniversalVocabularyMt', vStrMon).
 8399exactlyAssertedEL_next(relationAll, decontextualizedCollection, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', vStrMon).
 8400exactlyAssertedEL_next(relationAll, minimizeExtent, 'BookkeepingPredicate', 'BaseKB', vStrDef).
 8401exactlyAssertedEL_next(relationAllExists, constantID, 'CycLConstant', 'NonNegativeInteger', 'BaseKB', vStrMon).
 8402exactlyAssertedEL_next(relationAllExists, cycProblemStoreID, 'CycProblemStore', 'NonNegativeInteger', 'UniversalVocabularyMt', vStrDef).
 8403exactlyAssertedEL_next(relationAllExists, cycProblemStoreInferences, 'CycProblemStore', 'CycInference', 'UniversalVocabularyMt', vStrDef).
 8404exactlyAssertedEL_next(relationAllExists, natFunction, 'CycLNonAtomicTerm-ClosedFunctor', 'ReifiableFunction', 'BaseKB', vStrMon).
 8405exactlyAssertedEL_next(relationAllInstance, arg1Isa, 'ArgTypeBinaryPredicate', tRelation, 'BaseKB', vStrDef).
 8406exactlyAssertedEL_next(relationAllInstance, arg1Isa, 'ArgTypeTernaryPredicate', tRelation, 'BaseKB', vStrDef).
 8407exactlyAssertedEL_next(relationAllInstance, arg2Isa, 'ArgGenlBinaryPredicate', tCol, 'BaseKB', vStrDef).
 8408exactlyAssertedEL_next(relationAllInstance, arg2Isa, 'ArgIsaBinaryPredicate', tCol, 'BaseKB', vStrDef).
 8409exactlyAssertedEL_next(relationAllInstance, arg2Isa, 'ArgTypeTernaryPredicate', 'NonNegativeInteger', 'BaseKB', vStrDef).
 8410exactlyAssertedEL_next(relationAllInstance, arg3Isa, 'ArgGenlTernaryPredicate', tCol, 'BaseKB', vStrDef).
 8411exactlyAssertedEL_next(relationAllInstance, arg3Isa, 'ArgIsaTernaryPredicate', tCol, 'BaseKB', vStrDef).
 8412exactlyAssertedEL_next(relationAllInstance, arity, 'BinaryRelation', 2, 'CoreCycLMt', vStrMon).
 8413exactlyAssertedEL_next(relationAllInstance, arity, 'QuaternaryRelation', 4, 'BaseKB', vStrMon).
 8414exactlyAssertedEL_next(relationAllInstance, arity, 'QuintaryRelation', 5, 'BaseKB', vStrMon).
 8415exactlyAssertedEL_next(relationAllInstance, arity, 'TernaryRelation', 3, 'BaseKB', vStrMon).
 8416exactlyAssertedEL_next(relationAllInstance, arity, 'UnaryRelation', 1, 'BaseKB', vStrMon).
 8417exactlyAssertedEL_next(relationAllInstance, arityMax, 'UnitOfMeasure', 2, 'BaseKB', vStrDef).
 8418exactlyAssertedEL_next(relationAllInstance, arityMin, 'UnitOfMeasure', 1, 'BaseKB', vStrDef).
 8419exactlyAssertedEL_next(relationAllInstance, assertionDirection, 'CycLGAFAssertion', 'Forward-AssertionDirection', 'BaseKB', vStrDef).
 8420exactlyAssertedEL_next(relationAllInstance, assertionDirection, 'CycLRuleAssertion', 'Backward-AssertionDirection', 'BaseKB', vStrDef).
 8421exactlyAssertedEL_next(relationAllInstance, collectionConventionMt, 'AtemporalNecessarilyEssentialCollectionType', 'UniversalVocabularyMt', 'UniversalVocabularyMt', vStrMon).
 8422exactlyAssertedEL_next(relationAllInstance, definingMt, 'Microtheory', 'BaseKB', 'BaseKB', vStrDef).
 8423exactlyAssertedEL_next(relationAllInstance, genlMt, 'Microtheory', 'BaseKB', 'BaseKB', vStrDef).
 8424exactlyAssertedEL_next(relationAllInstance, genlPreds, 'IrreflexiveBinaryPredicate', different, 'BaseKB', vStrMon).
 8425exactlyAssertedEL_next(relationAllInstance, genls, tCol, 'Thing', 'BaseKB', vStrMon).
 8426exactlyAssertedEL_next(relationAllInstance, resultIsa, 'CollectionDenotingFunction', tCol, 'UniversalVocabularyMt', vStrDef).
 8427exactlyAssertedEL_next(relationInstanceAll, subsetOf, 'TheEmptySet', 'SetOrCollection', 'BaseKB', vStrDef).
 8428exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa1-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8429exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa1-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8430exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa1-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8431exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa1-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8432exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa2-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8433exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa2-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8434exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa2-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8435exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa2-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8436exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa3-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8437exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa3-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8438exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa3-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8439exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa3-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8440exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa4-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8441exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa4-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8442exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa4-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8443exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa4-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8444exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa5-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8445exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa5-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8446exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa5-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8447exactlyAssertedEL_next(transitiveViaArg, 'interArgIsa5-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8448exactlyAssertedEL_next(transitiveViaArg, admittedAllArgument, genlPreds, 2, 'UniversalVocabularyMt', vStrMon).
 8449exactlyAssertedEL_next(transitiveViaArg, arg1Genl, genls, 2, 'BaseKB', vStrMon).
 8450exactlyAssertedEL_next(transitiveViaArg, arg1Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8451exactlyAssertedEL_next(transitiveViaArg, arg1Isa, genls, 2, 'BaseKB', vStrMon).
 8452exactlyAssertedEL_next(transitiveViaArg, arg1Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8453exactlyAssertedEL_next(transitiveViaArg, arg1SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8454exactlyAssertedEL_next(transitiveViaArg, arg2Genl, genls, 2, 'BaseKB', vStrMon).
 8455exactlyAssertedEL_next(transitiveViaArg, arg2Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8456exactlyAssertedEL_next(transitiveViaArg, arg2Isa, genls, 2, 'BaseKB', vStrMon).
 8457exactlyAssertedEL_next(transitiveViaArg, arg2Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8458exactlyAssertedEL_next(transitiveViaArg, arg2SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8459exactlyAssertedEL_next(transitiveViaArg, arg3Genl, genls, 2, 'BaseKB', vStrMon).
 8460exactlyAssertedEL_next(transitiveViaArg, arg3Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8461exactlyAssertedEL_next(transitiveViaArg, arg3Isa, genls, 2, 'BaseKB', vStrMon).
 8462exactlyAssertedEL_next(transitiveViaArg, arg3Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8463exactlyAssertedEL_next(transitiveViaArg, arg3SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8464exactlyAssertedEL_next(transitiveViaArg, arg4Genl, genls, 2, 'BaseKB', vStrMon).
 8465exactlyAssertedEL_next(transitiveViaArg, arg4Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8466exactlyAssertedEL_next(transitiveViaArg, arg4Isa, genls, 2, 'BaseKB', vStrMon).
 8467exactlyAssertedEL_next(transitiveViaArg, arg4Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8468exactlyAssertedEL_next(transitiveViaArg, arg4SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8469exactlyAssertedEL_next(transitiveViaArg, arg5Genl, genls, 2, 'BaseKB', vStrMon).
 8470exactlyAssertedEL_next(transitiveViaArg, arg5Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8471exactlyAssertedEL_next(transitiveViaArg, arg5Isa, genls, 2, 'BaseKB', vStrMon).
 8472exactlyAssertedEL_next(transitiveViaArg, arg5Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8473exactlyAssertedEL_next(transitiveViaArg, arg5SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8474exactlyAssertedEL_next(transitiveViaArg, arg6Genl, genls, 2, 'BaseKB', vStrMon).
 8475exactlyAssertedEL_next(transitiveViaArg, arg6Genl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8476exactlyAssertedEL_next(transitiveViaArg, arg6Isa, genls, 2, 'BaseKB', vStrMon).
 8477exactlyAssertedEL_next(transitiveViaArg, arg6Isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8478exactlyAssertedEL_next(transitiveViaArg, arg6SometimesIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8479exactlyAssertedEL_next(transitiveViaArg, argAndRestGenl, genls, 3, 'BaseKB', vStrDef).
 8480exactlyAssertedEL_next(transitiveViaArg, argAndRestIsa, genls, 3, 'BaseKB', vStrMon).
 8481exactlyAssertedEL_next(transitiveViaArg, argIsa, genls, 3, 'BaseKB', vStrMon).
 8482exactlyAssertedEL_next(transitiveViaArg, argsGenl, genls, 2, 'BaseKB', vStrMon).
 8483exactlyAssertedEL_next(transitiveViaArg, argsGenl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8484exactlyAssertedEL_next(transitiveViaArg, argsIsa, genls, 2, 'BaseKB', vStrMon).
 8485exactlyAssertedEL_next(transitiveViaArg, argsIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8486exactlyAssertedEL_next(transitiveViaArg, canonicalizerDirectiveForAllArgs, genlCanonicalizerDirectives, 2, 'CoreCycLImplementationMt', vStrMon).
 8487exactlyAssertedEL_next(transitiveViaArg, canonicalizerDirectiveForArg, genlCanonicalizerDirectives, 3, 'CoreCycLImplementationMt', vStrMon).
 8488exactlyAssertedEL_next(transitiveViaArg, canonicalizerDirectiveForArgAndRest, genlCanonicalizerDirectives, 3, 'CoreCycLImplementationMt', vStrMon).
 8489exactlyAssertedEL_next(transitiveViaArg, defnSufficient, genls, 1, 'UniversalVocabularyMt', vStrDef).
 8490exactlyAssertedEL_next(transitiveViaArg, genlInverse, genlPreds, 2, 'BaseKB', vStrDef).
 8491exactlyAssertedEL_next(transitiveViaArg, genls, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8492exactlyAssertedEL_next(transitiveViaArg, greaterThan, quantitySubsumes, 2, 'UniversalVocabularyMt', vStrMon).
 8493exactlyAssertedEL_next(transitiveViaArg, holdsIn, sentenceImplies, 2, 'BaseKB', vStrMon).
 8494exactlyAssertedEL_next(transitiveViaArg, isa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8495exactlyAssertedEL_next(transitiveViaArg, quotedIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8496exactlyAssertedEL_next(transitiveViaArg, relationAll, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8497exactlyAssertedEL_next(transitiveViaArg, relationAllExists, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8498exactlyAssertedEL_next(transitiveViaArg, relationAllExists, genls, 3, 'UniversalVocabularyMt', vStrMon).
 8499exactlyAssertedEL_next(transitiveViaArg, relationAllExistsMin, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8500exactlyAssertedEL_next(transitiveViaArg, relationAllExistsMin, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8501exactlyAssertedEL_next(transitiveViaArg, relationAllInstance, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8502exactlyAssertedEL_next(transitiveViaArg, relationExistsAll, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8503exactlyAssertedEL_next(transitiveViaArg, relationExistsAll, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8504exactlyAssertedEL_next(transitiveViaArg, relationExistsCountAll, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8505exactlyAssertedEL_next(transitiveViaArg, relationExistsInstance, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8506exactlyAssertedEL_next(transitiveViaArg, relationExistsInstance, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8507exactlyAssertedEL_next(transitiveViaArg, relationExistsMinAll, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8508exactlyAssertedEL_next(transitiveViaArg, relationExistsMinAll, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8509exactlyAssertedEL_next(transitiveViaArg, relationInstanceAll, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8510exactlyAssertedEL_next(transitiveViaArg, relationInstanceExists, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8511exactlyAssertedEL_next(transitiveViaArg, relationInstanceExists, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8512exactlyAssertedEL_next(transitiveViaArg, relationInstanceMember, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8513exactlyAssertedEL_next(transitiveViaArg, relationMemberInstance, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8514exactlyAssertedEL_next(transitiveViaArg, requiredArg1Pred, genlPreds, 2, 'UniversalVocabularyMt', vStrDef).
 8515exactlyAssertedEL_next(transitiveViaArg, requiredArg2Pred, genlPreds, 2, 'UniversalVocabularyMt', vStrDef).
 8516exactlyAssertedEL_next(transitiveViaArg, resultGenl, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8517exactlyAssertedEL_next(transitiveViaArg, resultIsa, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8518exactlyAssertedEL_next(transitiveViaArg, subsetOf, subsetOf, 2, 'BaseKB', vStrMon).
 8519exactlyAssertedEL_next(transitiveViaArg, subsetOf, subsetOf, 2, 'UniversalVocabularyMt', vStrDef).
 8520exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-2', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8521exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-2', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8522exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-3', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8523exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-3', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8524exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8525exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-4', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8526exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-4', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8527exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8528exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-5', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8529exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-5', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8530exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa1-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8531exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-1', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8532exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-1', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8533exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-3', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8534exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-3', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8535exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8536exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-4', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8537exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-4', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8538exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8539exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-5', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8540exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-5', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8541exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa2-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8542exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-1', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8543exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-1', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8544exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8545exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-2', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8546exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-2', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8547exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8548exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-4', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8549exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-4', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8550exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8551exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-5', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8552exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-5', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8553exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa3-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8554exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-1', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8555exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-1', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8556exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8557exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-2', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8558exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-2', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8559exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8560exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-3', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8561exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-3', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8562exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8563exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-5', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8564exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-5', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8565exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa4-5', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8566exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-1', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8567exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-1', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8568exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-1', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8569exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-2', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8570exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-2', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8571exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-2', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8572exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-3', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8573exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-3', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8574exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-3', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8575exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-4', genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8576exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-4', genls, 2, 'UniversalVocabularyMt', vStrDef).
 8577exactlyAssertedEL_next(transitiveViaArgInverse, 'interArgIsa5-4', genls, 3, 'UniversalVocabularyMt', vStrDef).
 8578exactlyAssertedEL_next(transitiveViaArgInverse, admittedAllArgument, genls, 1, 'UniversalVocabularyMt', vStrMon).
 8579exactlyAssertedEL_next(transitiveViaArgInverse, defnNecessary, genls, 1, 'UniversalVocabularyMt', vStrDef).
 8580exactlyAssertedEL_next(transitiveViaArgInverse, disjointWith, genls, 1, 'UniversalVocabularyMt', vStrDef).
 8581exactlyAssertedEL_next(transitiveViaArgInverse, disjointWith, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8582exactlyAssertedEL_next(transitiveViaArgInverse, genlInverse, genlPreds, 1, 'BaseKB', vStrDef).
 8583exactlyAssertedEL_next(transitiveViaArgInverse, genls, genls, 1, 'UniversalVocabularyMt', vStrMon).
 8584exactlyAssertedEL_next(transitiveViaArgInverse, interArgResultIsa, genls, 3, 'UniversalVocabularyMt', vStrMon).
 8585exactlyAssertedEL_next(transitiveViaArgInverse, ist, genlMt, 1, 'UniversalVocabularyMt', vStrMon).
 8586exactlyAssertedEL_next(transitiveViaArgInverse, microtheoryDesignationArgnum, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8587exactlyAssertedEL_next(transitiveViaArgInverse, negationPreds, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8588exactlyAssertedEL_next(transitiveViaArgInverse, negationPreds, genlPreds, 2, 'UniversalVocabularyMt', vStrMon).
 8589exactlyAssertedEL_next(transitiveViaArgInverse, relationAll, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8590exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExists, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8591exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExistsCount, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8592exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExistsMax, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8593exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExistsMax, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8594exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExistsMax, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8595exactlyAssertedEL_next(transitiveViaArgInverse, relationAllExistsMin, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8596exactlyAssertedEL_next(transitiveViaArgInverse, relationAllInstance, genls, 2, 'UniversalVocabularyMt', vStrMon).
 8597exactlyAssertedEL_next(transitiveViaArgInverse, relationAllInstance, quantitySubsumes, 3, 'UniversalVocabularyMt', vStrDef).
 8598exactlyAssertedEL_next(transitiveViaArgInverse, relationExistsAll, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8599exactlyAssertedEL_next(transitiveViaArgInverse, relationExistsMaxAll, genlPreds, 1, 'UniversalVocabularyMt', vStrDef).
 8600exactlyAssertedEL_next(transitiveViaArgInverse, relationExistsMaxAll, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8601exactlyAssertedEL_next(transitiveViaArgInverse, relationExistsMaxAll, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8602exactlyAssertedEL_next(transitiveViaArgInverse, relationExistsMinAll, genls, 2, 'UniversalVocabularyMt', vStrDef).
 8603exactlyAssertedEL_next(transitiveViaArgInverse, relationInstanceAll, genls, 3, 'UniversalVocabularyMt', vStrDef).
 8604exactlyAssertedEL_next(transitiveViaArgInverse, requiredArg1Pred, genls, 1, 'UniversalVocabularyMt', vStrDef).
 8605exactlyAssertedEL_next(transitiveViaArgInverse, requiredArg2Pred, genls, 1, 'UniversalVocabularyMt', vStrDef).
 8606exactlyAssertedEL_next(transitiveViaArgInverse, sentenceDesignationArgnum, genlPreds, 1, 'UniversalVocabularyMt', vStrMon).
 8607exactlyAssertedEL_next(transitiveViaArgInverse, subsetOf, subsetOf, 1, 'BaseKB', vStrMon).
 8608assertedTinyKB_implies_first( isa('$VAR'('UNIT'), 'UnitOfMeasure'), arityMin('$VAR'('UNIT'), 1), 'BaseKB', vStrMon).
 8609assertedTinyKB_implies_first( isa('$VAR'('UNIT'), 'UnitOfMeasure'), arityMax('$VAR'('UNIT'), 2), 'BaseKB', vStrMon).
 8610assertedTinyKB_implies_first( isa('$VAR'('TEMPLATE'), 'RuleTemplate'), ruleTemplateDirection('$VAR'('TEMPLATE'), 'Backward-AssertionDirection'), 'BaseKB', vStrDef).
 8611assertedTinyKB_implies_first( isa('$VAR'('REL'), 'UnaryRelation'), arity('$VAR'('REL'), 1), 'CoreCycLMt', vStrMon).
 8612assertedTinyKB_implies_first( isa('$VAR'('REL'), 'TernaryRelation'), arity('$VAR'('REL'), 3), 'CoreCycLMt', vStrMon).
 8613assertedTinyKB_implies_first( isa('$VAR'('REL'), 'QuintaryRelation'), arity('$VAR'('REL'), 5), 'CoreCycLMt', vStrMon).
 8614assertedTinyKB_implies_first( isa('$VAR'('REL'), 'QuaternaryRelation'), arity('$VAR'('REL'), 4), 'CoreCycLMt', vStrMon).
 8615assertedTinyKB_implies_first( isa('$VAR'('REL'), 'BinaryRelation'), arity('$VAR'('REL'), 2), 'CoreCycLMt', vStrMon).
 8616assertedTinyKB_implies_first( interArgResultIsa('$VAR'('FN'), '$VAR'('_NUM'), 'Thing', '$VAR'('COLL')), resultIsa('$VAR'('FN'), '$VAR'('COLL')), 'UniversalVocabularyMt', vStrDef).
 8617assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 5, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'interArgIsa5-4'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8618assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 5, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'interArgIsa5-3'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8619assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 5, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'interArgIsa5-2'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8620assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 5, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'interArgIsa5-1'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8621assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 4, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'interArgIsa4-5'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8622assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 4, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'interArgIsa4-3'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8623assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 4, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'interArgIsa4-2'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8624assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 4, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'interArgIsa4-1'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8625assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 3, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'interArgIsa3-5'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8626assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 3, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'interArgIsa3-4'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8627assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 3, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'interArgIsa3-2'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8628assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 3, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'interArgIsa3-1'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8629assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 2, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'interArgIsa2-5'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8630assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 2, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'interArgIsa2-4'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8631assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 2, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'interArgIsa2-3'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8632assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 2, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'interArgIsa2-1'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'UniversalVocabularyMt', vStrMon).
 8633assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 1, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'interArgIsa1-5'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8634assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 1, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'interArgIsa1-4'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8635assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 1, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'interArgIsa1-3'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8636assertedTinyKB_implies_first( interArgIsa('$VAR'('PRED'), 1, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'interArgIsa1-2'('$VAR'('PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8637assertedTinyKB_implies_first( argQuotedIsa('$VAR'('PRED'), '$VAR'('N'), '$VAR'('_COL')), quotedArgument('$VAR'('PRED'), '$VAR'('N')), 'UniversalVocabularyMt', vStrDef).
 8638assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 6), arg6Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'BaseKB', vStrMon).
 8639assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 5), arg5Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 8640assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 4), arg4Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 8641assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 3), arg3Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 8642assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 2), arg2Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 8643assertedTinyKB_implies_first( and(resultIsaArg('$VAR'('FUNC'), 1), arg1Genl('$VAR'('FUNC'), '$VAR'('COL'))), resultIsa('$VAR'('FUNC'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 8644assertedTinyKB_implies_first( and(resultIsa('$VAR'('FUNCTION'), '$VAR'('COLTYPE')), genls('$VAR'('COLTYPE'), tCol)), isa('$VAR'('FUNCTION'), 'CollectionDenotingFunction'), 'BaseKB', vStrMon).
 8645assertedTinyKB_implies_first( instanceElementType('$VAR'('SET_TYPE'), '$VAR'('_COL')), defnSufficient('$VAR'('SET_TYPE'), 'SubLQuoteFn'('CYC-SET-OF-TYPE-SUFFICIENT')), 'UniversalVocabularyImplementationMt', vStrMon).
 8646
 8647assertedTinyKB_implies_first( hypotheticalTerm('$VAR'('TERM')), quotedIsa('$VAR'('TERM'), 'IndeterminateTerm'), 'CoreCycLImplementationMt', vStrDef).
 8648assertedTinyKB_implies_first( hypotheticalTerm('$VAR'('TERM')), highlyRelevantTerm('$VAR'('TERM')), 'CoreCycLImplementationMt', vStrDef).
 8649assertedTinyKB_implies_first( hypotheticalTerm('$VAR'('TERM')), ephemeralTerm('$VAR'('TERM')), 'CoreCycLImplementationMt', vStrDef).
 8650assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 6, '$VAR'('COL')), arg6SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8651assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 5, '$VAR'('COL')), arg5SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8652assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 4, '$VAR'('COL')), arg4SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8653assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 3, '$VAR'('COL')), arg3SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8654assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 2, '$VAR'('COL')), arg2SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8655assertedTinyKB_implies_Already( argSometimesIsa('$VAR'('RELN'), 1, '$VAR'('COL')), arg1SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8656assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 6, '$VAR'('COL')), arg6QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8657assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 5, '$VAR'('COL')), arg5QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8658assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 4, '$VAR'('COL')), arg4QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8659assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 3, '$VAR'('COL')), arg3QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8660assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 2, '$VAR'('COL')), arg2QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8661assertedTinyKB_implies_Already( argQuotedIsa('$VAR'('RELN'), 1, '$VAR'('COL')), arg1QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8662assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 6, '$VAR'('COL')), arg6Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8663assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 5, '$VAR'('COL')), arg5Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8664assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 4, '$VAR'('COL')), arg4Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8665assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 3, '$VAR'('COL')), arg3Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8666assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 2, '$VAR'('COL')), arg2Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8667assertedTinyKB_implies_Already( argIsa('$VAR'('RELN'), 1, '$VAR'('COL')), arg1Isa('$VAR'('RELN'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8668assertedTinyKB_implies_Already( arg6SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 6, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8669assertedTinyKB_implies_Already( arg6QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 6, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8670assertedTinyKB_implies_Already( arg6Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 6, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8671assertedTinyKB_implies_Already( arg5SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 5, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8672assertedTinyKB_implies_Already( arg5QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 5, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8673assertedTinyKB_implies_Already( arg4SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 4, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8674assertedTinyKB_implies_Already( arg4QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 4, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8675assertedTinyKB_implies_Already( arg4Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 4, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8676assertedTinyKB_implies_Already( arg5Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 5, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8677assertedTinyKB_implies_Already( arg3SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 3, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8678assertedTinyKB_implies_Already( arg3QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 3, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8679assertedTinyKB_implies_Already( arg3Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 3, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8680assertedTinyKB_implies_Already( arg2SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 2, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8681assertedTinyKB_implies_Already( arg2QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 2, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8682assertedTinyKB_implies_Already( arg2Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 2, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8683assertedTinyKB_implies_Already( arg1SometimesIsa('$VAR'('RELN'), '$VAR'('COL')), argSometimesIsa('$VAR'('RELN'), 1, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8684assertedTinyKB_implies_Already( arg1QuotedIsa('$VAR'('RELN'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), 1, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8685assertedTinyKB_implies_Already( arg2Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(2, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8686assertedTinyKB_implies_Already( arg1Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 1, '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 8687
 8688assertedTinyKB_implies_first( arg6Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(6, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8689assertedTinyKB_implies_first( arg5Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(5, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8690assertedTinyKB_implies_first( arg4Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(4, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8691assertedTinyKB_implies_first( arg3Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(3, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8692assertedTinyKB_implies_first( arg1Isa('$VAR'('PRED'), '$VAR'('TYPE')), resultIsa('FunctionToArg'(1, '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 8693
 8694assertedTinyKB_implies_first( afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE')), afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE')), 'BaseKB', vStrDef).
 8695assertedTinyKB_implies_first( afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-KEY')), afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('ADD-TVA-CACHE-KEY')), 'BaseKB', vStrDef).
 8696assertedTinyKB_implies_first( afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('ADD-TVA-CACHE-VALUE')), afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE')), 'BaseKB', vStrDef).
 8697assertedTinyKB_implies_first( afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('ADD-TVA-CACHE-KEY')), afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-KEY')), 'BaseKB', vStrDef).
 8698assertedTinyKB_implies_first( disjointWith('$VAR'('X'), '$VAR'('Y')), disjointWith('$VAR'('Y'), '$VAR'('X')), 'LogicalTruthMt', vStrMon).
 8699assertedTinyKB_implies_first( denotes('Quote'('EscapeQuote'('$VAR'('X'))), '$VAR'('_ANYTHING')), denotes('Quote'('EscapeQuote'('$VAR'('X'))), '$VAR'('X')), 'LogicalTruthMt', vStrMon).
 8700assertedTinyKB_implies_first( completelyEnumerableCollection('$VAR'('COL')), completeExtentEnumerableForValueInArg(isa, '$VAR'('COL'), 2), 'CoreCycLMt', vStrDef).
 8701assertedTinyKB_implies_first( completelyDecidableCollection('$VAR'('COL')), completeExtentDecidableForValueInArg(isa, '$VAR'('COL'), 2), 'CoreCycLMt', vStrDef).
 8702assertedTinyKB_implies_first( completeExtentEnumerableForValueInArg(isa, '$VAR'('COL'), 2), completelyEnumerableCollection('$VAR'('COL')), 'CoreCycLMt', vStrDef).
 8703assertedTinyKB_implies_first( completeExtentDecidableForValueInArg(isa, '$VAR'('COL'), 2), completelyDecidableCollection('$VAR'('COL')), 'CoreCycLMt', vStrDef).
 8704assertedTinyKB_implies_first( completeExtentDecidable('$VAR'('PRED')), backchainForbidden('$VAR'('PRED')), 'UniversalVocabularyMt', vStrMon).
 8705assertedTinyKB_implies_first( collectionIsaBackchainRequired('$VAR'('PRED')), collectionIsaBackchainEncouraged('$VAR'('PRED')), 'UniversalVocabularyMt', vStrDef).
 8706assertedTinyKB_implies_first( collectionGenlsBackchainRequired('$VAR'('PRED')), collectionGenlsBackchainEncouraged('$VAR'('PRED')), 'UniversalVocabularyMt', vStrDef).
 8707assertedTinyKB_implies_first( collectionBackchainRequired('$VAR'('PRED')), collectionBackchainEncouraged('$VAR'('PRED')), 'UniversalVocabularyMt', vStrDef).
 8708assertedTinyKB_implies_first( canonicalizerDirectiveForArgAndRest('$VAR'('RELN'), 1, '$VAR'('DIRECTIVE')), canonicalizerDirectiveForAllArgs('$VAR'('RELN'), '$VAR'('DIRECTIVE')), 'CoreCycLImplementationMt', vStrMon).
 8709assertedTinyKB_implies_first( canonicalizerDirectiveForAllArgs('$VAR'('RELN'), '$VAR'('DIRECTIVE')), canonicalizerDirectiveForArgAndRest('$VAR'('RELN'), 1, '$VAR'('DIRECTIVE')), 'CoreCycLImplementationMt', vStrMon).
 8710assertedTinyKB_implies_first( 'interArgIsa5-4'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 5, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8711assertedTinyKB_implies_first( 'interArgIsa5-3'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 5, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8712assertedTinyKB_implies_first( 'interArgIsa5-2'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 5, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8713assertedTinyKB_implies_first( 'interArgIsa5-1'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 5, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8714assertedTinyKB_implies_first( 'interArgIsa4-5'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 4, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8715assertedTinyKB_implies_first( 'interArgIsa4-3'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 4, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8716assertedTinyKB_implies_first( 'interArgIsa4-2'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 4, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8717assertedTinyKB_implies_first( 'interArgIsa4-1'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 4, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8718assertedTinyKB_implies_first( 'interArgIsa3-5'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 3, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8719assertedTinyKB_implies_first( 'interArgIsa3-4'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 3, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8720assertedTinyKB_implies_first( 'interArgIsa3-2'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 3, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8721assertedTinyKB_implies_first( 'interArgIsa3-1'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 3, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8722assertedTinyKB_implies_first( 'interArgIsa2-5'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 2, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8723assertedTinyKB_implies_first( 'interArgIsa2-4'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 2, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8724assertedTinyKB_implies_first( 'interArgIsa2-3'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 2, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8725assertedTinyKB_implies_first( 'interArgIsa2-1'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 2, '$VAR'('IND_COL'), 1, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8726assertedTinyKB_implies_first( 'interArgIsa1-5'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 1, '$VAR'('IND_COL'), 5, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8727assertedTinyKB_implies_first( 'interArgIsa1-4'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 1, '$VAR'('IND_COL'), 4, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8728assertedTinyKB_implies_first( 'interArgIsa1-3'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 1, '$VAR'('IND_COL'), 3, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8729assertedTinyKB_implies_first( 'interArgIsa1-2'('$VAR'('CONSTRAINED_PRED'), '$VAR'('IND_COL'), '$VAR'('DEP_COL')), interArgIsa('$VAR'('CONSTRAINED_PRED'), 1, '$VAR'('IND_COL'), 2, '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8730
 8731assertedTinyKB_implies_first( isa('$VAR'('QUANT'), 'ExistentialQuantifier-Bounded'), arg3QuotedIsa('$VAR'('QUANT'), 'CycLSentence-Assertible'), 'UniversalVocabularyMt', vStrDef).
 8732assertedTinyKB_implies_first( isa('$VAR'('QUANT'), 'ExistentialQuantifier-Bounded'), arg2QuotedIsa('$VAR'('QUANT'), ftVar), 'UniversalVocabularyMt', vStrDef).
 8733assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), transitiveViaArgInverse('$VAR'('PRED'), '$VAR'('PRED'), 1), 'UniversalVocabularyMt', vStrDef).
 8734assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), transitiveViaArg('$VAR'('PRED'), '$VAR'('PRED'), 2), 'BaseKB', vStrMon).
 8735assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), genlInverse('$VAR'('PRED'), '$VAR'('PRED')), 'UniversalVocabularyMt', vStrMon).
 8736assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ReflexiveBinaryPredicate'), genlPreds(equals, '$VAR'('PRED')), 'BaseKB', vStrMon).
 8737assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'IrreflexiveBinaryPredicate'), genlPreds('$VAR'('PRED'), different), 'BaseKB', vStrMon).
 8738assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgIsaPredicate'), arg1Isa('$VAR'('PRED'), tRelation), 'BaseKB', vStrDef).
 8739assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgIsaPredicate'), afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-REMOVING')), 'BaseKB', vStrDef).
 8740assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgIsaPredicate'), afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('INTER-ARG-ISA-AFTER-ADDING')), 'BaseKB', vStrDef).
 8741assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgFormatPredicate'), arg1Isa('$VAR'('PRED'), tRelation), 'BaseKB', vStrDef).
 8742assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgFormatPredicate'), afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('INTER-ARG-FORMAT-AFTER-REMOVING')), 'BaseKB', vStrDef).
 8743assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InterArgFormatPredicate'), afterAdding('$VAR'('PRED'), 'SubLQuoteFn'('INTER-ARG-FORMAT-AFTER-ADDING')), 'BaseKB', vStrDef).
 8744assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'InferenceRelatedBookkeepingPredicate'), definingMt('$VAR'('PRED'), 'BaseKB'), 'BaseKB', vStrMon).
 8745assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'BookkeepingPredicate'), minimizeExtent('$VAR'('PRED')), 'BaseKB', vStrDef).
 8746assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'AsymmetricBinaryPredicate'), negationInverse('$VAR'('PRED'), '$VAR'('PRED')), 'UniversalVocabularyMt', vStrMon).
 8747assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgIsaTernaryPredicate'), transitiveViaArg('$VAR'('PRED'), genls, 3), 'BaseKB', vStrMon).
 8748assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgIsaBinaryPredicate'), transitiveViaArg('$VAR'('PRED'), genls, 2), 'BaseKB', vStrMon).
 8749assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgGenlTernaryPredicate'), transitiveViaArg('$VAR'('PRED'), genls, 3), 'BaseKB', vStrMon).
 8750assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgGenlQuantityTernaryPredicate'), transitiveViaArgInverse('$VAR'('PRED'), quantitySubsumes, 3), 'BaseKB', vStrMon).
 8751assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgGenlQuantityBinaryPredicate'), transitiveViaArgInverse('$VAR'('PRED'), quantitySubsumes, 2), 'BaseKB', vStrMon).
 8752assertedTinyKB_implies_first( isa('$VAR'('PRED'), 'ArgGenlBinaryPredicate'), transitiveViaArg('$VAR'('PRED'), genls, 2), 'BaseKB', vStrMon).
 8753assertedTinyKB_implies_first( isa('$VAR'('MT'), 'Microtheory'), ist('BaseKB', isa('$VAR'('MT'), 'Microtheory')), 'BaseKB', vStrMon).
 8754assertedTinyKB_implies_first( isa('$VAR'('MIC'), 'Microtheory'), genlMt('$VAR'('MIC'), 'BaseKB'), 'BaseKB', vStrMon).
 8755assertedTinyKB_implies_first( isa('$VAR'('MEASURE_FN'), 'UnitOfMeasure'), resultIsa('$VAR'('MEASURE_FN'), 'ScalarInterval'), 'BaseKB', vStrDef).
 8756assertedTinyKB_implies_first( isa('$VAR'('FUNC'), 'IndeterminateTermDenotingFunction'), resultQuotedIsa('$VAR'('FUNC'), 'IndeterminateTerm'), 'BaseKB', vStrDef).
 8757assertedTinyKB_implies_first( isa('$VAR'('COL1'), tCol), or(genls('$VAR'('COL1'), '$VAR'('COL2')), different('$VAR'('COL1'), '$VAR'('COL2'))), 'BaseKB', vStrMon).
 8758assertedTinyKB_implies_first( isa('$VAR'('ANECT'), 'AtemporalNecessarilyEssentialCollectionType'), decontextualizedCollection('$VAR'('ANECT')), 'UniversalVocabularyMt', vStrMon).
 8759assertedTinyKB_implies_first( isa('$VAR'('ANECT'), 'AtemporalNecessarilyEssentialCollectionType'), collectionConventionMt('$VAR'('ANECT'), 'UniversalVocabularyMt'), 'UniversalVocabularyMt', vStrMon).
 8760assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), resultIsaArg('$VAR'('FUNC'), '$VAR'('N')), natArgument('$VAR'('NAT'), '$VAR'('N'), '$VAR'('COL'))), isa('$VAR'('NAT'), '$VAR'('COL')), 'CoreCycLMt', vStrMon).
 8761assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), resultGenlArg('$VAR'('FUNC'), '$VAR'('N')), natArgument('$VAR'('NAT'), '$VAR'('N'), '$VAR'('COL'))), genls('$VAR'('NAT'), '$VAR'('COL')), 'CoreCycLMt', vStrMon).
 8762assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), preservesGenlsInArg('$VAR'('FUNC'), '$VAR'('NUM')), natFunction('$VAR'('INDEP_COLL_NAT'), '$VAR'('FUNC')), genls('$VAR'('TERM'), '$VAR'('INDEP_COLL')), natArgument('$VAR'('NAT'), '$VAR'('NUM'), '$VAR'('TERM')), natArgument('$VAR'('INDEP_COLL_NAT'), '$VAR'('NUM'), '$VAR'('INDEP_COLL'))), genls('$VAR'('NAT'), '$VAR'('INDEP_COLL_NAT')), 'UniversalVocabularyMt', vStrDef).
 8763assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), natArgument('$VAR'('NAT'), '$VAR'('N'), '$VAR'('TERM')), interArgResultIsa('$VAR'('FUNC'), '$VAR'('N'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), isa('$VAR'('NAT'), '$VAR'('DEP_COL')), 'CoreCycLMt', vStrDef).
 8764assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), natArgument('$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')), interArgResultIsa('$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), isa('$VAR'('NAT'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 8765assertedTinyKB_implies_first( and(natFunction('$VAR'('NAT'), '$VAR'('FUNC')), genls('$VAR'('COL'), '$VAR'('INDEP_COL')), natArgument('$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('COL')), interArgResultGenl('$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), genls('$VAR'('NAT'), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 8766
 8767assertedTinyKB_implies_first( genls('$VAR'('SPEC'), 'Quantifier'), decontextualizedCollection('$VAR'('SPEC')), 'BaseKB', vStrMon).
 8768assertedTinyKB_implies_first( genls('$VAR'('SPEC'), 'LogicalConnective'), decontextualizedCollection('$VAR'('SPEC')), 'BaseKB', vStrMon).
 8769assertedTinyKB_implies_first( genlPreds('$VAR'('SPEC_PRED'), genls), afterRemoving('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE')), 'BaseKB', vStrDef).
 8770assertedTinyKB_implies_first( genlPreds('$VAR'('PRED'), termDependsOn), afterRemoving('$VAR'('PRED'), 'SubLQuoteFn'('REMOVE-DEPENDENT-TERM')), 'BaseKB', vStrMon).
 8771assertedTinyKB_implies_first( genlPreds('$VAR'('EQUALITY_PRED'), equals), afterRemoving('$VAR'('EQUALITY_PRED'), 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE')), 'BaseKB', vStrDef).
 8772assertedTinyKB_implies_first( genlPreds('$VAR'('EQUALITY_PRED'), equals), afterAdding('$VAR'('EQUALITY_PRED'), 'SubLQuoteFn'('DECACHE-SOME-EQUALITY-ASSERTIONS-SOMEWHERE')), 'BaseKB', vStrDef).
 8773assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), isa), afterAdding('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-ISA')), 'BaseKB', vStrMon).
 8774assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), genls), afterRemoving('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('REMOVE-TVA-CACHE-VALUE')), 'BaseKB', vStrDef).
 8775assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), genls), afterAdding('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLS')), 'BaseKB', vStrMon).
 8776assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), genlPreds), afterAdding('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLPREDS')), 'BaseKB', vStrMon).
 8777assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), genlMt), afterAdding('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLMT')), 'BaseKB', vStrMon).
 8778assertedTinyKB_implies_first( genlInverse('$VAR'('SPEC_INVERSE'), genlInverse), afterAdding('$VAR'('SPEC_INVERSE'), 'SubLQuoteFn'('PROPAGATE-INVERSE-TO-GENLINVERSE')), 'BaseKB', vStrMon).
 8779
 8780assertedTinyKB_not_first(quotedIsa(thereExistExactly, 'InferenceSupportedTerm'), 'UniversalVocabularyMt', vStrDef).
 8781assertedTinyKB_not_first(quotedIsa(thereExistAtMost, 'InferenceSupportedTerm'), 'UniversalVocabularyMt', vStrDef).
 8782assertedTinyKB_not_first(quotedIsa(thereExistAtLeast, 'InferenceSupportedTerm'), 'UniversalVocabularyMt', vStrDef).
 8783assertedTinyKB_not_first(quotedIsa('False', 'CycLSentence-Assertible'), 'UniversalVocabularyMt', vStrDef).
 8784assertedTinyKB_not_first(isa(subsetOf, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8785assertedTinyKB_not_first(isa(subsetOf, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8786assertedTinyKB_not_first(isa(siblingDisjointExceptions, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8787assertedTinyKB_not_first(isa(quotedIsa, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8788assertedTinyKB_not_first(isa(quotedIsa, 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8789assertedTinyKB_not_first(isa(quotedIsa, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8790assertedTinyKB_not_first(isa(quotedDefnSufficient, 'InferenceSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8791assertedTinyKB_not_first(isa(quotedDefnNecessary, 'InferenceSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8792assertedTinyKB_not_first(isa(quotedDefnIff, 'InferenceSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8793assertedTinyKB_not_first(isa(quantityIntersects, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8794assertedTinyKB_not_first(isa(quantityIntersects, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8795assertedTinyKB_not_first(isa(negationPreds, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8796assertedTinyKB_not_first(isa(negationInverse, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8797assertedTinyKB_not_first(isa(negationInverse, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8798assertedTinyKB_not_first(isa(knownAntecedentRule, 'InferenceSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8799assertedTinyKB_not_first(isa(isa, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8800assertedTinyKB_not_first(isa(isa, 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8801assertedTinyKB_not_first(isa(isa, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8802assertedTinyKB_not_first(isa(genls, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8803assertedTinyKB_not_first(isa(genls, 'AsymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8804assertedTinyKB_not_first(isa(genls, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8805assertedTinyKB_not_first(isa(genlPreds, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8806assertedTinyKB_not_first(isa(genlMt, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8807assertedTinyKB_not_first(isa(genlInverse, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8808assertedTinyKB_not_first(isa(genlInverse, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8809assertedTinyKB_not_first(isa(genlInverse, 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8810assertedTinyKB_not_first(isa(genlInverse, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8811assertedTinyKB_not_first(isa(genlInverse, 'AsymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8812assertedTinyKB_not_first(isa(genlInverse, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8813assertedTinyKB_not_first(isa(evaluationResultQuotedIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8814assertedTinyKB_not_first(isa(evaluate, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8815assertedTinyKB_not_first(isa(elementOf, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8816assertedTinyKB_not_first(isa(elementOf, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8817assertedTinyKB_not_first(isa(elementOf, 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8818assertedTinyKB_not_first(isa(elementOf, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8819assertedTinyKB_not_first(isa(elementOf, 'AsymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8820assertedTinyKB_not_first(isa(elementOf, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8821assertedTinyKB_not_first(isa(disjointWith, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8822assertedTinyKB_not_first(isa(disjointWith, 'IrreflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8823assertedTinyKB_not_first(isa(disjointWith, 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8824assertedTinyKB_not_first(isa(constraint, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8825assertedTinyKB_not_first(isa(conceptuallyRelated, 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8826assertedTinyKB_not_first(isa(conceptuallyRelated, 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8827assertedTinyKB_not_first(isa(arg6SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8828assertedTinyKB_not_first(isa(arg5SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8829assertedTinyKB_not_first(isa(arg4SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8830assertedTinyKB_not_first(isa(arg3SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8831assertedTinyKB_not_first(isa(arg2SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8832assertedTinyKB_not_first(isa(arg1SometimesIsa, 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8833assertedTinyKB_not_first(isa('IntervalEntry', 'WFFSupportedTerm'), 'UniversalVocabularyMt', vStrDef).
 8834assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8835assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8836assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8837assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8838assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'AsymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8839assertedTinyKB_not_first(isa('genls-SpecDenotesGenlInstances', 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8840assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'WFFSupportedPredicate'), 'UniversalVocabularyMt', vStrDef).
 8841assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'TransitiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8842assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'SymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8843assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'ReflexiveBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8844assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'AsymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8845assertedTinyKB_not_first(isa('genls-GenlDenotesSpecInstances', 'AntiSymmetricBinaryPredicate'), 'UniversalVocabularyMt', vStrDef).
 8846assertedTinyKB_not_first(genls('CommutativeRelation', 'PartiallyCommutativeRelation'), 'UniversalVocabularyMt', vStrDef).
 8847assertedTinyKB_not_first(genls('CollectionDenotingFunction', 'ReifiableFunction'), 'UniversalVocabularyMt', vStrDef).
 8848assertedTinyKB_not_first(genlPreds(reformulatorEquals, equals), 'UniversalVocabularyMt', vStrDef).
 8849assertedTinyKB_not_first(genlPreds(hlPrototypicalInstance, isa), 'UniversalVocabularyMt', vStrDef).
 8850assertedTinyKB_not_first(equals('$VAR'('_SET'), 'TheSetOf'('$VAR'('X'), and(isa('$VAR'('X'), 'Set-Mathematical'), not(elementOf('$VAR'('X'), '$VAR'('X')))))), 'BaseKB', vStrMon).
 8851assertedTinyKB_not_first(elementOf('$VAR'('X'), 'TheEmptySet'), 'BaseKB', vStrMon).
 8852assertedTinyKB_not_first(different('$VAR'('OBJ'), '$VAR'('OBJ')), 'BaseKB', vStrMon).
 8853assertedTinyKB_not_first(commutativeInArgsAndRest('$VAR'('REL'), 1, 2, 3), 'BaseKB', vStrDef).
 8854assertedTinyKB_not_first(commutativeInArgsAndRest('$VAR'('REL'), 1, 2), 'BaseKB', vStrDef).
 8855assertedTinyKB_not_first(commutativeInArgsAndRest('$VAR'('REL'), 1), 'BaseKB', vStrDef).
 8856assertedTinyKB_not_first(arg2Isa(evaluate, 'CycLNonAtomicTerm-Askable'), 'UniversalVocabularyMt', vStrDef).
 8857assertedTinyKB_implies( and(natFunction('$VAR'('NAT'), '$VAR'('FUNCTION')), resultQuotedIsa('$VAR'('FUNCTION'), '$VAR'('COL'))), quotedIsa('$VAR'('NAT'), '$VAR'('COL')), 'CoreCycLMt', vStrDef).
 8858assertedTinyKB_implies( and(natFunction('$VAR'('NAT'), '$VAR'('FUNCTION')), resultIsa('$VAR'('FUNCTION'), '$VAR'('COL'))), isa('$VAR'('NAT'), '$VAR'('COL')), 'CoreCycLMt', vStrMon).
 8859assertedTinyKB_implies( and(natFunction('$VAR'('NAT'), '$VAR'('FUNCTION')), resultGenl('$VAR'('FUNCTION'), '$VAR'('COL'))), genls('$VAR'('NAT'), '$VAR'('COL')), 'CoreCycLMt', vStrMon).
 8860
 8861% ================================
 8862% ================================
 8863% ================================
 8864% ================================
 8865% ================================
 8866% ================================
 8867% ================================
 8868% ================================
 8869% ================================
 8870% ================================
 8871
 8872assertedTinyKB_implies( nearestDifferentIsa('$VAR'('OBJ_1'), '$VAR'('OBJ_2'), '$VAR'('NEAR_DIFF')), isa('$VAR'('OBJ_1'), '$VAR'('NEAR_DIFF')), 'BaseKB', vStrMon).
 8873assertedTinyKB_implies( nearestDifferentGenls('$VAR'('COL_1'), '$VAR'('COL_2'), '$VAR'('NEAR_DIFF')), genls('$VAR'('COL_1'), '$VAR'('NEAR_DIFF')), 'BaseKB', vStrMon).
 8874
 8875assertedTinyKB_implies( nearestCommonSpecs('$VAR'('COL'), '$VAR'('COL'), '$VAR'('NEAREST_SPEC')), nearestGenls('$VAR'('NEAREST_SPEC'), '$VAR'('COL')), 'BaseKB', vStrDef).
 8876assertedTinyKB_implies( nearestCommonIsa('$VAR'('OBJ'), '$VAR'('OBJ'), '$VAR'('NEAR_ISA')), nearestIsa('$VAR'('OBJ'), '$VAR'('NEAR_ISA')), 'BaseKB', vStrMon).
 8877assertedTinyKB_implies( nearestCommonGenls('$VAR'('COL'), '$VAR'('COL'), '$VAR'('NEAR_GENL')), nearestGenls('$VAR'('COL'), '$VAR'('NEAR_GENL')), 'BaseKB', vStrMon).
 8878assertedTinyKB_implies( nearestCommonGenlMt('$VAR'('MT'), '$VAR'('MT'), '$VAR'('NEAR_MT')), nearestGenlMt('$VAR'('MT'), '$VAR'('NEAR_MT')), 'BaseKB', vStrMon).
 8879
 8880assertedTinyKB_implies( 'ist-Asserted'('$VAR'('MT'), '$VAR'('FORMULA')), ist('$VAR'('MT'), knownSentence('$VAR'('FORMULA'))), 'UniversalVocabularyMt', vStrMon).
 8881
 8882assertedTinyKB_implies( quotedIsa('$VAR'('ASSERTION'), 'CycLRuleAssertion'), assertionDirection('$VAR'('ASSERTION'), 'Backward-AssertionDirection'), 'BaseKB', vStrDef).
 8883assertedTinyKB_implies( quotedIsa('$VAR'('ASSERTION'), 'CycLGAFAssertion'), assertionDirection('$VAR'('ASSERTION'), 'Forward-AssertionDirection'), 'BaseKB', vStrDef).
 8884
 8885exactlyAssertedEL_with_vars(implies_bc, quotedIsa('$VAR'('X'), '$VAR'('COL')), isa('Quote'('EscapeQuote'('$VAR'('X'))), '$VAR'('COL')), 'BaseKB', vStrDef).
 8886assertedTinyKB_implies( quotedIsa('$VAR'('EXPR'), 'CycLClosedExpression'), equals('Quote'('$VAR'('EXPR')), 'Quote'('EscapeQuote'('$VAR'('EXPR')))), 'BaseKB', vStrMon).
 8887assertedTinyKB_implies( quantitySubsumes('$VAR'('NUM2'), '$VAR'('SUBNUM2')), quantitySubsumes('Unity'('$VAR'('_NUM1'), '$VAR'('NUM2')), '$VAR'('SUBNUM2')), 'BaseKB', vStrDef).
 8888assertedTinyKB_implies( quantitySubsumes('$VAR'('NUM1'), '$VAR'('SUBNUM1')), quantitySubsumes('Unity'('$VAR'('NUM1'), '$VAR'('_NUM2')), '$VAR'('SUBNUM1')), 'BaseKB', vStrDef).
 8889assertedTinyKB_implies( pointQuantValue('$VAR'('SCALAR'), '$VAR'('VALUE')), minQuantValue('$VAR'('SCALAR'), '$VAR'('VALUE')), 'BaseKB', vStrMon).
 8890assertedTinyKB_implies( pointQuantValue('$VAR'('SCALAR'), '$VAR'('VALUE')), maxQuantValue('$VAR'('SCALAR'), '$VAR'('VALUE')), 'BaseKB', vStrMon).
 8891assertedTinyKB_implies( multiplicationUnits('$VAR'('UNIT1'), '$VAR'('UNIT2'), '$VAR'('PROD_UNIT')), multiplicationUnits('$VAR'('UNIT1'), '$VAR'('UNIT2'), '$VAR'('PROD_UNIT')), 'BaseKB', vStrMon).
 8892assertedTinyKB_implies( isa('$VAR'('WEEKDAY'), 'DayOfWeekType'), defnSufficient('$VAR'('WEEKDAY'), 'SubLQuoteFn'('CYC-DAY-OF-WEEK-DEFN')), 'CoreCycLImplementationMt', vStrMon).
 8893assertedTinyKB_implies( isa('$VAR'('UNIT'), 'UnitOfMeasure'), unitMultiplicationFactor('$VAR'('UNIT'), '$VAR'('UNIT'), 1), 'UniversalVocabularyMt', vStrDef).
 8894
 8895assertedTinyKB_implies( isa('$VAR'('CONNECT'), 'ExceptionPredicate'), abnormal('TheList'('$VAR'('CONNECT'), '$VAR'('ARITY'), '$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('N'), '$VAR'('ARG_N_ISA')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[isa, '$VAR'('CONNECT'), 'FixedArityRelation'], [isa, '$VAR'('CONNECT'), 'LogicalConnective'], [arity, '$VAR'('CONNECT'), '$VAR'('ARITY')], [isa, '$VAR'('ARG_N_QUOTED_ISA'), 'ArgQuotedIsaBinaryPredicate'], [constrainsArg, '$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('N')], [integerBetween, 1, '$VAR'('N'), '$VAR'('ARITY')]], [['$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('CONNECT'), 'CycLSentence-Assertible']]], 'BaseKB', ["?CONNECT", "?ARITY", "?ARG-N-QUOTED-ISA", "?N"], [implies, [and, [isa, '$VAR'('CONNECT'), 'FixedArityRelation'], [isa, '$VAR'('CONNECT'), 'LogicalConnective'], [arity, '$VAR'('CONNECT'), '$VAR'('ARITY')], [isa, '$VAR'('ARG_N_QUOTED_ISA'), 'ArgQuotedIsaBinaryPredicate'], [constrainsArg, '$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('N')], [integerBetween, 1, '$VAR'('N'), '$VAR'('ARITY')]], ['$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('CONNECT'), 'CycLSentence-Assertible']])), 'BaseKB', vStrMon).
 8896assertedTinyKB_implies( isa('$VAR'('INSTANCE'), 'ScalarInterval'), abnormal('TheList'('$VAR'('PRED'), '$VAR'('COLLECTION'), '$VAR'('INSTANCE')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[relationAllInstance, '$VAR'('PRED'), '$VAR'('COLLECTION'), '$VAR'('INSTANCE')]], [[conceptuallyRelated, '$VAR'('COLLECTION'), '$VAR'('INSTANCE')]]], 'BaseKB', ["?PRED", "?COLLECTION", "?INSTANCE"], [implies, [relationAllInstance, '$VAR'('PRED'), '$VAR'('COLLECTION'), '$VAR'('INSTANCE')], [conceptuallyRelated, '$VAR'('COLLECTION'), '$VAR'('INSTANCE')]])), 'BaseKB', vStrMon).
 8897assertedTinyKB_implies( notAssertible('$VAR'('PRED')), abnormal('TheList'('$VAR'('PRED')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[genlPreds, '$VAR'('PRED'), termDependsOn]], [[afterRemoving, '$VAR'('PRED'), ['SubLQuoteFn', 'REMOVE-DEPENDENT-TERM']]]], 'BaseKB', ["?PRED"], [implies, [genlPreds, '$VAR'('PRED'), termDependsOn], [afterRemoving, '$VAR'('PRED'), ['SubLQuoteFn', 'REMOVE-DEPENDENT-TERM']]])), 'BaseKB', vStrDef).
 8898assertedTinyKB_implies( notAssertible('$VAR'('SPEC_PRED')), abnormal('TheList'('$VAR'('SPEC_PRED')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[different, disjointWith, '$VAR'('SPEC_PRED')], [genlPreds, '$VAR'('SPEC_PRED'), disjointWith]], [[afterAdding, '$VAR'('SPEC_PRED'), ['SubLQuoteFn', 'PROPAGATE-TO-DISJOINTWITH']]]], 'BaseKB', ["?SPEC-PRED"], [implies, [and, [different, disjointWith, '$VAR'('SPEC_PRED')], [genlPreds, '$VAR'('SPEC_PRED'), disjointWith]], [afterAdding, '$VAR'('SPEC_PRED'), ['SubLQuoteFn', 'PROPAGATE-TO-DISJOINTWITH']]])), 'BaseKB', vStrDef).
 8899assertedTinyKB_implies( omitArgIsa('$VAR'('RELN'), '$VAR'('N')), abnormal('TheList'('$VAR'('Q_COL'), '$VAR'('COL'), '$VAR'('RELN'), '$VAR'('N')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[['genls-SpecDenotesGenlInstances', '$VAR'('Q_COL'), '$VAR'('COL')], [argQuotedIsa, '$VAR'('RELN'), '$VAR'('N'), '$VAR'('Q_COL')]], [[argIsa, '$VAR'('RELN'), '$VAR'('N'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?Q-COL", "?COL", "?RELN", "?N"], [implies, [and, ['genls-SpecDenotesGenlInstances', '$VAR'('Q_COL'), '$VAR'('COL')], [argQuotedIsa, '$VAR'('RELN'), '$VAR'('N'), '$VAR'('Q_COL')]], [argIsa, '$VAR'('RELN'), '$VAR'('N'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrDef).
 8900assertedTinyKB_implies( operatorFormulas('$VAR'('A'), '$VAR'('B')), natFunction('$VAR'('B'), '$VAR'('A')), 'BaseKB', vStrDef).
 8901
 8902assertedTinyKB_implies( natArgument('$VAR'('NAT'), 0, '$VAR'('FUNCTION')), natFunction('$VAR'('NAT'), '$VAR'('FUNCTION')), 'BaseKB', vStrMon).
 8903assertedTinyKB_implies( knownAntecedentRule('$VAR'('ASSERTION')), highlyRelevantAssertion('$VAR'('ASSERTION')), 'UniversalVocabularyMt', vStrMon).
 8904assertedTinyKB_implies( ist('MtSpace'('$VAR'('MT')), '$VAR'('SENTENCE')), ist('$VAR'('MT'), '$VAR'('SENTENCE')), 'UniversalVocabularyMt', vStrDef).
 8905
 8906assertedTinyKB_implies( and(trueSentence('$VAR'('FORMULA')), interArgDifferent('$VAR'('FORMULAARGFN_2'), '$VAR'('ARG_1'), '$VAR'('ARG_2')), evaluate('$VAR'('FORMULAARGFN_2'), 'FormulaArgFn'(0, '$VAR'('FORMULA'))), evaluate('$VAR'('FORMULAARGFN'), 'FormulaArgFn'('$VAR'('ARG_1'), '$VAR'('FORMULA'))), evaluate('$VAR'('FORMULAARGFN_1'), 'FormulaArgFn'('$VAR'('ARG_2'), '$VAR'('FORMULA')))), different('$VAR'('FORMULAARGFN'), '$VAR'('FORMULAARGFN_1')), 'BaseKB', vStrMon).
 8907assertedTinyKB_implies( and(trueSentence('$VAR'('ANTE')), sentenceImplies('$VAR'('ANTE'), '$VAR'('CONSEQ'))), trueSentence('$VAR'('CONSEQ')), 'BaseKB', vStrMon).
 8908assertedTinyKB_implies( and(rewriteOf('$VAR'('TERM'), '$VAR'('NART1')), rewriteOf('$VAR'('TERM'), '$VAR'('NART2'))), equals('$VAR'('NART1'), '$VAR'('NART2')), 'BaseKB', vStrDef).
 8909assertedTinyKB_implies( and(rewriteOf('$VAR'('REWRITE'), '$VAR'('TERM')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('TERM'), '$VAR'('ARG3'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('REWRITE'), '$VAR'('ARG3')), 'UniversalVocabularyMt', vStrDef).
 8910assertedTinyKB_implies( and(rewriteOf('$VAR'('REWRITE'), '$VAR'('TERM')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('TERM'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('REWRITE')), 'UniversalVocabularyMt', vStrDef).
 8911
 8912assertedTinyKB_implies( and(requiredArg2Pred('$VAR'('COL_2'), '$VAR'('PRED')), 'interArgIsa2-1'('$VAR'('PRED'), '$VAR'('COL_2'), '$VAR'('COL_1'))), relationExistsAll('$VAR'('PRED'), '$VAR'('COL_1'), '$VAR'('COL_2')), 'BaseKB', vStrDef).
 8913assertedTinyKB_implies( and(relationAllExistsMax('$VAR'('REL'), '$VAR'('A'), '$VAR'('B'), '$VAR'('N')), relationAllExistsMin('$VAR'('REL'), '$VAR'('A'), '$VAR'('B'), '$VAR'('N'))), relationAllExistsCount('$VAR'('REL'), '$VAR'('A'), '$VAR'('B'), '$VAR'('N')), 'BaseKB', vStrDef).
 8914assertedTinyKB_implies( and(relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('M')), relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('N'))), numericallyEquals('$VAR'('M'), '$VAR'('N')), 'BaseKB', vStrDef).
 8915assertedTinyKB_implies( and(relationAllExistsCount('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('N')), relationAllExistsMin('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('M'))), greaterThanOrEqualTo('$VAR'('N'), '$VAR'('M')), 'BaseKB', vStrMon).
 8916assertedTinyKB_implies( and(relationAll('$VAR'('PRED'), '$VAR'('COL')), isa('$VAR'('OBJ'), '$VAR'('COL'))), holds('$VAR'('PRED'), '$VAR'('OBJ')), 'BaseKB', vStrMon).
 8917assertedTinyKB_implies( and(quotedIsa('$VAR'('SUBL_NUM'), 'SubLPositiveInteger'), denotes('$VAR'('SUBL_NUM'), '$VAR'('NUM'))), isa('$VAR'('NUM'), 'PositiveInteger'), 'LogicalTruthImplementationMt', vStrDef).
 8918assertedTinyKB_implies( and(quotedIsa('$VAR'('SUBL_NUM'), 'SubLNonNegativeInteger'), denotes('$VAR'('SUBL_NUM'), '$VAR'('NUM'))), isa('$VAR'('NUM'), 'NonNegativeInteger'), 'LogicalTruthImplementationMt', vStrDef).
 8919assertedTinyKB_implies( and(quantitySubsumes('$VAR'('SUPER'), '$VAR'('SUB')), followingValue('$VAR'('SUPER'), '$VAR'('LATER'))), followingValue('$VAR'('SUB'), '$VAR'('LATER')), 'BaseKB', vStrDef).
 8920assertedTinyKB_implies( and(quantitySubsumes('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), quantitySubsumes('$VAR'('INTERVAL2'), '$VAR'('INTERVAL1'))), numericallyEquals('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8921
 8922assertedTinyKB_implies( and(numericallyEquals('$VAR'('M'), '$VAR'('N')), relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('N'))), relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('M')), 'BaseKB', vStrMon).
 8923assertedTinyKB_implies( and(termOfUnit('$VAR'('UNITPRODUCTFN'), 'UnitProductFn'('$VAR'('PERFN'), '$VAR'('UNIT2'))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('UNIT1'), '$VAR'('UNITPRODUCTFN')), 'UniversalVocabularyMt', vStrMon).
 8924assertedTinyKB_implies( and(termOfUnit('$VAR'('PERFN_1'), 'PerFn'('$VAR'('UNIT2'), '$VAR'('UNIT3'))), termOfUnit('$VAR'('PERFN_2'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2'))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT3')))), multiplicationUnits('$VAR'('PERFN_1'), '$VAR'('PERFN_2'), '$VAR'('PERFN')), 'BaseKB', vStrDef).
 8925assertedTinyKB_implies( and(termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNITPRODUCTFN'), '$VAR'('UNIT2'))), termOfUnit('$VAR'('UNITPRODUCTFN'), 'UnitProductFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('PERFN'), '$VAR'('UNIT1')), 'UniversalVocabularyMt', vStrMon).
 8926assertedTinyKB_implies( ist('$VAR'('MT'), '$VAR'('SENTENCE')), ist('MtSpace'('$VAR'('MT')), '$VAR'('SENTENCE')), 'UniversalVocabularyMt', vStrDef).
 8927assertedTinyKB_implies( isa('$VAR'('X'), 'PositiveInteger'), greaterThanOrEqualTo('$VAR'('X'), 1), 'BaseKB', vStrDef).
 8928assertedTinyKB_implies( and(unitMultiplicationFactor('$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE'), '$VAR'('FACTOR1')), termOfUnit('$VAR'('PERFN_1'), 'PerFn'('$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE'))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO')))), unitMultiplicationFactor('$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')), 'BaseKB', vStrMon).
 8929assertedTinyKB_implies( and(unitMultiplicationFactor('$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO'), '$VAR'('FACTOR1')), termOfUnit('$VAR'('PERFN_1'), 'PerFn'('$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE'))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE')))), unitMultiplicationFactor('$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')), 'BaseKB', vStrDef).
 8930assertedTinyKB_implies( and(unitMultiplicationFactor('$VAR'('SMALL'), '$VAR'('BIG'), '$VAR'('FACTOR')), evaluate('$VAR'('TIMESFN'), 'TimesFn'('$VAR'('FACTOR'), '$VAR'('N')))), equals(holds('$VAR'('BIG'), '$VAR'('N')), holds('$VAR'('SMALL'), '$VAR'('TIMESFN'))), 'BaseKB', vStrMon).
 8931
 8932exactlyAssertedEL_with_vars(evaluationDefn, 'FunctionToArg'('$VAR'('N'), '$VAR'('PREDICATE')), 'SubLQuoteFn'('CYC-FUNCTION-TO-ARG'), 'BaseKB', vStrMon).
 8933exactlyAssertedEL_with_vars(evaluationDefn, 'FormulaArityFn', 'SubLQuoteFn'('CYC-RELATION-EXPRESSION-ARITY'), 'BaseKB', vStrMon).
 8934exactlyAssertedEL_with_vars(evaluationDefn, 'FormulaArgSetFn', 'SubLQuoteFn'('CYC-RELATION-ARG-SET'), 'BaseKB', vStrMon).
 8935exactlyAssertedEL_with_vars(evaluationDefn, 'FormulaArgListFn', 'SubLQuoteFn'('CYC-RELATION-ARGS-LIST'), 'BaseKB', vStrMon).
 8936exactlyAssertedEL_with_vars(evaluationDefn, 'FormulaArgFn', 'SubLQuoteFn'('CYC-RELATION-ARG'), 'BaseKB', vStrMon).
 8937exactlyAssertedEL_with_vars(evaluationDefn, 'EvaluateSubLFn', 'SubLQuoteFn'('CYC-EVALUATE-SUBL'), 'BaseKB', vStrMon).
 8938exactlyAssertedEL_with_vars(evaluationDefn, 'DifferenceFn', 'SubLQuoteFn'('CYC-DIFFERENCE'), 'BaseKB', vStrMon).
 8939exactlyAssertedEL_with_vars(evaluationDefn, 'DateEncodeStringFn', 'SubLQuoteFn'('CYC-DATE-ENCODE-STRING'), 'BaseKB', vStrMon).
 8940exactlyAssertedEL_with_vars(evaluationDefn, 'DateDecodeStringFn', 'SubLQuoteFn'('CYC-DATE-DECODE-STRING'), 'BaseKB', vStrMon).
 8941exactlyAssertedEL_with_vars(evaluationDefn, 'Average', 'SubLQuoteFn'('CYC-AVERAGE'), 'BaseKB', vStrMon).
 8942exactlyAssertedEL_with_vars(evaluationDefn, 'AbsoluteValueFn', 'SubLQuoteFn'('CYC-ABSOLUTE-VALUE'), 'BaseKB', vStrMon).
 8943
 8944assertedTinyKB_implies( extentCardinality('TheSetOf'('$VAR'('OBJ'), and(isa('$VAR'('OBJ'), '$VAR'('COLL_1')), ~(isa('$VAR'('OBJ'), '$VAR'('COLL_2'))))), 0), subsetOf('$VAR'('COLL_1'), '$VAR'('COLL_2')), 'BaseKB', vStrDef).
 8945assertedTinyKB_implies( extConceptOverlapsColAndReln('$VAR'('COL'), '$VAR'('RELN'), '$VAR'('SOURCE'), '$VAR'('STRING')), overlappingExternalConcept('$VAR'('RELN'), '$VAR'('SOURCE'), '$VAR'('STRING')), 'BaseKB', vStrDef).
 8946assertedTinyKB_implies( extConceptOverlapsColAndReln('$VAR'('COL'), '$VAR'('RELN'), '$VAR'('SOURCE'), '$VAR'('STRING')), overlappingExternalConcept('$VAR'('COL'), '$VAR'('SOURCE'), '$VAR'('STRING')), 'BaseKB', vStrDef).
 8947assertedTinyKB_implies( except('$VAR'('ASSERTION')), exceptWhen(except('$VAR'('ASSERTION')), '$VAR'('ASSERTION')), 'BaseKB', vStrDef).
 8948assertedTinyKB_implies( equals('$VAR'('A'), '$VAR'('B')), 'equalStrings-CaseInsensitive'('$VAR'('A'), '$VAR'('B')), 'BaseKB', vStrDef).
 8949assertedTinyKB_implies( elInverse('$VAR'('SLOT'), '$VAR'('INVERSE')), expansion('$VAR'('INVERSE'), holds('$VAR'('SLOT'), (':ARG2'), (':ARG1'))), 'BaseKB', vStrDef).
 8950
 8951assertedTinyKB_implies_InCode( genls('$VAR'('SUB'), '$VAR'('SUPER')), genls('$VAR'('SUPER'), 'Thing'), 'BaseKB', vStrMon).
 8952assertedTinyKB_implies_InCode( genls('$VAR'('SUB'), '$VAR'('SUPER')), genls('$VAR'('SUB'), 'Thing'), 'BaseKB', vStrMon).
 8953assertedTinyKB_implies_TODO( forwardNonTriggerLiteral(isa('$VAR'('TERM'), '$VAR'('INDEP_COL'))), meetsPragmaticRequirement('TheList'('$VAR'('NAT'), '$VAR'('FUNC'), '$VAR'('TERM'), '$VAR'('INDEP_COL'), '$VAR'('ARG'), '$VAR'('DEP_COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [isa, '$VAR'('TERM'), '$VAR'('INDEP_COL')], [natArgument, '$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')], [interArgResultIsa, '$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')]], [[isa, '$VAR'('NAT'), '$VAR'('DEP_COL')]]], 'BaseKB', ["?NAT", "?FUNC", "?TERM", "?INDEP-COL", "?ARG", "?DEP-COL"], [implies, [and, [natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [isa, '$VAR'('TERM'), '$VAR'('INDEP_COL')], [natArgument, '$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')], [interArgResultIsa, '$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')]], [isa, '$VAR'('NAT'), '$VAR'('DEP_COL')]])), 'BaseKB', vStrDef).
 8954assertedTinyKB_implies_TODO( forwardNonTriggerLiteral(isa('$VAR'('ARG'), '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('ARG'), '$VAR'('COL'), '$VAR'('NART'), '$VAR'('FUNC'), '$VAR'('INT')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[knownSentence, [isa, '$VAR'('ARG'), '$VAR'('COL')]], [natFunction, '$VAR'('NART'), '$VAR'('FUNC')], [resultIsaArgIsa, '$VAR'('FUNC'), '$VAR'('INT')], [natArgument, '$VAR'('NART'), '$VAR'('INT'), '$VAR'('ARG')]], [[isa, '$VAR'('NART'), '$VAR'('COL')]]], 'BaseKB', ["?ARG", "?COL", "?NART", "?FUNC", "?INT"], [implies, [and, [knownSentence, [isa, '$VAR'('ARG'), '$VAR'('COL')]], [natFunction, '$VAR'('NART'), '$VAR'('FUNC')], [resultIsaArgIsa, '$VAR'('FUNC'), '$VAR'('INT')], [natArgument, '$VAR'('NART'), '$VAR'('INT'), '$VAR'('ARG')]], [isa, '$VAR'('NART'), '$VAR'('COL')]])), 'BaseKB', vStrMon).
 8955assertedTinyKB_implies_TODO( forwardNonTriggerLiteral(arity('$VAR'('PRED'), 2)), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [[relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]]], 'BaseKB', ["?PRED", "?COL1", "?COL2"], [implies, [and, [arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]])), 'BaseKB', vStrMon).
 8956
 8957assertedTinyKB_implies( assertionUtility('$VAR'('ASSERTION'), 1), highlyRelevantAssertion('$VAR'('ASSERTION')), 'UniversalVocabularyMt', vStrDef).
 8958assertedTinyKB_implies( irrelevantAssertion('$VAR'('ASSERTION')), 'assertionUtility-1'('$VAR'('ASSERTION'), -1), 'UniversalVocabularyMt', vStrDef).
 8959assertedTinyKB_implies( 'assertionUtility-1'('$VAR'('ASSERTION'), 1), highlyRelevantAssertion('$VAR'('ASSERTION')), 'UniversalVocabularyMt', vStrDef).
 8960assertedTinyKB_implies( 'assertionUtility-1'('$VAR'('ASSERTION'), -1), irrelevantAssertion('$VAR'('ASSERTION')), 'UniversalVocabularyMt', vStrDef).
 8961assertedTinyKB_implies( integerBetween('$VAR'('LOW'), '$VAR'('MED'), '$VAR'('HIGH')), greaterThanOrEqualTo('$VAR'('MED'), '$VAR'('LOW')), 'BaseKB', vStrDef).
 8962assertedTinyKB_implies( integerBetween('$VAR'('LOW'), '$VAR'('MED'), '$VAR'('HIGH')), greaterThanOrEqualTo('$VAR'('HIGH'), '$VAR'('MED')), 'BaseKB', vStrDef).
 8963assertedTinyKB_implies( highlyRelevantAssertion('$VAR'('ASSERTION')), assertionUtility('$VAR'('ASSERTION'), 1), 'UniversalVocabularyMt', vStrDef).
 8964assertedTinyKB_implies( highlyRelevantAssertion('$VAR'('ASSERTION')), 'assertionUtility-1'('$VAR'('ASSERTION'), 1), 'UniversalVocabularyMt', vStrDef).
 8965
 8966assertedTinyKB_implies( holdsIn('$VAR'('_T1'), holdsIn('$VAR'('T2'), '$VAR'('P'))), holdsIn('$VAR'('T2'), '$VAR'('P')), 'BaseKB', vStrDef).
 8967
 8968assertedTinyKB_implies( knownSentence(relationAllInstance(quotedIsa, '$VAR'('COLL'), '$VAR'('QUOTED_COLL'))), meetsPragmaticRequirement('TheList'('$VAR'('INS'), '$VAR'('COLL'), '$VAR'('QUOTED_COLL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[isa, '$VAR'('INS'), '$VAR'('COLL')], [relationAllInstance, quotedIsa, '$VAR'('COLL'), '$VAR'('QUOTED_COLL')]], [[quotedIsa, '$VAR'('INS'), '$VAR'('QUOTED_COLL')]]], 'BookkeepingMt', ["?INS", "?COLL", "?QUOTED-COLL"], [implies, [and, [isa, '$VAR'('INS'), '$VAR'('COLL')], [relationAllInstance, quotedIsa, '$VAR'('COLL'), '$VAR'('QUOTED_COLL')]], [quotedIsa, '$VAR'('INS'), '$VAR'('QUOTED_COLL')]])), 'BookkeepingMt', vStrDef).
 8969assertedTinyKB_implies( knownSentence(interArgResultIsa('$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), meetsPragmaticRequirement('TheList'('$VAR'('NAT'), '$VAR'('FUNC'), '$VAR'('TERM'), '$VAR'('INDEP_COL'), '$VAR'('ARG'), '$VAR'('DEP_COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [isa, '$VAR'('TERM'), '$VAR'('INDEP_COL')], [natArgument, '$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')], [interArgResultIsa, '$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')]], [[isa, '$VAR'('NAT'), '$VAR'('DEP_COL')]]], 'BaseKB', ["?NAT", "?FUNC", "?TERM", "?INDEP-COL", "?ARG", "?DEP-COL"], [implies, [and, [natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [isa, '$VAR'('TERM'), '$VAR'('INDEP_COL')], [natArgument, '$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')], [interArgResultIsa, '$VAR'('FUNC'), '$VAR'('ARG'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')]], [isa, '$VAR'('NAT'), '$VAR'('DEP_COL')]])), 'BaseKB', vStrDef).
 8970assertedTinyKB_implies( knownSentence(genls('$VAR'('TERM'), '$VAR'('INDEP_COLL'))), meetsPragmaticRequirement('TheList'('$VAR'('NAT'), '$VAR'('FUNC'), '$VAR'('NUM'), '$VAR'('INDEP_COLL_NAT'), '$VAR'('TERM'), '$VAR'('INDEP_COLL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [preservesGenlsInArg, '$VAR'('FUNC'), '$VAR'('NUM')], [natFunction, '$VAR'('INDEP_COLL_NAT'), '$VAR'('FUNC')], [genls, '$VAR'('TERM'), '$VAR'('INDEP_COLL')], [natArgument, '$VAR'('NAT'), '$VAR'('NUM'), '$VAR'('TERM')], [natArgument, '$VAR'('INDEP_COLL_NAT'), '$VAR'('NUM'), '$VAR'('INDEP_COLL')]], [[genls, '$VAR'('NAT'), '$VAR'('INDEP_COLL_NAT')]]], 'UniversalVocabularyMt', ["?NAT", "?FUNC", "?NUM", "?INDEP-COLL-NAT", "?TERM", "?INDEP-COLL"], [implies, [and, [natFunction, '$VAR'('NAT'), '$VAR'('FUNC')], [preservesGenlsInArg, '$VAR'('FUNC'), '$VAR'('NUM')], [natFunction, '$VAR'('INDEP_COLL_NAT'), '$VAR'('FUNC')], [genls, '$VAR'('TERM'), '$VAR'('INDEP_COLL')], [natArgument, '$VAR'('NAT'), '$VAR'('NUM'), '$VAR'('TERM')], [natArgument, '$VAR'('INDEP_COLL_NAT'), '$VAR'('NUM'), '$VAR'('INDEP_COLL')]], [genls, '$VAR'('NAT'), '$VAR'('INDEP_COLL_NAT')]])), 'UniversalVocabularyMt', vStrDef).
 8971assertedTinyKB_implies( knownSentence(genlPreds('$VAR'('SPEC'), '$VAR'('PRED'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('SPEC')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[decontextualizedPredicate, '$VAR'('PRED')], [genlPreds, '$VAR'('SPEC'), '$VAR'('PRED')]], [[decontextualizedPredicate, '$VAR'('SPEC')]]], 'BaseKB', ["?PRED", "?SPEC"], [implies, [and, [decontextualizedPredicate, '$VAR'('PRED')], [genlPreds, '$VAR'('SPEC'), '$VAR'('PRED')]], [decontextualizedPredicate, '$VAR'('SPEC')]])), 'BaseKB', vStrMon).
 8972assertedTinyKB_implies( knownSentence(genlPreds('$VAR'('SPEC'), '$VAR'('PRED'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('MT'), '$VAR'('SPEC')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[decontextualizedPredicate, '$VAR'('PRED')], [predicateConventionMt, '$VAR'('PRED'), '$VAR'('MT')], [genlPreds, '$VAR'('SPEC'), '$VAR'('PRED')]], [[predicateConventionMt, '$VAR'('SPEC'), '$VAR'('MT')]]], 'BaseKB', ["?PRED", "?MT", "?SPEC"], [implies, [and, [decontextualizedPredicate, '$VAR'('PRED')], [predicateConventionMt, '$VAR'('PRED'), '$VAR'('MT')], [genlPreds, '$VAR'('SPEC'), '$VAR'('PRED')]], [predicateConventionMt, '$VAR'('SPEC'), '$VAR'('MT')]])), 'BaseKB', vStrDef).
 8973assertedTinyKB_implies( knownSentence(collectionIsaBackchainRequired('$VAR'('PRED'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[collectionIsaBackchainRequired, '$VAR'('PRED')]], [[collectionIsaBackchainEncouraged, '$VAR'('PRED')]]], 'UniversalVocabularyMt', ["?PRED"], [implies, [collectionIsaBackchainRequired, '$VAR'('PRED')], [collectionIsaBackchainEncouraged, '$VAR'('PRED')]])), 'UniversalVocabularyMt', vStrDef).
 8974assertedTinyKB_implies( knownSentence(collectionGenlsBackchainRequired('$VAR'('PRED'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[collectionGenlsBackchainRequired, '$VAR'('PRED')]], [[collectionGenlsBackchainEncouraged, '$VAR'('PRED')]]], 'UniversalVocabularyMt', ["?PRED"], [implies, [collectionGenlsBackchainRequired, '$VAR'('PRED')], [collectionGenlsBackchainEncouraged, '$VAR'('PRED')]])), 'UniversalVocabularyMt', vStrDef).
 8975assertedTinyKB_implies( knownSentence(collectionBackchainRequired('$VAR'('PRED'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[collectionBackchainRequired, '$VAR'('PRED')]], [[collectionBackchainEncouraged, '$VAR'('PRED')]]], 'UniversalVocabularyMt', ["?PRED"], [implies, [collectionBackchainRequired, '$VAR'('PRED')], [collectionBackchainEncouraged, '$VAR'('PRED')]])), 'UniversalVocabularyMt', vStrDef).
 8976assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 6, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 6, '$VAR'('COL')]], [[arg6SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 6, '$VAR'('COL')], [arg6SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8977assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 5, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 5, '$VAR'('COL')]], [[arg5SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 5, '$VAR'('COL')], [arg5SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8978assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 4, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 4, '$VAR'('COL')]], [[arg4SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 4, '$VAR'('COL')], [arg4SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8979assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 3, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 3, '$VAR'('COL')]], [[arg3SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 3, '$VAR'('COL')], [arg3SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8980assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 2, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 2, '$VAR'('COL')]], [[arg2SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 2, '$VAR'('COL')], [arg2SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8981assertedTinyKB_implies( knownSentence(argSometimesIsa('$VAR'('RELN'), 1, '$VAR'('COL'))), meetsPragmaticRequirement('TheList'('$VAR'('RELN'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[argSometimesIsa, '$VAR'('RELN'), 1, '$VAR'('COL')]], [[arg1SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]]], 'UniversalVocabularyMt', ["?RELN", "?COL"], [implies, [argSometimesIsa, '$VAR'('RELN'), 1, '$VAR'('COL')], [arg1SometimesIsa, '$VAR'('RELN'), '$VAR'('COL')]])), 'UniversalVocabularyMt', vStrMon).
 8982
 8983assertedTinyKB_implies( admittedSentence(isa('$VAR'('A'), '$VAR'('B'))), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[elementOf, '$VAR'('A'), '$VAR'('B')]], [[isa, '$VAR'('A'), '$VAR'('B')]]], 'BaseKB', ["?A", "?B"], [implies, [elementOf, '$VAR'('A'), '$VAR'('B')], [isa, '$VAR'('A'), '$VAR'('B')]])), 'BaseKB', vStrDef).
 8984assertedTinyKB_implies( admittedSentence(genls('$VAR'('A'), '$VAR'('B'))), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[subsetOf, '$VAR'('A'), '$VAR'('B')]], [[genls, '$VAR'('A'), '$VAR'('B')]]], 'BaseKB', ["?A", "?B"], [implies, [subsetOf, '$VAR'('A'), '$VAR'('B')], [genls, '$VAR'('A'), '$VAR'('B')]])), 'BaseKB', vStrDef).
 8985assertedTinyKB_implies( admittedSentence('equalStrings-CaseInsensitive'('$VAR'('A'), '$VAR'('B'))), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[equals, '$VAR'('A'), '$VAR'('B')]], [['equalStrings-CaseInsensitive', '$VAR'('A'), '$VAR'('B')]]], 'BaseKB', ["?A", "?B"], [implies, [equals, '$VAR'('A'), '$VAR'('B')], ['equalStrings-CaseInsensitive', '$VAR'('A'), '$VAR'('B')]])), 'BaseKB', vStrDef).
 8986assertedTinyKB_implies( admittedAllArgument('$VAR'('COL'), '$VAR'('NUM'), '$VAR'('RELN')), relationAllInstance('Kappa'('?X'('$VAR'('Y')), admittedArgument('$VAR'('X'), '$VAR'('NUM'), '$VAR'('Y'))), '$VAR'('COL'), '$VAR'('RELN')), 'UniversalVocabularyMt', vStrMon).
 8987
 8988assertedTinyKB_implies( and(negationPreds('$VAR'('GENL_PRED'), '$VAR'('NEG_PRED')), genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED'))), negationPreds('$VAR'('NEG_PRED'), '$VAR'('SPEC_PRED')), 'BaseKB', vStrMon).
 8989assertedTinyKB_implies( and(negationPreds('$VAR'('GENL_PRED'), '$VAR'('NEG_PRED')), genlInverse('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED'))), negationInverse('$VAR'('NEG_PRED'), '$VAR'('SPEC_PRED')), 'BaseKB', vStrMon).
 8990assertedTinyKB_implies( and(negationInverse('$VAR'('GENL_PRED'), '$VAR'('NEG_PRED')), genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED'))), negationInverse('$VAR'('NEG_PRED'), '$VAR'('SPEC_PRED')), 'BaseKB', vStrMon).
 8991assertedTinyKB_implies( and(negationInverse('$VAR'('GENL_PRED'), '$VAR'('NEG_PRED')), genlInverse('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED'))), negationPreds('$VAR'('NEG_PRED'), '$VAR'('SPEC_PRED')), 'BaseKB', vStrMon).
 8992assertedTinyKB_implies( and(minQuantValue('$VAR'('VALUE1'), '$VAR'('VALUE1MIN')), maxQuantValue('$VAR'('VALUE2'), '$VAR'('VALUE2MAX')), greaterThan('$VAR'('VALUE1MIN'), '$VAR'('VALUE2MAX'))), greaterThan('$VAR'('VALUE1'), '$VAR'('VALUE2')), 'BaseKB', vStrDef).
 8993assertedTinyKB_implies( and(minQuantValue('$VAR'('MORE'), '$VAR'('MOREMIN')), greaterThan('$VAR'('MORE'), '$VAR'('LESS')), maxQuantValue('$VAR'('LESS'), '$VAR'('LESSMAX'))), greaterThan('$VAR'('MOREMIN'), '$VAR'('LESSMAX')), 'BaseKB', vStrDef).
 8994assertedTinyKB_implies( and(minQuantValue('$VAR'('INTERVAL1'), '$VAR'('VALUE')), maxQuantValue('$VAR'('INTERVAL2'), '$VAR'('VALUE'))), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8995assertedTinyKB_implies( and(minQuantValue('$VAR'('INTERVAL1'), '$VAR'('MIN')), minQuantValue('$VAR'('INTERVAL2'), '$VAR'('MIN'))), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8996assertedTinyKB_implies( and(maxQuantValue('$VAR'('INTERVAL1'), '$VAR'('MAX1')), minQuantValue('$VAR'('INTERVAL1'), '$VAR'('MIN1')), minQuantValue('$VAR'('INTERVAL2'), '$VAR'('MIN2')), maxQuantValue('$VAR'('INTERVAL2'), '$VAR'('MAX2')), greaterThanOrEqualTo('$VAR'('MAX1'), '$VAR'('MAX2')), greaterThanOrEqualTo('$VAR'('MIN2'), '$VAR'('MIN1'))), quantitySubsumes('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8997assertedTinyKB_implies( and(maxQuantValue('$VAR'('INTERVAL1'), '$VAR'('MAX1')), minQuantValue('$VAR'('INTERVAL1'), '$VAR'('MIN1')), minQuantValue('$VAR'('INTERVAL2'), '$VAR'('MIN2')), greaterThanOrEqualTo('$VAR'('MIN2'), '$VAR'('MIN1')), greaterThanOrEqualTo('$VAR'('MAX1'), '$VAR'('MIN2'))), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8998assertedTinyKB_implies( and(maxQuantValue('$VAR'('INTERVAL1'), '$VAR'('MAX1')), minQuantValue('$VAR'('INTERVAL1'), '$VAR'('MIN1')), maxQuantValue('$VAR'('INTERVAL2'), '$VAR'('MAX2')), greaterThanOrEqualTo('$VAR'('MAX2'), '$VAR'('MIN1')), greaterThanOrEqualTo('$VAR'('MAX1'), '$VAR'('MAX2'))), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 8999assertedTinyKB_implies( and(maxQuantValue('$VAR'('INTERVAL1'), '$VAR'('MAX')), maxQuantValue('$VAR'('INTERVAL2'), '$VAR'('MAX'))), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 9000assertedTinyKB_implies( and(maxQuantValue('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('VAL'))), minQuantValue('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('VAL')))), equals('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('VAL'))), 'BaseKB', vStrMon).
 9001assertedTinyKB_implies( and(ist('$VAR'('MT'), not(numericallyEquals('$VAR'('M'), '$VAR'('N')))), ist('$VAR'('MT'), relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('N')))), ist('$VAR'('MT'), not(relationAllExistsCount('$VAR'('REL'), '$VAR'('COL1'), '$VAR'('COL2'), '$VAR'('M')))), 'UniversalVocabularyMt', vStrDef).
 9002assertedTinyKB_implies( and(isa('$VAR'('X'), '$VAR'('COL1')), trueSentence(forAll('$VAR'('Y'), or(isa('$VAR'('Y'), '$VAR'('COL2')), ~(isa('$VAR'('Y'), '$VAR'('COL1'))))))), isa('$VAR'('X'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9003assertedTinyKB_implies( and(isa('$VAR'('UNITPRODUCTFN'), 'UnitOfMeasure'), isa('$VAR'('PERFN'), 'UnitOfMeasure'), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2'))), termOfUnit('$VAR'('UNITPRODUCTFN'), 'UnitProductFn'('$VAR'('PERFN'), '$VAR'('UNIT2')))), equals('$VAR'('UNIT1'), '$VAR'('UNITPRODUCTFN')), 'UniversalVocabularyMt', vStrMon).
 9004assertedTinyKB_implies( and(isa('$VAR'('UNIT1'), 'UnitOfMeasure'), isa('$VAR'('UNIT2'), 'UnitOfMeasure'), evaluate('$VAR'('TIMESFN'), 'TimesFn'(holds('$VAR'('UNIT1'), '$VAR'('NUM2')), holds('$VAR'('UNIT2'), '$VAR'('NUM1')))), evaluate('$VAR'('TIMESFN_1'), 'TimesFn'(holds('$VAR'('UNIT1'), '$VAR'('NUM1')), holds('$VAR'('UNIT2'), '$VAR'('NUM2'))))), equals('$VAR'('TIMESFN'), '$VAR'('TIMESFN_1')), 'BaseKB', vStrMon).
 9005assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), quantityIntersects(holds('$VAR'('UNIT'), '$VAR'('NUM1A'), '$VAR'('NUM1B')), holds('$VAR'('UNIT'), '$VAR'('NUM2A'), '$VAR'('NUM2B')))), quantityIntersects('Unity'('$VAR'('NUM1A'), '$VAR'('NUM1B')), 'Unity'('$VAR'('NUM2A'), '$VAR'('NUM2B'))), 'BaseKB', vStrDef).
 9006assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), quantityIntersects(holds('$VAR'('UNIT'), '$VAR'('NUM1')), holds('$VAR'('UNIT'), '$VAR'('NUM2')))), quantityIntersects('$VAR'('NUM1'), '$VAR'('NUM2')), 'BaseKB', vStrDef).
 9007assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), isa(holds('$VAR'('UNIT'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT'), '$VAR'('N')), 'ScalarIntegralValue'), evaluate('$VAR'('TIMESFN'), 'TimesFn'(holds('$VAR'('UNIT'), '$VAR'('M')), holds('$VAR'('UNIT'), '$VAR'('N'))))), isa('$VAR'('TIMESFN'), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9008assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), isa(holds('$VAR'('UNIT'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT'), '$VAR'('N')), 'ScalarIntegralValue'), evaluate('$VAR'('PLUSFN'), 'PlusFn'(holds('$VAR'('UNIT'), '$VAR'('M')), holds('$VAR'('UNIT'), '$VAR'('N'))))), isa('$VAR'('PLUSFN'), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9009assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), isa(holds('$VAR'('UNIT'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT'), '$VAR'('N')), 'ScalarIntegralValue'), evaluate('$VAR'('DIFFERENCEFN'), 'DifferenceFn'(holds('$VAR'('UNIT'), '$VAR'('M')), holds('$VAR'('UNIT'), '$VAR'('N'))))), isa('$VAR'('DIFFERENCEFN'), 'ScalarIntegralValue'), 'BaseKB', vStrDef).
 9010assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), greaterThan(holds('$VAR'('UNIT'), '$VAR'('NUM1A'), '$VAR'('NUM1B')), holds('$VAR'('UNIT'), '$VAR'('NUM2A'), '$VAR'('NUM2B')))), greaterThan('Unity'('$VAR'('NUM1A'), '$VAR'('NUM1B')), 'Unity'('$VAR'('NUM2A'), '$VAR'('NUM2B'))), 'BaseKB', vStrDef).
 9011assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), greaterThan(holds('$VAR'('UNIT'), '$VAR'('NUM1')), holds('$VAR'('UNIT'), '$VAR'('NUM2')))), greaterThan('$VAR'('NUM1'), '$VAR'('NUM2')), 'BaseKB', vStrDef).
 9012assertedTinyKB_implies( and(isa('$VAR'('UNIT'), 'UnitOfMeasure'), equals('$VAR'('QUANT'), holds('$VAR'('UNIT'), '$VAR'('NUM')))), equals('$VAR'('QUANT'), holds('$VAR'('UNIT'), '$VAR'('NUM'), '$VAR'('NUM'))), 'BaseKB', vStrDef).
 9013assertedTinyKB_implies( and(isa('$VAR'('THING'), '$VAR'('UNIVCOL')), relationAllExists('$VAR'('PRED'), '$VAR'('UNIVCOL'), '$VAR'('EXISTCOL'))), trueSentence(thereExists('$VAR'('OTHER'), and(isa('$VAR'('OTHER'), '$VAR'('EXISTCOL')), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('OTHER'))))), 'BaseKB', vStrDef).
 9014assertedTinyKB_implies( and(isa('$VAR'('THING'), '$VAR'('COL1')), coExtensional('$VAR'('COL1'), '$VAR'('COL2'))), isa('$VAR'('THING'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9015assertedTinyKB_implies( and(isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), relationExistsAll('$VAR'('PRED'), '$VAR'('DEP_COL'), '$VAR'('INDEP_COL'))), isa('RelationExistsAllFn'('$VAR'('TERM'), '$VAR'('PRED'), '$VAR'('DEP_COL'), '$VAR'('INDEP_COL')), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 9016assertedTinyKB_implies( and(isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), relationExistsAll('$VAR'('PRED'), '$VAR'('DEP_COL'), '$VAR'('INDEP_COL'))), holds('$VAR'('PRED'), 'RelationExistsAllFn'('$VAR'('TERM'), '$VAR'('PRED'), '$VAR'('DEP_COL'), '$VAR'('INDEP_COL')), '$VAR'('TERM')), 'BaseKB', vStrMon).
 9017assertedTinyKB_implies( and(isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), relationAllExists('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), isa('RelationAllExistsFn'('$VAR'('TERM'), '$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), '$VAR'('DEP_COL')), 'BaseKB', vStrMon).
 9018assertedTinyKB_implies( and(isa('$VAR'('TERM'), '$VAR'('INDEP_COL')), relationAllExists('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), holds('$VAR'('PRED'), '$VAR'('TERM'), 'RelationAllExistsFn'('$VAR'('TERM'), '$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), 'BaseKB', vStrMon).
 9019assertedTinyKB_implies( and(isa('$VAR'('SPEC_PRED'), 'ReflexiveBinaryPredicate'), genlInverse('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), different('$VAR'('GENL_PRED'), '$VAR'('SPEC_PRED')), arg1Isa('$VAR'('SPEC_PRED'), '$VAR'('ARG1ISA')), arg2Isa('$VAR'('GENL_PRED'), '$VAR'('ARG1ISA')), arg2Isa('$VAR'('SPEC_PRED'), '$VAR'('ARG2ISA')), arg1Isa('$VAR'('GENL_PRED'), '$VAR'('ARG2ISA'))), isa('$VAR'('GENL_PRED'), 'ReflexiveBinaryPredicate'), 'BaseKB', vStrMon).
 9020assertedTinyKB_implies( and(isa('$VAR'('SMALLER_UNIT'), 'UnitOfMeasure'), isa('$VAR'('LARGER_UNIT'), 'UnitOfMeasure'), unitMultiplicationFactor('$VAR'('SMALLER_UNIT'), '$VAR'('LARGER_UNIT'), '$VAR'('N')), evaluate('$VAR'('TIMESFN'), 'TimesFn'('$VAR'('M'), holds('$VAR'('SMALLER_UNIT'), '$VAR'('N'))))), equals('$VAR'('TIMESFN'), holds('$VAR'('LARGER_UNIT'), '$VAR'('M'))), 'BaseKB', vStrDef).
 9021assertedTinyKB_implies( and(isa('$VAR'('SMALLER_UNIT'), 'UnitOfMeasure'), isa('$VAR'('LARGER_UNIT'), 'UnitOfMeasure'), unitMultiplicationFactor('$VAR'('SMALLER_UNIT'), '$VAR'('LARGER_UNIT'), '$VAR'('N'))), equals(holds('$VAR'('LARGER_UNIT'), 1), holds('$VAR'('SMALLER_UNIT'), '$VAR'('N'))), 'UniversalVocabularyMt', vStrDef).
 9022assertedTinyKB_implies( and(isa('$VAR'('SLOT'), 'IrreflexiveBinaryPredicate'), isa('$VAR'('SLOT'), 'TransitiveBinaryPredicate')), isa('$VAR'('SLOT'), 'AsymmetricBinaryPredicate'), 'BaseKB', vStrDef).
 9023assertedTinyKB_implies( and(isa('$VAR'('SLOT'), 'AntiSymmetricBinaryPredicate'), isa('$VAR'('SLOT'), 'IrreflexiveBinaryPredicate')), isa('$VAR'('SLOT'), 'AsymmetricBinaryPredicate'), 'BaseKB', vStrDef).
 9024assertedTinyKB_implies( and(isa('$VAR'('SIBDIS_COL'), 'SiblingDisjointCollectionType'), isa('$VAR'('COL1'), '$VAR'('SIBDIS_COL')), isa('$VAR'('COL2'), '$VAR'('SIBDIS_COL'))), or(genls('$VAR'('COL1'), '$VAR'('COL2')), disjointWith('$VAR'('COL1'), '$VAR'('COL2')), siblingDisjointExceptions('$VAR'('COL1'), '$VAR'('COL2')), genls('$VAR'('COL2'), '$VAR'('COL1'))), 'BaseKB', vStrDef).
 9025assertedTinyKB_implies( and(isa('$VAR'('RELN'), 'MicrotheoryDesignatingRelation'), sentenceDesignationArgnum('$VAR'('RELN'), '$VAR'('NUM'))), argIsa('$VAR'('RELN'), '$VAR'('NUM'), 'CycLSentence-Assertible'), 'BaseKB', vStrDef).
 9026assertedTinyKB_implies( and(isa('$VAR'('RELN'), 'MicrotheoryDesignatingRelation'), microtheoryDesignationArgnum('$VAR'('RELN'), '$VAR'('NUM'))), argIsa('$VAR'('RELN'), '$VAR'('NUM'), 'Microtheory'), 'BaseKB', vStrDef).
 9027assertedTinyKB_implies( and(isa('$VAR'('RELN'), 'MicrotheoryDesignatingRelation'), isa('$VAR'('RELN'), 'VariableArityRelation'), arityMin('$VAR'('RELN'), '$VAR'('ARITY_MIN'))), greaterThanOrEqualTo('$VAR'('ARITY_MIN'), 2), 'BaseKB', vStrDef).
 9028assertedTinyKB_implies( and(isa('$VAR'('RELN'), 'FixedArityRelation'), isa('$VAR'('RELN'), 'MicrotheoryDesignatingRelation'), arity('$VAR'('RELN'), '$VAR'('ARITY'))), greaterThanOrEqualTo('$VAR'('ARITY'), 2), 'BaseKB', vStrDef).
 9029assertedTinyKB_implies( and(isa('$VAR'('RELN'), 'CommutativeRelation'), arity('$VAR'('RELN'), '$VAR'('ARITY')), integerBetween(0, '$VAR'('M'), '$VAR'('ARITY')), different('$VAR'('M'), '$VAR'('N')), integerBetween(0, '$VAR'('N'), '$VAR'('ARITY'))), commutativeInArgs('$VAR'('RELN'), '$VAR'('M'), '$VAR'('N')), 'BaseKB', vStrMon).
 9030assertedTinyKB_implies( and(isa('$VAR'('REL'), 'TransitiveBinaryPredicate'), relationExistsMaxAll('$VAR'('REL'), '$VAR'('TYPE2'), '$VAR'('TYPE3'), 1), relationAllExistsCount('$VAR'('REL'), '$VAR'('TYPE1'), '$VAR'('TYPE2'), '$VAR'('X')), relationAllExistsCount('$VAR'('REL'), '$VAR'('TYPE2'), '$VAR'('TYPE3'), '$VAR'('Y')), evaluate('$VAR'('TIMESFN'), 'TimesFn'('$VAR'('X'), '$VAR'('Y')))), relationAllExistsMin('$VAR'('REL'), '$VAR'('TYPE1'), '$VAR'('TYPE3'), '$VAR'('TIMESFN')), 'BaseKB', vStrDef).
 9031assertedTinyKB_implies( and(isa('$VAR'('REL'), 'PartiallyCommutativeRelation'), arity('$VAR'('REL'), '$VAR'('N'))), greaterThanOrEqualTo('$VAR'('N'), 3), 'BaseKB', vStrDef).
 9032assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), relationExistsAll('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), relationExistsAll('$VAR'('PRED'), '$VAR'('COL2'), '$VAR'('COL3'))), relationExistsAll('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL3')), 'BaseKB', vStrMon).
 9033assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), relationAllExists('$VAR'('PRED'), '$VAR'('COL2'), '$VAR'('COL3'))), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL3')), 'BaseKB', vStrDef).
 9034assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), holdsIn('$VAR'('TIME'), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), holdsIn('$VAR'('TIME'), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG3')))), holdsIn('$VAR'('TIME'), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG3'))), 'BaseKB', vStrDef).
 9035assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('X'), '$VAR'('Y')), holds('$VAR'('PRED'), '$VAR'('Y'), '$VAR'('Z'))), holds('$VAR'('PRED'), '$VAR'('X'), '$VAR'('Z')), 'BaseKB', vStrDef).
 9036assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TernaryPredicate'), commutativeInArgs('$VAR'('PRED'), 2, 3), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG3'), '$VAR'('ARG2')), 'BaseKB', vStrDef).
 9037assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TernaryPredicate'), commutativeInArgs('$VAR'('PRED'), 1, 3), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'))), holds('$VAR'('PRED'), '$VAR'('ARG3'), '$VAR'('ARG2'), '$VAR'('ARG1')), 'BaseKB', vStrDef).
 9038assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'TernaryPredicate'), commutativeInArgs('$VAR'('PRED'), 1, 2), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'))), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG1'), '$VAR'('ARG3')), 'BaseKB', vStrDef).
 9039assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG1')), 'BaseKB', vStrDef).
 9040assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG_1'), '$VAR'('ARG_2'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG_2'), '$VAR'('ARG_1')), 'BaseKB', vStrDef).
 9041assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), 'interArgIsa2-1'('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('COL'))), 'interArgIsa1-2'('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 9042assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), 'interArgIsa1-2'('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('COL'))), 'interArgIsa2-1'('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 9043assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'ReflexiveBinaryPredicate'), arg1Isa('$VAR'('PRED'), '$VAR'('CONSTRAINT1')), isa('$VAR'('OBJ1'), '$VAR'('CONSTRAINT1')), equals('$VAR'('OBJ1'), '$VAR'('OBJ2'))), holds('$VAR'('PRED'), '$VAR'('OBJ1'), '$VAR'('OBJ2')), 'BaseKB', vStrMon).
 9044assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'ReflexiveBinaryPredicate'), admittedArgument('$VAR'('THING'), 1, '$VAR'('PRED')), admittedArgument('$VAR'('THING'), 2, '$VAR'('PRED')), equals('$VAR'('SAMETHING'), '$VAR'('THING'))), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('SAMETHING')), 'BaseKB', vStrMon).
 9045assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'ReflexiveBinaryPredicate'), admittedArgument('$VAR'('OBJ'), 1, '$VAR'('PRED')), admittedArgument('$VAR'('OBJ'), 2, '$VAR'('PRED'))), holds('$VAR'('PRED'), '$VAR'('OBJ'), '$VAR'('OBJ')), 'BaseKB', vStrMon).
 9046assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 3, 4), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG4'), '$VAR'('ARG3')), 'BaseKB', vStrDef).
 9047assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 2, 4), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG4'), '$VAR'('ARG3'), '$VAR'('ARG2')), 'BaseKB', vStrDef).
 9048assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 2, 3), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG3'), '$VAR'('ARG2'), '$VAR'('ARG4')), 'BaseKB', vStrDef).
 9049assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 1, 4), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG4'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG1')), 'BaseKB', vStrDef).
 9050assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 1, 3), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG3'), '$VAR'('ARG2'), '$VAR'('ARG1'), '$VAR'('ARG4')), 'BaseKB', vStrDef).
 9051assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'QuaternaryPredicate'), commutativeInArgs('$VAR'('PRED'), 1, 2), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG1'), '$VAR'('ARG3'), '$VAR'('ARG4')), 'BaseKB', vStrDef).
 9052assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'IrreflexiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('OBJ1'), '$VAR'('OBJ2'))), different('$VAR'('OBJ1'), '$VAR'('OBJ2')), 'BaseKB', vStrDef).
 9053assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'FixedArityRelation'), arity('$VAR'('PRED'), '$VAR'('ARITY')), genlPreds('$VAR'('SPECPRED'), '$VAR'('PRED'))), arity('$VAR'('SPECPRED'), '$VAR'('ARITY')), 'BaseKB', vStrDef).
 9054assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'BinaryPredicate'), isa('$VAR'('PRED'), 'CommutativeRelation')), isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), 'BaseKB', vStrMon).
 9055assertedTinyKB_implies( and(isa('$VAR'('PRED'), 'BinaryPredicate'), arg2Isa('$VAR'('PRED'), '$VAR'('COL2')), requiredArg1Pred('$VAR'('COL1'), '$VAR'('PRED'))), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9056assertedTinyKB_implies( and(isa('$VAR'('POINT1'), 'ScalarPointValue'), minQuantValue('$VAR'('POINT1'), '$VAR'('POINT2'))), equals('$VAR'('POINT1'), '$VAR'('POINT2')), 'BaseKB', vStrMon).
 9057assertedTinyKB_implies( and(isa('$VAR'('POINT1'), 'ScalarPointValue'), maxQuantValue('$VAR'('POINT1'), '$VAR'('POINT2'))), equals('$VAR'('POINT1'), '$VAR'('POINT2')), 'BaseKB', vStrMon).
 9058assertedTinyKB_implies( and(isa('$VAR'('OBJECT2'), '$VAR'('TYPE')), holds('$VAR'('RELATION'), '$VAR'('OBJECT1'), '$VAR'('OBJECT2'))), relationInstanceExists('$VAR'('RELATION'), '$VAR'('OBJECT1'), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9059assertedTinyKB_implies( and(isa('$VAR'('OBJECT1'), '$VAR'('TYPE')), holds('$VAR'('RELATION'), '$VAR'('OBJECT1'), '$VAR'('OBJECT2'))), relationExistsInstance('$VAR'('RELATION'), '$VAR'('TYPE'), '$VAR'('OBJECT2')), 'BaseKB', vStrDef).
 9060assertedTinyKB_implies( and(isa('$VAR'('OBJ_1'), '$VAR'('COMMON_NEAR')), isa('$VAR'('OBJ_2'), '$VAR'('COMMON_NEAR'))), or(nearestCommonIsa('$VAR'('OBJ_1'), '$VAR'('OBJ_2'), '$VAR'('COMMON_NEAR')), elementOf('$VAR'('COMMON_NEAR'), 'TheSetOf'('$VAR'('COMMON_FARTHER'), thereExists('$VAR'('COMMON_FAR'), and(isa('$VAR'('OBJ_1'), '$VAR'('COMMON_FAR')), isa('$VAR'('OBJ_2'), '$VAR'('COMMON_FAR')), genls('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER')), different('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER'))))))), 'BaseKB', vStrDef).
 9061assertedTinyKB_implies( and(isa('$VAR'('OBJ'), '$VAR'('SUBSET')), genls('$VAR'('SUBSET'), '$VAR'('SUPERSET'))), isa('$VAR'('OBJ'), '$VAR'('SUPERSET')), 'BaseKB', vStrMon).
 9062assertedTinyKB_implies( and(isa('$VAR'('OBJ'), '$VAR'('COL_2')), relationExistsAll('$VAR'('PRED'), '$VAR'('COL_1'), '$VAR'('COL_2'))), relationExistsInstance('$VAR'('PRED'), '$VAR'('COL_1'), '$VAR'('OBJ')), 'BaseKB', vStrMon).
 9063assertedTinyKB_implies( and(isa('$VAR'('OBJ'), '$VAR'('COL_1')), relationAllExists('$VAR'('PRED'), '$VAR'('COL_1'), '$VAR'('COL_2'))), relationInstanceExists('$VAR'('PRED'), '$VAR'('OBJ'), '$VAR'('COL_2')), 'BaseKB', vStrMon).
 9064assertedTinyKB_implies( and(isa('$VAR'('OBJ'), '$VAR'('COL')), conceptuallyRelated('$VAR'('COL'), '$VAR'('REL_OBJ'))), conceptuallyRelated('$VAR'('OBJ'), '$VAR'('REL_OBJ')), 'BaseKB', vStrDef).
 9065assertedTinyKB_implies( and(isa('$VAR'('NUM'), 'Integer'), isa(holds('$VAR'('UNIT1'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT2'), '$VAR'('N')), 'ScalarIntegralValue'), unitMultiplicationFactor('$VAR'('UNIT1'), '$VAR'('UNIT2'), '$VAR'('NUM')), evaluate('$VAR'('TIMESFN'), 'TimesFn'(holds('$VAR'('UNIT1'), '$VAR'('M')), holds('$VAR'('UNIT2'), '$VAR'('N'))))), isa('$VAR'('TIMESFN'), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9066assertedTinyKB_implies( and(isa('$VAR'('NUM'), 'Integer'), isa(holds('$VAR'('UNIT1'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT2'), '$VAR'('N')), 'ScalarIntegralValue'), unitMultiplicationFactor('$VAR'('UNIT1'), '$VAR'('UNIT2'), '$VAR'('NUM')), evaluate('$VAR'('PLUSFN'), 'PlusFn'(holds('$VAR'('UNIT1'), '$VAR'('M')), holds('$VAR'('UNIT2'), '$VAR'('N'))))), isa('$VAR'('PLUSFN'), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9067assertedTinyKB_implies( and(isa('$VAR'('NUM'), 'Integer'), isa(holds('$VAR'('UNIT1'), '$VAR'('M')), 'ScalarIntegralValue'), isa(holds('$VAR'('UNIT2'), '$VAR'('N')), 'ScalarIntegralValue'), unitMultiplicationFactor('$VAR'('UNIT1'), '$VAR'('UNIT2'), '$VAR'('NUM')), evaluate('$VAR'('DIFFERENCEFN'), 'DifferenceFn'(holds('$VAR'('UNIT1'), '$VAR'('M')), holds('$VAR'('UNIT2'), '$VAR'('N'))))), isa('$VAR'('DIFFERENCEFN'), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9068assertedTinyKB_implies( and(isa('$VAR'('N'), 'PositiveInteger'), greaterThanOrEqualTo('$VAR'('N'), '$VAR'('ARGNUM')), greaterThanOrEqualTo('$VAR'('ARITY'), '$VAR'('N')), arity('$VAR'('RELN'), '$VAR'('ARITY')), canonicalizerDirectiveForArgAndRest('$VAR'('RELN'), '$VAR'('ARGNUM'), '$VAR'('DIRECTIVE'))), canonicalizerDirectiveForArg('$VAR'('RELN'), '$VAR'('N'), '$VAR'('DIRECTIVE')), 'CoreCycLImplementationMt', vStrMon).
 9069assertedTinyKB_implies( and(isa('$VAR'('N'), 'PositiveInteger'), greaterThanOrEqualTo('$VAR'('ARITY'), '$VAR'('N')), arity('$VAR'('RELN'), '$VAR'('ARITY')), canonicalizerDirectiveForAllArgs('$VAR'('RELN'), '$VAR'('DIRECTIVE'))), canonicalizerDirectiveForArg('$VAR'('RELN'), '$VAR'('N'), '$VAR'('DIRECTIVE')), 'CoreCycLImplementationMt', vStrMon).
 9070assertedTinyKB_implies( and(isa('$VAR'('M'), 'PositiveInteger'), isa('$VAR'('N'), 'PositiveInteger'), different('$VAR'('M'), '$VAR'('N'), 1)), interArgDifferent(commutativeInArgs, '$VAR'('M'), '$VAR'('N')), 'UniversalVocabularyMt', vStrMon).
 9071assertedTinyKB_implies( and(isa('$VAR'('LOW'), 'ScalarPointValue'), isa('$VAR'('UNIT'), 'UnitOfMeasure')), minQuantValue(holds('$VAR'('UNIT'), '$VAR'('LOW'), '$VAR'('HIGH')), holds('$VAR'('UNIT'), '$VAR'('LOW'))), 'BaseKB', vStrDef).
 9072assertedTinyKB_implies( and(isa('$VAR'('INTERVAL1'), 'ScalarPointValue'), isa('$VAR'('INTERVAL2'), 'ScalarPointValue'), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2'))), numericallyEquals('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 9073assertedTinyKB_implies( and(isa('$VAR'('INTERVAL1'), 'ScalarInterval'), isa('$VAR'('INTERVAL2'), 'ScalarInterval'), equals('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2'))), numericallyEquals('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), 'BaseKB', vStrDef).
 9074assertedTinyKB_implies( and(isa('$VAR'('INT'), 'Integer'), isa('$VAR'('UNIT'), 'UnitOfMeasure')), isa(holds('$VAR'('UNIT'), '$VAR'('INT')), 'ScalarIntegralValue'), 'BaseKB', vStrMon).
 9075assertedTinyKB_implies( and(isa('$VAR'('INST_UNIV'), '$VAR'('UNIV_COL')), relationAllExistsCount('$VAR'('REL'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), '$VAR'('NUM'))), trueSentence(thereExistExactly('$VAR'('NUM'), '$VAR'('INST_EXIST'), and(isa('$VAR'('INST_EXIST'), '$VAR'('EXIST_COL')), holds('$VAR'('REL'), '$VAR'('INST_UNIV'), '$VAR'('INST_EXIST'))))), 'BaseKB', vStrDef).
 9076assertedTinyKB_implies( and(isa('$VAR'('INST'), '$VAR'('COL2')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('INST'))), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9077assertedTinyKB_implies( and(isa('$VAR'('INST'), '$VAR'('COL')), relationInstanceAll('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COL'))), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('INST')), 'BaseKB', vStrDef).
 9078assertedTinyKB_implies( and(isa('$VAR'('INST'), '$VAR'('COL')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING'))), trueSentence(holds('$VAR'('PRED'), '$VAR'('INST'), '$VAR'('THING'))), 'BaseKB', vStrDef).
 9079assertedTinyKB_implies( and(isa('$VAR'('INST'), '$VAR'('COL')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING'))), holds('$VAR'('PRED'), '$VAR'('INST'), '$VAR'('THING')), 'BaseKB', vStrDef).
 9080assertedTinyKB_implies( and(isa('$VAR'('INST'), '$VAR'('COL')), admittedAllArgument('$VAR'('COL'), '$VAR'('NUM'), '$VAR'('RELN'))), admittedArgument('$VAR'('INST'), '$VAR'('NUM'), '$VAR'('RELN')), 'UniversalVocabularyMt', vStrMon).
 9081assertedTinyKB_implies( and(isa('$VAR'('INS1'), tPred), isa('$VAR'('INS2'), 'SymmetricBinaryPredicate'), isa('$VAR'('INS3'), 'PositiveInteger'), transitiveViaArgInverse('$VAR'('INS1'), '$VAR'('INS2'), '$VAR'('INS3'))), transitiveViaArg('$VAR'('INS1'), '$VAR'('INS2'), '$VAR'('INS3')), 'BaseKB', vStrDef).
 9082assertedTinyKB_implies( and(isa('$VAR'('INS1'), tPred), isa('$VAR'('INS2'), 'SymmetricBinaryPredicate'), isa('$VAR'('INS3'), 'PositiveInteger'), transitiveViaArg('$VAR'('INS1'), '$VAR'('INS2'), '$VAR'('INS3'))), transitiveViaArgInverse('$VAR'('INS1'), '$VAR'('INS2'), '$VAR'('INS3')), 'BaseKB', vStrDef).
 9083assertedTinyKB_implies( and(isa('$VAR'('INS'), '$VAR'('SPEC')), genls('$VAR'('SPEC'), '$VAR'('GENL'))), isa('$VAR'('INS'), '$VAR'('GENL')), 'LogicalTruthMt', vStrMon).
 9084assertedTinyKB_implies( and(isa('$VAR'('INS'), '$VAR'('COLL')), relationAllInstance(quotedIsa, '$VAR'('COLL'), '$VAR'('QUOTED_COLL'))), quotedIsa('$VAR'('INS'), '$VAR'('QUOTED_COLL')), 'BookkeepingMt', vStrDef).
 9085assertedTinyKB_implies( and(isa('$VAR'('INS'), '$VAR'('COL')), trueSentence(holds('$VAR'('PRED'), '$VAR'('INS'), '$VAR'('VALUE')))), relationExistsInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('VALUE')), 'BaseKB', vStrDef).
 9086assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), holds('$VAR'('PRED'), '$VAR'('DEP_INS'), '$VAR'('INDEP_INS')), 'interArgIsa2-1'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9087assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa5-4'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('DEP_INS'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9088assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa5-3'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_4'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9089assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa5-2'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_3'), '$VAR'('ANY_ARG_4'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9090assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa5-1'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('ANY_ARG_4'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9091assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa4-5'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('INDEP_INS'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9092assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa4-3'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('DEP_INS'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9093assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa4-2'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_3'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9094assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa4-1'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9095assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa3-5'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('INDEP_INS'), '$VAR'('ANY_ARG_4'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9096assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa3-4'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('ANY_ARG_2'), '$VAR'('INDEP_INS'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9097assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa3-2'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('DEP_INS'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9098assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa3-1'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('DEP_INS'), '$VAR'('ANY_ARG_2'), '$VAR'('INDEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9099assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa2-5'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('INDEP_INS'), '$VAR'('ANY_ARG_3'), '$VAR'('ANY_ARG_4'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9100assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa2-4'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('INDEP_INS'), '$VAR'('ANY_ARG_3'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9101assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa2-3'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('ANY_ARG_1'), '$VAR'('INDEP_INS'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9102assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa1-5'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('INDEP_INS'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('ANY_ARG_4'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9103assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa1-4'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), holds('$VAR'('PRED'), '$VAR'('INDEP_INS'), '$VAR'('ANY_ARG_2'), '$VAR'('ANY_ARG_3'), '$VAR'('DEP_INS'))), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9104assertedTinyKB_implies( and(arityMax('$VAR'('RELN'), '$VAR'('MAX')), arityMin('$VAR'('RELN'), '$VAR'('MIN'))), greaterThanOrEqualTo('$VAR'('MAX'), '$VAR'('MIN')), 'BaseKB', vStrMon).
 9105assertedTinyKB_implies( and(arity('$VAR'('RELN'), 5), isa('$VAR'('RELN'), 'CommutativeRelation')), commutativeInArgs('$VAR'('RELN'), 1, 2, 3, 4, 5), 'BaseKB', vStrMon).
 9106assertedTinyKB_implies( and(arity('$VAR'('RELN'), 4), isa('$VAR'('RELN'), 'CommutativeRelation')), commutativeInArgs('$VAR'('RELN'), 1, 2, 3, 4), 'BaseKB', vStrMon).
 9107assertedTinyKB_implies( and(arity('$VAR'('RELN'), 3), isa('$VAR'('RELN'), 'CommutativeRelation')), commutativeInArgs('$VAR'('RELN'), 1, 2, 3), 'BaseKB', vStrMon).
 9108assertedTinyKB_implies( and(arity('$VAR'('RELN'), 2), isa('$VAR'('RELN'), 'CommutativeRelation')), commutativeInArgs('$VAR'('RELN'), 1, 2), 'BaseKB', vStrMon).
 9109
 9110assertedTinyKB_implies( and(arity('$VAR'('PRED1'), '$VAR'('ARITY')), arity('$VAR'('PRED2'), '$VAR'('ARITY')), disjointWith('$VAR'('TYPE1'), '$VAR'('TYPE2')), argIsa('$VAR'('PRED1'), '$VAR'('ARG'), '$VAR'('TYPE1')), argIsa('$VAR'('PRED2'), '$VAR'('ARG'), '$VAR'('TYPE2'))), negationPreds('$VAR'('PRED1'), '$VAR'('PRED2')), 'UniversalVocabularyMt', vStrDef).
 9111assertedTinyKB_implies( and(elInverse('$VAR'('PRED'), '$VAR'('INVERSE')), arg2Isa('$VAR'('PRED'), '$VAR'('COL'))), arg1Isa('$VAR'('INVERSE'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 9112assertedTinyKB_implies( and(elInverse('$VAR'('PRED'), '$VAR'('INVERSE')), arg2Genl('$VAR'('PRED'), '$VAR'('COL'))), arg1Genl('$VAR'('INVERSE'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 9113assertedTinyKB_implies( and(elInverse('$VAR'('PRED'), '$VAR'('INVERSE')), arg1Isa('$VAR'('PRED'), '$VAR'('COL'))), arg2Isa('$VAR'('INVERSE'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 9114assertedTinyKB_implies( and(elInverse('$VAR'('PRED'), '$VAR'('INVERSE')), arg1Genl('$VAR'('PRED'), '$VAR'('COL'))), arg2Genl('$VAR'('INVERSE'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrMon).
 9115assertedTinyKB_implies( and(isa('$VAR'('CONNECT'), 'LogicalConnective'), isa('$VAR'('CONNECT'), 'VariableArityRelation')), argsQuotedIsa('$VAR'('CONNECT'), 'CycLSentence-Assertible'), 'BaseKB', vStrMon).
 9116assertedTinyKB_implies( and(isa('$VAR'('CONNECT'), 'FixedArityRelation'), isa('$VAR'('CONNECT'), 'LogicalConnective'), arity('$VAR'('CONNECT'), '$VAR'('ARITY')), isa('$VAR'('ARG_N_QUOTED_ISA'), 'ArgQuotedIsaBinaryPredicate'), constrainsArg('$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('N')), integerBetween(1, '$VAR'('N'), '$VAR'('ARITY'))), holds('$VAR'('ARG_N_QUOTED_ISA'), '$VAR'('CONNECT'), 'CycLSentence-Assertible'), 'BaseKB', vStrMon).
 9117assertedTinyKB_not_first(and(scopingArg('$VAR'('RELN'), '$VAR'('N')), arity('$VAR'('RELN'), '$VAR'('ARITY')), greaterThan('$VAR'('N'), '$VAR'('ARITY'))), 'BaseKB', vStrDef).
 9118assertedTinyKB_not_first(and(resultGenlArg('$VAR'('FUNC'), '$VAR'('ARGNUM')), arity('$VAR'('FUNC'), '$VAR'('ARITY')), greaterThan('$VAR'('ARGNUM'), '$VAR'('ARITY'))), 'BaseKB', vStrMon).
 9119assertedTinyKB_not_first(and(omitArgIsa('$VAR'('RELN'), '$VAR'('N')), argIsa('$VAR'('RELN'), '$VAR'('N'), '$VAR'('_THING'))), 'UniversalVocabularyMt', vStrDef).
 9120assertedTinyKB_not_first(and(notAssertible('$VAR'('PRED')), isa('$VAR'('PRED'), 'DistributingMetaKnowledgePredicate')), 'UniversalVocabularyMt', vStrDef).
 9121assertedTinyKB_not_first(and(backchainForbiddenWhenUnboundInArg('$VAR'('PRED'), '$VAR'('N')), arity('$VAR'('PRED'), '$VAR'('M')), greaterThan('$VAR'('N'), '$VAR'('M'))), 'UniversalVocabularyMt', vStrDef).
 9122assertedTinyKB_not_first(and(arity('$VAR'('REL'), 1), commutativeInArgsAndRest('$VAR'('REL'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9123assertedTinyKB_not_first(and(arity('$VAR'('REL'), 1), commutativeInArgs('$VAR'('REL'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9124exactlyAssertedEL_with_vars(relationAllInstance, resultIsa, 'UnitOfMeasure', 'ScalarInterval', 'UniversalVocabularyMt', vStrMon).
 9125
 9126exactlyAssertedEL_with_vars(equiv, arity('$VAR'('REL'), 4), isa('$VAR'('REL'), 'QuaternaryRelation'), 'BaseKB', vStrMon).
 9127exactlyAssertedEL_with_vars(equiv, arity('$VAR'('REL'), 3), isa('$VAR'('REL'), 'TernaryRelation'), 'BaseKB', vStrDef).
 9128exactlyAssertedEL_with_vars(equiv, arity('$VAR'('REL'), 2), isa('$VAR'('REL'), 'BinaryRelation'), 'BaseKB', vStrMon).
 9129assertedTinyKB_implies_first( and(resultIsa('$VAR'('F'), '$VAR'('COL')), termOfUnit('$VAR'('U'), '$VAR'('F'))), isa('$VAR'('U'), '$VAR'('COL')), 'BaseKB', vStrDef).
 9130exactlyAssertedEL_with_vars(expansion, genls, implies(isa('$VAR'('OBJ'), (':ARG1')), isa('$VAR'('OBJ'), (':ARG2'))), 'BaseKB', vStrDef).
 9131exactlyAssertedEL_with_vars(expansion, resultIsa, implies(equals('$VAR'('VALUE'), 'NART'([(':ARG1'), '?ARGS'])), isa('$VAR'('VALUE'), (':ARG2'))), 'BaseKB', vStrMon).
 9132exactlyAssertedEL_with_vars(expansion, resultGenl, implies(equals('$VAR'('VALUE'), 'NART'([(':ARG1'), '?ARGS'])), genls('$VAR'('VALUE'), (':ARG2'))), 'BaseKB', vStrMon).
 9133exactlyAssertedEL_with_vars(relationAllInstance, resultIsa, 'UnitOfMeasure', 'ScalarInterval', 'UniversalVocabularyMt', vStrMon).
 9134
 9135assertedTinyKB_implies( and(isa('$VAR'('HIGH'), 'ScalarPointValue'), isa('$VAR'('LOW'), 'ScalarPointValue'), isa('$VAR'('UNIT'), 'UnitOfMeasure')), maxQuantValue(holds('$VAR'('UNIT'), '$VAR'('LOW'), '$VAR'('HIGH')), holds('$VAR'('UNIT'), '$VAR'('HIGH'))), 'BaseKB', vStrDef).
 9136assertedTinyKB_implies( and(isa('$VAR'('FUNCTION'), tFunction), quotedIsa('$VAR'('FUNCTION'), 'CycLConstant')), or(isa('$VAR'('FUNCTION'), 'ReifiableFunction'), isa('$VAR'('FUNCTION'), 'UnreifiableFunction')), 'BaseKB', vStrDef).
 9137assertedTinyKB_implies( and(isa('$VAR'('FUNC'), tFunction), arity('$VAR'('FUNC'), 5)), isa('$VAR'('FUNC'), 'QuintaryFunction'), 'BaseKB', vStrDef).
 9138assertedTinyKB_implies( and(isa('$VAR'('FUNC'), 'AssociativeRelation'), isa('$VAR'('FUNC'), tFunction), resultIsa('$VAR'('FUNC'), '$VAR'('RESULTCOL')), argIsa('$VAR'('FUNC'), '$VAR'('_N'), '$VAR'('ARGCOL'))), genls('$VAR'('RESULTCOL'), '$VAR'('ARGCOL')), 'BaseKB', vStrMon).
 9139assertedTinyKB_implies( and(isa('$VAR'('FUNC'), 'AssociativeRelation'), isa('$VAR'('FUNC'), tFunction), argIsa('$VAR'('FUNC'), '$VAR'('_N'), '$VAR'('ARGCOL'))), argIsa('$VAR'('FUNC'), '$VAR'('_M'), '$VAR'('ARGCOL')), 'BaseKB', vStrMon).
 9140assertedTinyKB_implies( and(isa('$VAR'('FUNC'), 'AssociativeRelation'), isa('$VAR'('FUNC'), 'BinaryFunction')), equals(holds('$VAR'('FUNC'), '$VAR'('THING1'), holds('$VAR'('FUNC'), '$VAR'('THING2'), '$VAR'('THING3'))), holds('$VAR'('FUNC'), '$VAR'('THING3'), holds('$VAR'('FUNC'), '$VAR'('THING1'), '$VAR'('THING2')))), 'BaseKB', vStrMon).
 9141assertedTinyKB_implies( and(isa('$VAR'('FUN'), tFunction), arity('$VAR'('FUN'), 2)), isa('$VAR'('FUN'), 'BinaryFunction'), 'BaseKB', vStrDef).
 9142assertedTinyKB_implies( and(isa('$VAR'('DIS_COL_TYPE'), 'DisjointCollectionType'), isa('$VAR'('COL1'), '$VAR'('DIS_COL_TYPE')), isa('$VAR'('COL2'), '$VAR'('DIS_COL_TYPE')), different('$VAR'('COL1'), '$VAR'('COL2'))), disjointWith('$VAR'('COL1'), '$VAR'('COL2')), 'BaseKB', vStrDef).
 9143assertedTinyKB_implies( and(isa('$VAR'('COL'), tCol), isa('$VAR'('RELN'), 'BinaryPredicate'), overlappingExternalConcept('$VAR'('RELN'), '$VAR'('SOURCE'), '$VAR'('STRING')), overlappingExternalConcept('$VAR'('COL'), '$VAR'('SOURCE'), '$VAR'('STRING'))), extConceptOverlapsColAndReln('$VAR'('COL'), '$VAR'('RELN'), '$VAR'('SOURCE'), '$VAR'('STRING')), 'BaseKB', vStrDef).
 9144assertedTinyKB_implies( and(isa('$VAR'('BPRED'), 'SymmetricBinaryPredicate'), transitiveViaArgInverse('$VAR'('PRED'), '$VAR'('BPRED'), '$VAR'('N'))), transitiveViaArg('$VAR'('PRED'), '$VAR'('BPRED'), '$VAR'('N')), 'BaseKB', vStrDef).
 9145assertedTinyKB_implies( and(isa('$VAR'('BPRED'), 'SymmetricBinaryPredicate'), transitiveViaArg('$VAR'('PRED'), '$VAR'('BPRED'), '$VAR'('N'))), transitiveViaArgInverse('$VAR'('PRED'), '$VAR'('BPRED'), '$VAR'('N')), 'BaseKB', vStrDef).
 9146assertedTinyKB_implies( and(isa('$VAR'('BINPRED'), 'BinaryPredicate'), arg1Isa('$VAR'('BINPRED'), '$VAR'('COL2')), requiredArg2Pred('$VAR'('COL1'), '$VAR'('BINPRED'))), relationExistsAll('$VAR'('BINPRED'), '$VAR'('COL2'), '$VAR'('COL1')), 'BaseKB', vStrMon).
 9147assertedTinyKB_implies( and(isa('$VAR'('ARG_ISA_PRED'), 'ArgIsaBinaryPredicate'), constrainsArg('$VAR'('ARG_ISA_PRED'), '$VAR'('N')), preservesGenlsInArg('$VAR'('FUNC'), '$VAR'('N'))), holds('$VAR'('ARG_ISA_PRED'), '$VAR'('FUNC'), tCol), 'BaseKB', vStrDef).
 9148assertedTinyKB_implies( and(isa('$VAR'('ARG_ISA'), 'ArgIsaBinaryPredicate'), constrainsArg('$VAR'('ARG_ISA'), '$VAR'('NUM'))), trueRule('NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(holds('$VAR'('ARG_ISA'), '$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), '$VAR'('NUM'), '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), '$VAR'('NUM'), '$VAR'('COL')), holds('$VAR'('ARG_ISA'), '$VAR'('RELN'), '$VAR'('COL'))))), 'CoreCycLMt', vStrMon).
 9149assertedTinyKB_implies( and(isa('$VAR'('ARG2'), '$VAR'('UNIV_COL')), relationExistsMinAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL'), '$VAR'('NUM'))), trueSentence(thereExistAtLeast('$VAR'('NUM'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), '$VAR'('EXIST_COL')), holds('$VAR'('SLOT'), '$VAR'('ARG'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9150assertedTinyKB_implies( and(isa('$VAR'('ARG2'), '$VAR'('UNIV_COL')), relationExistsMaxAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL'), '$VAR'('NUM'))), trueSentence(thereExistAtMost('$VAR'('NUM'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), '$VAR'('EXIST_COL')), holds('$VAR'('SLOT'), '$VAR'('ARG'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9151assertedTinyKB_implies( and(isa('$VAR'('ARG2'), '$VAR'('UNIV_COL')), relationExistsCountAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL'), '$VAR'('NUM'))), trueSentence(thereExistExactly('$VAR'('NUM'), '$VAR'('ARG1'), and(isa('$VAR'('ARG1'), '$VAR'('EXIST_COL')), holds('$VAR'('SLOT'), '$VAR'('ARG1'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9152assertedTinyKB_implies( and(isa('$VAR'('ARG1'), '$VAR'('UNIV_COL')), relationAllExistsMin('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), '$VAR'('NUM'))), trueSentence(thereExistAtLeast('$VAR'('NUM'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), '$VAR'('EXIST_COL')), holds('$VAR'('SLOT'), '$VAR'('ARG1'), '$VAR'('ARG'))))), 'BaseKB', vStrDef).
 9153assertedTinyKB_implies( and(isa('$VAR'('ARG1'), '$VAR'('UNIV_COL')), relationAllExistsMax('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), '$VAR'('NUM'))), trueSentence(thereExistAtMost('$VAR'('NUM'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), '$VAR'('EXIST_COL')), holds('$VAR'('SLOT'), '$VAR'('ARG1'), '$VAR'('ARG'))))), 'BaseKB', vStrDef).
 9154assertedTinyKB_implies( and(isa('$VAR'('ALL_INST'), '$VAR'('ALL_COL')), relationAllExists('$VAR'('PRED'), '$VAR'('ALL_COL'), '$VAR'('EX_COL'))), trueSentence(thereExists('$VAR'('EX_INST'), and(isa('$VAR'('EX_INST'), '$VAR'('EX_COL')), holds('$VAR'('PRED'), '$VAR'('ALL_INST'), '$VAR'('EX_INST'))))), 'BaseKB', vStrMon).
 9155assertedTinyKB_implies( and(isa('$VAR'('_ANY'), '$VAR'('COL')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('INST'))), relationExistsInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('INST')), 'BaseKB', vStrMon).
 9156assertedTinyKB_implies( and(holds('$VAR'('PRED'), '$VAR'('ARG1')), genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG1')), 'BaseKB', vStrMon).
 9157assertedTinyKB_implies( and(greaterThanOrEqualTo(5, '$VAR'('N')), arg6Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg5Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9158assertedTinyKB_implies( and(greaterThanOrEqualTo(4, '$VAR'('N')), arg5Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg4Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9159assertedTinyKB_implies( and(greaterThanOrEqualTo(3, '$VAR'('N')), arg4Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg3Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9160assertedTinyKB_implies( and(greaterThanOrEqualTo(2, '$VAR'('N')), arg3Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg2Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9161assertedTinyKB_implies( and(greaterThanOrEqualTo(1, '$VAR'('N')), arg2Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg1Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9162assertedTinyKB_implies( and(greaterThanOrEqualTo('$VAR'('N'), '$VAR'('ARGNUM')), argAndRestIsa('$VAR'('PRED'), '$VAR'('ARGNUM'), '$VAR'('COL'))), argIsa('$VAR'('PRED'), '$VAR'('N'), '$VAR'('COL')), 'BaseKB', vStrDef).
 9163assertedTinyKB_implies( and(greaterThanOrEqualTo('$VAR'('MAX'), '$VAR'('MIN')), maxQuantValue('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('MAX'))), minQuantValue('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('MIN')))), equals('$VAR'('ATT'), holds('$VAR'('UNIT'), '$VAR'('MIN'), '$VAR'('MAX'))), 'BaseKB', vStrMon).
 9164assertedTinyKB_implies( and(greaterThan('$VAR'('NUM'), 0), relationExistsMinAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL'), '$VAR'('NUM'))), relationExistsAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL')), 'BaseKB', vStrDef).
 9165assertedTinyKB_implies( and(greaterThan('$VAR'('NUM'), 0), relationExistsCountAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL'), '$VAR'('NUM'))), relationExistsAll('$VAR'('SLOT'), '$VAR'('EXIST_COL'), '$VAR'('UNIV_COL')), 'BaseKB', vStrDef).
 9166assertedTinyKB_implies( and(greaterThan('$VAR'('NUM'), 0), relationAllExistsMin('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), '$VAR'('NUM'))), relationAllExists('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL')), 'BaseKB', vStrDef).
 9167assertedTinyKB_implies( and(greaterThan('$VAR'('NUM'), 0), relationAllExistsCount('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), '$VAR'('NUM'))), relationAllExists('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL')), 'BaseKB', vStrDef).
 9168assertedTinyKB_implies( and(greaterThan('$VAR'('NUM'), 0), greaterThanOrEqualTo('$VAR'('ARITY'), '$VAR'('NUM')), arity('$VAR'('FN'), '$VAR'('ARITY')), resultIsa('$VAR'('FN'), '$VAR'('COLL'))), interArgResultIsa('$VAR'('FN'), '$VAR'('NUM'), 'Thing', '$VAR'('COLL')), 'BaseKB', vStrDef).
 9169assertedTinyKB_implies( and(greaterThan('$VAR'('N'), 5), arg5Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg5Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9170assertedTinyKB_implies( and(greaterThan('$VAR'('N'), 4), arg4Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg4Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9171assertedTinyKB_implies( and(greaterThan('$VAR'('N'), 3), arg3Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg3Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9172assertedTinyKB_implies( and(greaterThan('$VAR'('N'), 2), arg2Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg2Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9173assertedTinyKB_implies( and(greaterThan('$VAR'('N'), 1), arg1Isa('$VAR'('PRED'), '$VAR'('TYPE'))), arg1Isa('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9174assertedTinyKB_implies( and(greaterThan('$VAR'('BIGGER'), '$VAR'('SMALLER')), relationAllInstance(greaterThanOrEqualTo, '$VAR'('COL'), '$VAR'('BIGGER'))), relationAllInstance(greaterThan, '$VAR'('COL'), '$VAR'('SMALLER')), 'UniversalVocabularyMt', vStrDef).
 9175assertedTinyKB_implies( and(genls('$VAR'('X'), 'larkc-Plugin'), 'larkc-hasOutputType'('$VAR'('X'), '$VAR'('TYPE')), genls('$VAR'('TYPE'), '$VAR'('TYPE1')), 'larkc-hasInputType'('$VAR'('Y'), '$VAR'('TYPE1')), genls('$VAR'('Y'), 'larkc-Plugin')), 'larkc-pluginByDataConnectsTo'('$VAR'('X'), '$VAR'('Y')), 'BaseKB', vStrDef).
 9176assertedTinyKB_implies( and(genls('$VAR'('X'), '$VAR'('Y')), genls('$VAR'('Y'), '$VAR'('Z'))), genls('$VAR'('X'), '$VAR'('Z')), 'LogicalTruthMt', vStrMon).
 9177assertedTinyKB_implies( and(genls('$VAR'('SPEC'), '$VAR'('COL2')), different('$VAR'('COL2'), '$VAR'('SPEC')), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('SPEC'))), abnormal('TheList'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [[relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]]], 'BaseKB', ["?PRED", "?COL1", "?COL2"], [implies, [and, [arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]])), 'BaseKB', vStrMon).
 9178assertedTinyKB_implies( and(genls('$VAR'('SPEC'), '$VAR'('COL')), defnNecessary('$VAR'('COL'), '$VAR'('DEFN'))), defnNecessary('$VAR'('SPEC'), '$VAR'('DEFN')), 'BaseKB', vStrMon).
 9179assertedTinyKB_implies( and(genls('$VAR'('SPEC'), '$VAR'('COL')), conceptuallyRelated('$VAR'('COL'), '$VAR'('REL_OBJ'))), conceptuallyRelated('$VAR'('SPEC'), '$VAR'('REL_OBJ')), 'BaseKB', vStrDef).
 9180assertedTinyKB_implies( and(genls('$VAR'('INDEP_SPEC'), '$VAR'('INDEP_COL')), holds('$VAR'('PRED'), '$VAR'('INDEP_SPEC'), '$VAR'('DEP_SPEC')), 'interArgGenl1-2'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL'))), genls('$VAR'('DEP_SPEC'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9181assertedTinyKB_implies( and(genls('$VAR'('COL_1'), '$VAR'('DIFF_NEAR')), different('$VAR'('COL_1'), '$VAR'('DIFF_NEAR'))), or(elementOf('$VAR'('COL_2'), 'TheSetOf'('$VAR'('ITEM_1'), genls('$VAR'('ITEM_1'), '$VAR'('DIFF_NEAR')))), nearestDifferentGenls('$VAR'('COL_1'), '$VAR'('COL_2'), '$VAR'('DIFF_NEAR')), elementOf('$VAR'('DIFF_NEAR'), 'TheSetOf'('$VAR'('DIFF_FARTHER'), thereExists('$VAR'('DIFF_FAR'), and(genls('$VAR'('COL_1'), '$VAR'('DIFF_FAR')), genls('$VAR'('DIFF_FAR'), '$VAR'('DIFF_FARTHER')), different('$VAR'('COL_1'), '$VAR'('DIFF_FAR')), different('$VAR'('DIFF_FAR'), '$VAR'('DIFF_FARTHER')), not(elementOf('$VAR'('COL_2'), 'TheSetOf'('$VAR'('ITEM_2'), genls('$VAR'('ITEM_2'), '$VAR'('DIFF_FAR'))))), not(elementOf('$VAR'('COL_2'), 'TheSetOf'('$VAR'('ITEM_3'), genls('$VAR'('ITEM_3'), '$VAR'('DIFF_FARTHER')))))))))), 'BaseKB', vStrMon).
 9182assertedTinyKB_implies( and(genls('$VAR'('COL_1'), '$VAR'('COMMON_NEAR')), different('$VAR'('COL_1'), '$VAR'('COMMON_NEAR')), genls('$VAR'('COL_2'), '$VAR'('COMMON_NEAR')), different('$VAR'('COL_2'), '$VAR'('COMMON_NEAR'))), or(nearestCommonGenls('$VAR'('COL_1'), '$VAR'('COL_2'), '$VAR'('COMMON_NEAR')), elementOf('$VAR'('COMMON_NEAR'), 'TheSetOf'('$VAR'('COMMON_FARTHER'), thereExists('$VAR'('COMMON_FAR'), and(genls('$VAR'('COL_1'), '$VAR'('COMMON_FAR')), genls('$VAR'('COL_2'), '$VAR'('COMMON_FAR')), genls('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER')), different('$VAR'('COL_1'), '$VAR'('COMMON_FAR')), different('$VAR'('COL_2'), '$VAR'('COMMON_FAR')), different('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER'))))))), 'BaseKB', vStrDef).
 9183assertedTinyKB_implies( and(genls('$VAR'('COL2'), '$VAR'('COL3')), arg2Isa('$VAR'('PRED'), '$VAR'('COL3'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [[relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]]], 'BaseKB', ["?PRED", "?COL1", "?COL2"], [implies, [and, [arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]])), 'BaseKB', vStrMon).
 9184assertedTinyKB_implies( and(genls('$VAR'('COL1'), '$VAR'('GENL')), different('$VAR'('COL1'), '$VAR'('GENL')), relationAllExists('$VAR'('PRED'), '$VAR'('GENL'), '$VAR'('COL2'))), abnormal('TheList'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [[relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]]], 'BaseKB', ["?PRED", "?COL1", "?COL2"], [implies, [and, [arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]])), 'BaseKB', vStrMon).
 9185assertedTinyKB_implies( and(genls('$VAR'('COL1'), '$VAR'('COL2')), genls('$VAR'('COL2'), '$VAR'('COL1'))), coExtensional('$VAR'('COL1'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9186assertedTinyKB_implies( and(genls('$VAR'('COL'), '$VAR'('NEAR_COL')), different('$VAR'('COL'), '$VAR'('NEAR_COL')), unknownSentence(thereExists('$VAR'('BETWEEN'), and(genls('$VAR'('BETWEEN'), '$VAR'('NEAR_COL')), genls('$VAR'('COL'), '$VAR'('BETWEEN')), different('$VAR'('BETWEEN'), '$VAR'('COL'), '$VAR'('NEAR_COL')))))), nearestGenls('$VAR'('COL'), '$VAR'('NEAR_COL')), 'BaseKB', vStrDef).
 9187assertedTinyKB_implies( and(genls('$VAR'('COL'), '$VAR'('GENL')), defnSufficient('$VAR'('COL'), '$VAR'('DEFN'))), defnSufficient('$VAR'('GENL'), '$VAR'('DEFN')), 'BaseKB', vStrMon).
 9188assertedTinyKB_implies( and(genls('$VAR'('ARGS_5'), '$VAR'('ARGS_6')), genls('$VAR'('ARGS_6'), '$VAR'('ARGS_5'))), coExtensional('$VAR'('ARGS_5'), '$VAR'('ARGS_6')), 'UniversalVocabularyMt', vStrDef).
 9189assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('PRED')), genls('$VAR'('EXISTS_SPEC'), '$VAR'('EXISTS_COL')), genls('$VAR'('ALL_SPEC'), '$VAR'('ALL_COL')), greaterThanOrEqualTo('$VAR'('MORE'), '$VAR'('MAX')), relationExistsMaxAll('$VAR'('PRED'), '$VAR'('EXISTS_COL'), '$VAR'('ALL_COL'), '$VAR'('MAX'))), relationExistsMaxAll('$VAR'('SPEC_PRED'), '$VAR'('EXISTS_SPEC'), '$VAR'('ALL_SPEC'), '$VAR'('MORE')), 'BaseKB', vStrDef).
 9190assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('PRED')), genlInverse('$VAR'('PRED'), '$VAR'('GENL_PRED'))), genlInverse('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), 'BaseKB', vStrMon).
 9191assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('PRED')), different('$VAR'('PRED'), '$VAR'('SPEC_PRED')), relationAllExists('$VAR'('SPEC_PRED'), '$VAR'('COL1'), '$VAR'('COL2'))), abnormal('TheList'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [[relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]]], 'BaseKB', ["?PRED", "?COL1", "?COL2"], [implies, [and, [arity, '$VAR'('PRED'), 2], [requiredArg1Pred, '$VAR'('COL1'), '$VAR'('PRED')], ['interArgIsa1-2', '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]], [relationAllExists, '$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')]])), 'BaseKB', vStrMon).
 9192assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), unknownSentence(thereExists('$VAR'('DIR'), reformulationDirectionInMode('$VAR'('DIR'), '$VAR'('MODE'), '$VAR'('RULE')))), defaultReformulationDirectionInModeForPred('$VAR'('DEFAULT_DIR'), '$VAR'('MODE'), '$VAR'('GENL_PRED')), evaluate('$VAR'('SPEC_PRED'), 'FormulaArgFn'(0, '$VAR'('RULE')))), reformulationDirectionInMode('$VAR'('DEFAULT_DIR'), '$VAR'('MODE'), '$VAR'('RULE')), 'BaseKB', vStrDef).
 9193assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), relationAllExists('$VAR'('SPEC_PRED'), '$VAR'('COL_1'), '$VAR'('COL_2'))), relationAllExists('$VAR'('GENL_PRED'), '$VAR'('COL_1'), '$VAR'('COL_2')), 'BaseKB', vStrDef).
 9194assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), relationAll('$VAR'('SPEC_PRED'), '$VAR'('COL'))), relationAll('$VAR'('GENL_PRED'), '$VAR'('COL')), 'BaseKB', vStrDef).
 9195assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), different('$VAR'('GENL_PRED'), '$VAR'('SPEC_PRED')), relationInstanceAll('$VAR'('SPEC_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), relationInstanceAll('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), 'BaseKB', vStrMon).
 9196assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), different('$VAR'('GENL_PRED'), '$VAR'('SPEC_PRED')), relationAllInstance('$VAR'('SPEC_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), relationAllInstance('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), 'BaseKB', vStrMon).
 9197assertedTinyKB_implies( and(genlPreds('$VAR'('SPEC'), '$VAR'('GENL')), fanOutArg('$VAR'('GENL'), '$VAR'('ARG_NUM'))), fanOutArg('$VAR'('SPEC'), '$VAR'('ARG_NUM')), 'BaseKB', vStrDef).
 9198assertedTinyKB_implies( and(genlPreds('$VAR'('PRED'), '$VAR'('NEAR_PRED')), different('$VAR'('NEAR_PRED'), '$VAR'('PRED')), unknownSentence(thereExists('$VAR'('BETWEEN'), and(genlPreds('$VAR'('BETWEEN'), '$VAR'('NEAR_PRED')), genlPreds('$VAR'('PRED'), '$VAR'('BETWEEN')), different('$VAR'('BETWEEN'), '$VAR'('NEAR_PRED'), '$VAR'('PRED')))))), nearestGenlPreds('$VAR'('PRED'), '$VAR'('NEAR_PRED')), 'BaseKB', vStrMon).
 9199assertedTinyKB_implies( and(genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'), '$VAR'('ARG5'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'), '$VAR'('ARG5')), 'BaseKB', vStrMon).
 9200assertedTinyKB_implies( and(genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4')), 'BaseKB', vStrMon).
 9201assertedTinyKB_implies( and(genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3')), 'BaseKB', vStrMon).
 9202assertedTinyKB_implies( and(genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), holds('$VAR'('GENL_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), 'BaseKB', vStrMon).
 9203assertedTinyKB_implies( and(genlMt('$VAR'('X'), '$VAR'('Y')), genlMt('$VAR'('Y'), '$VAR'('Z'))), genlMt('$VAR'('X'), '$VAR'('Z')), 'LogicalTruthMt', vStrMon).
 9204assertedTinyKB_implies( and(genlMt('$VAR'('MT_1'), '$VAR'('COMMON_NEAR')), different('$VAR'('COMMON_NEAR'), '$VAR'('MT_1')), different('$VAR'('COMMON_NEAR'), '$VAR'('MT_2')), genlMt('$VAR'('MT_2'), '$VAR'('COMMON_NEAR'))), or(nearestCommonGenlMt('$VAR'('MT_1'), '$VAR'('MT_2'), '$VAR'('COMMON_NEAR')), elementOf('$VAR'('COMMON_NEAR'), 'TheSetOf'('$VAR'('COMMON_FARTHER'), thereExists('$VAR'('COMMON_FAR'), and(genlMt('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER')), genlMt('$VAR'('MT_1'), '$VAR'('COMMON_FAR')), genlMt('$VAR'('MT_2'), '$VAR'('COMMON_FAR')), different('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER')), different('$VAR'('COMMON_FAR'), '$VAR'('MT_1')), different('$VAR'('COMMON_FAR'), '$VAR'('MT_2'))))))), 'BaseKB', vStrMon).
 9205assertedTinyKB_implies( and(genlInverse('$VAR'('SPEC_PRED'), '$VAR'('PRED')), genlPreds('$VAR'('PRED'), '$VAR'('GENL_PRED'))), genlInverse('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), 'BaseKB', vStrMon).
 9206assertedTinyKB_implies( and(genlInverse('$VAR'('SPEC_PRED'), '$VAR'('PRED')), genlInverse('$VAR'('PRED'), '$VAR'('GENL_PRED'))), genlPreds('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')), 'BaseKB', vStrMon).
 9207assertedTinyKB_implies( and(genlInverse('$VAR'('PRED'), '$VAR'('INVERSE')), relationExistsAll('$VAR'('PRED'), '$VAR'('TYPE1'), '$VAR'('TYPE2'))), relationAllExists('$VAR'('INVERSE'), '$VAR'('TYPE2'), '$VAR'('TYPE1')), 'BaseKB', vStrMon).
 9208assertedTinyKB_implies( and(genlInverse('$VAR'('PRED'), '$VAR'('GENL_INV_PRED')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), holds('$VAR'('GENL_INV_PRED'), '$VAR'('ARG2'), '$VAR'('ARG1')), 'BaseKB', vStrMon).
 9209assertedTinyKB_implies( and(evaluationResultQuotedIsa('$VAR'('FUNCTION'), '$VAR'('Q_COL')), 'genls-SpecDenotesGenlInstances'('$VAR'('Q_COL'), '$VAR'('COL'))), resultIsa('$VAR'('FUNCTION'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 9210assertedTinyKB_implies( and(evaluate('$VAR'('TIMESFN'), 'TimesFn'(holds('$VAR'('UNIT2'), 1), holds('$VAR'('UNIT1'), '$VAR'('N')))), termOfUnit('$VAR'('UNITPRODUCTFN'), 'UnitProductFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('TIMESFN'), holds('$VAR'('UNITPRODUCTFN'), '$VAR'('N'))), 'BaseKB', vStrMon).
 9211assertedTinyKB_implies( and(evaluate('$VAR'('TERM'), 'FormulaArgFn'('$VAR'('ARG'), '$VAR'('NAT'))), termOfUnit('$VAR'('NAT'), '$VAR'('FORMULA'))), natArgument('$VAR'('NAT'), '$VAR'('ARG'), '$VAR'('TERM')), 'BaseKB', vStrMon).
 9212assertedTinyKB_implies( and(evaluate('$VAR'('QUOTIENTFN'), 'QuotientFn'(holds('$VAR'('UNIT1'), '$VAR'('N')), holds('$VAR'('UNIT2'), 1))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('QUOTIENTFN'), holds('$VAR'('PERFN'), '$VAR'('N'))), 'BaseKB', vStrMon).
 9213assertedTinyKB_implies( and(evaluate('$VAR'('QUOTIENTFN'), 'QuotientFn'(holds('$VAR'('UNIT1'), '$VAR'('M'), '$VAR'('N')), holds('$VAR'('UNIT2'), 1))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('QUOTIENTFN'), holds('$VAR'('PERFN'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrMon).
 9214
 9215assertedTinyKB_implies( and(evaluate('$VAR'('FUNCTION'), 'FormulaArgFn'(0, '$VAR'('NAT'))), termOfUnit('$VAR'('NAT'), '$VAR'('FORMULA'))), natFunction('$VAR'('NAT'), '$VAR'('FUNCTION')), 'BaseKB', vStrDef).
 9216assertedTinyKB_implies( and(evaluate('$VAR'('ARGS_LIST'), 'FormulaArgListFn'('$VAR'('NAT1'))), evaluate('$VAR'('ARGS_LIST'), 'FormulaArgListFn'('$VAR'('NAT2'))), termOfUnit('$VAR'('NAT1'), '$VAR'('FORMULA1')), termOfUnit('$VAR'('NAT2'), '$VAR'('FORMULA2'))), natArgumentsEqual('$VAR'('NAT1'), '$VAR'('NAT2')), 'BaseKB', vStrMon).
 9217assertedTinyKB_implies( and(evaluate('$VAR'('ARG'), 'FormulaArgFn'('$VAR'('N'), '$VAR'('NAT'))), termOfUnit('$VAR'('NAT'), '$VAR'('FORMULA'))), termDependsOn('$VAR'('NAT'), '$VAR'('ARG')), 'BaseKB', vStrMon).
 9218assertedTinyKB_implies( and(equals('$VAR'('X'), '$VAR'('Y')), isa('$VAR'('X'), '$VAR'('COL'))), isa('$VAR'('Y'), '$VAR'('COL')), 'BaseKB', vStrDef).
 9219assertedTinyKB_implies( and(equals('$VAR'('X'), '$VAR'('Y')), equals('$VAR'('Y'), '$VAR'('Z'))), equals('$VAR'('X'), '$VAR'('Z')), 'LogicalTruthMt', vStrMon).
 9220
 9221assertedTinyKB_implies( evaluateImmediately('$VAR'('FUNC')), evaluateAtEL('$VAR'('FUNC')), 'UniversalVocabularyMt', vStrDef).
 9222assertedTinyKB_implies( evaluate('$VAR'('TIMESFN'), 'TimesFn'('$VAR'('X'), 0)), evaluate(0, '$VAR'('TIMESFN')), 'BaseKB', vStrMon).
 9223assertedTinyKB_implies( evaluate('$VAR'('QUOTIENTFN'), 'QuotientFn'('$VAR'('NUM_1'), '$VAR'('NUM_2'))), ratioOfTo('$VAR'('NUM_1'), '$VAR'('NUM_2'), '$VAR'('QUOTIENTFN')), 'BaseKB', vStrDef).
 9224assertedTinyKB_implies( evaluate('$VAR'('PLUSFN'), 'PlusFn'('$VAR'('X'), 0)), equals('$VAR'('PLUSFN'), '$VAR'('X')), 'BaseKB', vStrMon).
 9225assertedTinyKB_implies( evaluate('$VAR'('PLUSFN'), 'PlusFn'('$VAR'('X'))), equals('$VAR'('PLUSFN'), '$VAR'('X')), 'BaseKB', vStrMon).
 9226assertedTinyKB_implies( evaluate('$VAR'('FORMULAARGFN'), 'FormulaArgFn'(0, '$VAR'('FORMULA'))), operatorFormulas('$VAR'('FORMULAARGFN'), '$VAR'('FORMULA')), 'BaseKB', vStrDef).
 9227assertedTinyKB_implies( evaluate('$VAR'('_RESULT'), 'EvaluateSubLFn'('$VAR'('SUBL'))), performSubL('$VAR'('SUBL')), 'BaseKB', vStrMon).
 9228assertedTinyKB_implies( different('CycLNonAtomicTerm', '$VAR'('COL')), meetsPragmaticRequirement('TheList'('$VAR'('NAT'), '$VAR'('FUNCTION'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[natFunction, '$VAR'('NAT'), '$VAR'('FUNCTION')], [resultQuotedIsa, '$VAR'('FUNCTION'), '$VAR'('COL')]], [[quotedIsa, '$VAR'('NAT'), '$VAR'('COL')]]], 'CoreCycLMt', ["?NAT", "?FUNCTION", "?COL"], [implies, [and, [natFunction, '$VAR'('NAT'), '$VAR'('FUNCTION')], [resultQuotedIsa, '$VAR'('FUNCTION'), '$VAR'('COL')]], [quotedIsa, '$VAR'('NAT'), '$VAR'('COL')]])), 'CoreCycLMt', vStrDef).
 9229assertedTinyKB_implies( different('$VAR'('UNIT_THREE'), '$VAR'('UNIT_TWO')), meetsPragmaticRequirement('TheList'('$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE'), '$VAR'('FACTOR1'), '$VAR'('PERFN_1'), '$VAR'('UNIT_ONE'), '$VAR'('PERFN')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[unitMultiplicationFactor, '$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE'), '$VAR'('FACTOR1')], [termOfUnit, '$VAR'('PERFN_1'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE')]], [termOfUnit, '$VAR'('PERFN'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO')]]], [[unitMultiplicationFactor, '$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')]]], 'BaseKB', ["?UNIT-TWO", "?UNIT-THREE", "?FACTOR1", "?PERFN-1", "?UNIT-ONE", "?PERFN"], [implies, [and, [unitMultiplicationFactor, '$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE'), '$VAR'('FACTOR1')], [termOfUnit, '$VAR'('PERFN_1'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE')]], [termOfUnit, '$VAR'('PERFN'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO')]]], [unitMultiplicationFactor, '$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')]])), 'BaseKB', vStrMon).
 9230assertedTinyKB_implies( different('$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO')), meetsPragmaticRequirement('TheList'('$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO'), '$VAR'('FACTOR1'), '$VAR'('PERFN_1'), '$VAR'('UNIT_THREE'), '$VAR'('PERFN')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[unitMultiplicationFactor, '$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO'), '$VAR'('FACTOR1')], [termOfUnit, '$VAR'('PERFN_1'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE')]], [termOfUnit, '$VAR'('PERFN'), ['PerFn', '$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE')]]], [[unitMultiplicationFactor, '$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')]]], 'BaseKB', ["?UNIT-ONE", "?UNIT-TWO", "?FACTOR1", "?PERFN-1", "?UNIT-THREE", "?PERFN"], [implies, [and, [unitMultiplicationFactor, '$VAR'('UNIT_ONE'), '$VAR'('UNIT_TWO'), '$VAR'('FACTOR1')], [termOfUnit, '$VAR'('PERFN_1'), ['PerFn', '$VAR'('UNIT_ONE'), '$VAR'('UNIT_THREE')]], [termOfUnit, '$VAR'('PERFN'), ['PerFn', '$VAR'('UNIT_TWO'), '$VAR'('UNIT_THREE')]]], [unitMultiplicationFactor, '$VAR'('PERFN_1'), '$VAR'('PERFN'), '$VAR'('FACTOR1')]])), 'BaseKB', vStrMon).
 9231
 9232assertedTinyKB_implies( and(disjointWith('$VAR'('COL'), '$VAR'('SUPERSET')), genls('$VAR'('SUBSET'), '$VAR'('SUPERSET'))), disjointWith('$VAR'('COL'), '$VAR'('SUBSET')), 'BaseKB', vStrMon).
 9233assertedTinyKB_implies( and(different(negationPreds, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), negationPreds)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-NEGATIONPREDS')), 'BaseKB', vStrMon).
 9234assertedTinyKB_implies( and(different(negationInverse, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), negationInverse)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-NEGATIONINVERSE')), 'BaseKB', vStrMon).
 9235assertedTinyKB_implies( and(different(isa, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), isa)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-ISA')), 'BaseKB', vStrMon).
 9236assertedTinyKB_implies( and(different(genls, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), genls)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-GENLS')), 'BaseKB', vStrMon).
 9237assertedTinyKB_implies( and(different(genlPreds, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), genlPreds)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-GENLPREDS')), 'BaseKB', vStrMon).
 9238assertedTinyKB_implies( and(different(genlMt, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), genlMt)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-GENLMT')), 'BaseKB', vStrMon).
 9239assertedTinyKB_implies( and(different(genlInverse, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), genlInverse)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-GENLINVERSE')), 'BaseKB', vStrMon).
 9240assertedTinyKB_implies( and(different(disjointWith, '$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), disjointWith)), afterAdding('$VAR'('SPEC_PRED'), 'SubLQuoteFn'('PROPAGATE-TO-DISJOINTWITH')), 'BaseKB', vStrDef).
 9241assertedTinyKB_implies( and(different('False', '$VAR'('EVALUATESUBLFN')), evaluate('$VAR'('EVALUATESUBLFN'), 'EvaluateSubLFn'('ExpandSubLFn'('$VAR'('RESULT'), 'FIF'('QUOTE'('$VAR'('RESULT')), 'True', 'False')))), evaluate('$VAR'('RESULT'), 'EvaluateSubLFn'('$VAR'('SUBL')))), trueSubL('$VAR'('SUBL')), 'BaseKB', vStrMon).
 9242assertedTinyKB_implies( and(different('$VAR'('X'), '$VAR'('Y')), different('$VAR'('Y'), '$VAR'('Z'))), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('X'), '$VAR'('Y'), '$VAR'('Z')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[isa, '$VAR'('PRED'), 'TransitiveBinaryPredicate'], ['$VAR'('PRED'), '$VAR'('X'), '$VAR'('Y')], ['$VAR'('PRED'), '$VAR'('Y'), '$VAR'('Z')]], [['$VAR'('PRED'), '$VAR'('X'), '$VAR'('Z')]]], 'BaseKB', ["?PRED", "?X", "?Y", "?Z"], [implies, [and, [isa, '$VAR'('PRED'), 'TransitiveBinaryPredicate'], ['$VAR'('PRED'), '$VAR'('X'), '$VAR'('Y')], ['$VAR'('PRED'), '$VAR'('Y'), '$VAR'('Z')]], ['$VAR'('PRED'), '$VAR'('X'), '$VAR'('Z')]])), 'BaseKB', vStrDef).
 9243assertedTinyKB_implies( and(different('$VAR'('MT'), '$VAR'('NEAR_MT')), genlMt('$VAR'('MT'), '$VAR'('NEAR_MT')), unknownSentence(thereExists('$VAR'('BETWEEN'), and(genlMt('$VAR'('BETWEEN'), '$VAR'('NEAR_MT')), genlMt('$VAR'('MT'), '$VAR'('BETWEEN')), different('$VAR'('BETWEEN'), '$VAR'('MT'), '$VAR'('NEAR_MT')))))), nearestGenlMt('$VAR'('MT'), '$VAR'('NEAR_MT')), 'BaseKB', vStrMon).
 9244assertedTinyKB_implies( and(different('$VAR'('GENL_COL'), '$VAR'('SPEC_COL')), genls('$VAR'('SPEC_COL'), '$VAR'('GENL_COL')), relationInstanceAll('$VAR'('PRED'), '$VAR'('ARG'), '$VAR'('GENL_COL'))), relationInstanceAll('$VAR'('PRED'), '$VAR'('ARG'), '$VAR'('SPEC_COL')), 'BaseKB', vStrMon).
 9245assertedTinyKB_implies( and(different('$VAR'('GENL_COL'), '$VAR'('SPEC_COL')), genls('$VAR'('SPEC_COL'), '$VAR'('GENL_COL')), relationAllInstance('$VAR'('PRED'), '$VAR'('GENL_COL'), '$VAR'('ARG'))), relationAllInstance('$VAR'('PRED'), '$VAR'('SPEC_COL'), '$VAR'('ARG')), 'BaseKB', vStrMon).
 9246assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('SPEC_PRED')), genlPreds('$VAR'('SPEC_PRED'), genlMt)), predicateConventionMt('$VAR'('SPEC_PRED'), 'UniversalVocabularyMt'), 'BaseKB', vStrMon).
 9247assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('PRED')), predicateConventionMt('$VAR'('PRED'), '$VAR'('MT')), genlPreds('$VAR'('SPEC'), '$VAR'('PRED'))), predicateConventionMt('$VAR'('SPEC'), '$VAR'('MT')), 'BaseKB', vStrDef).
 9248assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('PRED')), predicateConventionMt('$VAR'('PRED'), '$VAR'('MT'))), genlMt('BaseKB', '$VAR'('MT')), 'UniversalVocabularyMt', vStrMon).
 9249assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('PRED')), genlPreds('$VAR'('SPEC'), '$VAR'('PRED'))), decontextualizedPredicate('$VAR'('SPEC')), 'BaseKB', vStrMon).
 9250assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('PRED')), different('$VAR'('PRED'), '$VAR'('SPEC')), genlInverse('$VAR'('SPEC'), '$VAR'('PRED')), predicateConventionMt('$VAR'('PRED'), '$VAR'('MT'))), predicateConventionMt('$VAR'('SPEC'), '$VAR'('MT')), 'BaseKB', vStrMon).
 9251assertedTinyKB_implies( and(decontextualizedPredicate('$VAR'('PRED')), different('$VAR'('PRED'), '$VAR'('SPEC')), genlInverse('$VAR'('SPEC'), '$VAR'('PRED'))), decontextualizedPredicate('$VAR'('SPEC')), 'BaseKB', vStrMon).
 9252assertedTinyKB_implies( and(decontextualizedCollection('$VAR'('COL')), collectionConventionMt('$VAR'('COL'), '$VAR'('MT'))), genlMt('BaseKB', '$VAR'('MT')), 'UniversalVocabularyMt', vStrMon).
 9253assertedTinyKB_implies( and(completelyEnumerableCollection('$VAR'('COL')), isa('$VAR'('INST'), '$VAR'('COL'))), knownSentence(isa('$VAR'('INST'), '$VAR'('COL'))), 'BaseKB', vStrDef).
 9254
 9255assertedTinyKB_implies( and(completelyDecidableCollection('$VAR'('COLL_2')), completelyDecidableCollection('$VAR'('COLL_1'))), meetsPragmaticRequirement('TheList'('$VAR'('COLL_2'), '$VAR'('COLL_1')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[extentCardinality, ['TheSetOf', '?OBJ', [and, [isa, '?OBJ', '$VAR'('COLL_1')], [not, [isa, '?OBJ', '$VAR'('COLL_2')]]]], 0]], [[subsetOf, '$VAR'('COLL_1'), '$VAR'('COLL_2')]]], 'BaseKB', ["?COLL-2", "?COLL-1"], [implies, [extentCardinality, ['TheSetOf', '?OBJ', [and, [isa, '?OBJ', '$VAR'('COLL_1')], [not, [isa, '?OBJ', '$VAR'('COLL_2')]]]], 0], [subsetOf, '$VAR'('COLL_1'), '$VAR'('COLL_2')]])), 'BaseKB', vStrDef).
 9256assertedTinyKB_implies( and(knownSentence(isa('$VAR'('ARG'), '$VAR'('COL'))), natFunction('$VAR'('NART'), '$VAR'('FUNC')), resultIsaArgIsa('$VAR'('FUNC'), '$VAR'('INT')), natArgument('$VAR'('NART'), '$VAR'('INT'), '$VAR'('ARG'))), isa('$VAR'('NART'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9257assertedTinyKB_not(and(isa('$VAR'('X'), 'TernaryPredicate'), arg4Isa('$VAR'('X'), '$VAR'('Y'))), 'BaseKB', vStrDef).
 9258
 9259assertedTinyKB_implies( and(knownSentence(genls('$VAR'('SPEC'), '$VAR'('GENL'))), genls('$VAR'('GENL'), '$VAR'('SPEC')), different('$VAR'('GENL'), '$VAR'('SPEC'))), coExtensional('$VAR'('GENL'), '$VAR'('SPEC')), 'BaseKB', vStrMon).
 9260assertedTinyKB_implies( and(knownSentence('$VAR'('FORMULA')), evaluate('$VAR'('FORMULAARGFN'), 'FormulaArgFn'(0, '$VAR'('FORMULA'))), evaluate('$VAR'('FORMULAARGFN_1'), 'FormulaArgFn'('$VAR'('ARG'), '$VAR'('FORMULA')))), assertedPredicateArg('$VAR'('FORMULAARGFN_1'), '$VAR'('ARG'), '$VAR'('FORMULAARGFN')), 'BaseKB', vStrMon).
 9261
 9262assertedTinyKB_implies( and(arity('$VAR'('PRED'), 2), requiredArg1Pred('$VAR'('COL1'), '$VAR'('PRED')), 'interArgIsa1-2'('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2'))), relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9263assertedTinyKB_implies( and(arity('$VAR'('PRED'), '$VAR'('M')), evaluate('$VAR'('M_1'), 'DifferenceFn'('$VAR'('M'), 1))), arity('FunctionToArg'('$VAR'('N'), '$VAR'('PRED')), '$VAR'('M_1')), 'BaseKB', vStrMon).
 9264assertedTinyKB_implies( and(arg5Isa('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 5, '$VAR'('REL'))), isa('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9265assertedTinyKB_implies( and(arg5Genl('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 5, '$VAR'('REL'))), genls('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9266assertedTinyKB_implies( and(arg4Isa('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 4, '$VAR'('REL'))), isa('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9267assertedTinyKB_implies( and(arg4Genl('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 4, '$VAR'('REL'))), genls('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9268assertedTinyKB_implies( and(arg4Format('$VAR'('GENLPRED'), 'SingleEntry'), different('$VAR'('GENLPRED'), '$VAR'('SPECPRED')), genlPreds('$VAR'('SPECPRED'), '$VAR'('GENLPRED'))), arg4Format('$VAR'('SPECPRED'), 'SingleEntry'), 'UniversalVocabularyMt', vStrMon).
 9269assertedTinyKB_implies( and(arg3Isa('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 3, '$VAR'('REL'))), isa('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9270assertedTinyKB_implies( and(arg3Genl('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 3, '$VAR'('REL'))), genls('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9271assertedTinyKB_implies( and(arg3Format('$VAR'('GENLPRED'), 'SingleEntry'), different('$VAR'('GENLPRED'), '$VAR'('SPECPRED')), genlPreds('$VAR'('SPECPRED'), '$VAR'('GENLPRED'))), arg3Format('$VAR'('SPECPRED'), 'SingleEntry'), 'UniversalVocabularyMt', vStrMon).
 9272assertedTinyKB_implies( and(arg2Isa('$VAR'('ROLE'), '$VAR'('TYPE')), requiredArg1Pred('$VAR'('SITTYPE'), '$VAR'('ROLE')), isa('$VAR'('SIT'), '$VAR'('SITTYPE'))), relationInstanceExists('$VAR'('ROLE'), '$VAR'('SIT'), '$VAR'('TYPE')), 'BaseKB', vStrDef).
 9273assertedTinyKB_implies( and(arg2Isa('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 2, '$VAR'('REL'))), isa('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9274assertedTinyKB_implies( and(arg2Isa('$VAR'('PRED'), '$VAR'('TYPE')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('ARG2'))), isa('$VAR'('ARG2'), '$VAR'('TYPE')), 'BaseKB', vStrMon).
 9275assertedTinyKB_implies( and(arg2Isa('$VAR'('PRED'), '$VAR'('COL')), relationExistsInstance('$VAR'('PRED'), '$VAR'('_DUMMY'), '$VAR'('THING'))), isa('$VAR'('THING'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9276assertedTinyKB_implies( and(arg2Genl('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 2, '$VAR'('REL'))), genls('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9277assertedTinyKB_implies( and(arg2Format('$VAR'('GENLPRED'), 'SingleEntry'), different('$VAR'('GENLPRED'), '$VAR'('SPECPRED')), genlPreds('$VAR'('SPECPRED'), '$VAR'('GENLPRED'))), arg2Format('$VAR'('SPECPRED'), 'SingleEntry'), 'UniversalVocabularyMt', vStrMon).
 9278assertedTinyKB_implies( and(arg1Isa('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 1, '$VAR'('REL'))), isa('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9279assertedTinyKB_implies( and(arg1Isa('$VAR'('PRED'), '$VAR'('TYPE')), relationInstanceAll('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('COL'))), isa('$VAR'('ARG1'), '$VAR'('TYPE')), 'BaseKB', vStrMon).
 9280assertedTinyKB_implies( and(arg1Isa('$VAR'('PRED'), '$VAR'('COL')), relationInstanceExists('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('_DUMMY'))), isa('$VAR'('THING'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9281assertedTinyKB_implies( and(arg1Isa('$VAR'('PRED'), '$VAR'('COL')), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('_DUMMY'))), isa('$VAR'('THING'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9282assertedTinyKB_implies( and(arg1Genl('$VAR'('REL'), '$VAR'('COLL')), admittedArgument('$VAR'('TERM'), 1, '$VAR'('REL'))), genls('$VAR'('TERM'), '$VAR'('COLL')), 'BaseKB', vStrDef).
 9283assertedTinyKB_implies( and(arg1Genl('$VAR'('PRED'), '$VAR'('COL2')), relationAllInstance('$VAR'('PRED'), '$VAR'('_ARG1'), '$VAR'('ARG2'))), isa('$VAR'('ARG2'), '$VAR'('COL2')), 'BaseKB', vStrMon).
 9284assertedTinyKB_implies( and(arg1Format('$VAR'('GENLPRED'), 'SingleEntry'), different('$VAR'('GENLPRED'), '$VAR'('SPECPRED')), genlPreds('$VAR'('SPECPRED'), '$VAR'('GENLPRED'))), arg1Format('$VAR'('SPECPRED'), 'SingleEntry'), 'UniversalVocabularyMt', vStrDef).
 9285assertedTinyKB_implies( and(admittedSentence('$VAR'('FORMULA')), integerBetween(1, '$VAR'('ARG'), '$VAR'('ARITY')), evaluate('$VAR'('RELATION'), 'FormulaArgFn'(0, '$VAR'('FORMULA'))), evaluate('$VAR'('ARITY'), 'FormulaArityFn'('$VAR'('FORMULA'))), evaluate('$VAR'('TERM'), 'FormulaArgFn'('$VAR'('ARG'), '$VAR'('FORMULA')))), admittedArgument('$VAR'('TERM'), '$VAR'('ARG'), '$VAR'('RELATION')), 'BaseKB', vStrDef).
 9286assertedTinyKB_implies( and(admittedArgument('$VAR'('B'), 1, natFunction), admittedArgument('$VAR'('A'), 2, natFunction)), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[operatorFormulas, '$VAR'('A'), '$VAR'('B')]], [[natFunction, '$VAR'('B'), '$VAR'('A')]]], 'BaseKB', ["?A", "?B"], [implies, [operatorFormulas, '$VAR'('A'), '$VAR'('B')], [natFunction, '$VAR'('B'), '$VAR'('A')]])), 'BaseKB', vStrDef).
 9287assertedTinyKB_implies( and(admittedArgument('$VAR'('A'), 1, isa), admittedArgument('$VAR'('B'), 2, isa)), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[elementOf, '$VAR'('A'), '$VAR'('B')]], [[isa, '$VAR'('A'), '$VAR'('B')]]], 'BaseKB', ["?A", "?B"], [implies, [elementOf, '$VAR'('A'), '$VAR'('B')], [isa, '$VAR'('A'), '$VAR'('B')]])), 'BaseKB', vStrDef).
 9288assertedTinyKB_implies( and(admittedArgument('$VAR'('A'), 1, genls), admittedArgument('$VAR'('B'), 2, genls)), meetsPragmaticRequirement('TheList'('$VAR'('A'), '$VAR'('B')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[subsetOf, '$VAR'('A'), '$VAR'('B')]], [[genls, '$VAR'('A'), '$VAR'('B')]]], 'BaseKB', ["?A", "?B"], [implies, [subsetOf, '$VAR'('A'), '$VAR'('B')], [genls, '$VAR'('A'), '$VAR'('B')]])), 'BaseKB', vStrDef).
 9289assertedTinyKB_implies( and('genls-SpecDenotesGenlInstances'('$VAR'('Q_COL'), '$VAR'('COL')), argQuotedIsa('$VAR'('RELN'), '$VAR'('N'), '$VAR'('Q_COL'))), argIsa('$VAR'('RELN'), '$VAR'('N'), '$VAR'('COL')), 'UniversalVocabularyMt', vStrDef).
 9290assertedTinyKB_implies( unknownSentence(thereExists('$VAR'('SOME_MT'), predicateConventionMt('$VAR'('SPEC'), '$VAR'('SOME_MT')))), meetsPragmaticRequirement('TheList'('$VAR'('PRED'), '$VAR'('SPEC'), '$VAR'('MT')), 'TINYKB-ASSERTION'(':TRUE-MON', [[[decontextualizedPredicate, '$VAR'('PRED')], [different, '$VAR'('PRED'), '$VAR'('SPEC')], [genlInverse, '$VAR'('SPEC'), '$VAR'('PRED')], [predicateConventionMt, '$VAR'('PRED'), '$VAR'('MT')]], [[predicateConventionMt, '$VAR'('SPEC'), '$VAR'('MT')]]], 'BaseKB', ["?PRED", "?SPEC", "?MT"], [implies, [and, [decontextualizedPredicate, '$VAR'('PRED')], [different, '$VAR'('PRED'), '$VAR'('SPEC')], [genlInverse, '$VAR'('SPEC'), '$VAR'('PRED')], [predicateConventionMt, '$VAR'('PRED'), '$VAR'('MT')]], [predicateConventionMt, '$VAR'('SPEC'), '$VAR'('MT')]])), 'BaseKB', vStrMon).
 9291assertedTinyKB_implies( unknownSentence(disjointWith('$VAR'('COL1'), '$VAR'('COL2'))), consistent(and(isa('$VAR'('THING'), '$VAR'('COL1')), isa('$VAR'('THING'), '$VAR'('COL2')))), 'BaseKB', vStrDef).
 9292assertedTinyKB_implies( trueSentence(thereExists('$VAR'('X'), and(isa('$VAR'('X'), '$VAR'('COL')), unknownSentence(holds('$VAR'('GENL_PRED'), '$VAR'('X')))))), meetsPragmaticRequirement('TheList'('$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED'), '$VAR'('COL')), 'TINYKB-ASSERTION'(':TRUE-DEF', [[[genlPreds, '$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')], [relationAll, '$VAR'('SPEC_PRED'), '$VAR'('COL')]], [[relationAll, '$VAR'('GENL_PRED'), '$VAR'('COL')]]], 'BaseKB', ["?SPEC-PRED", "?GENL-PRED", "?COL"], [implies, [and, [genlPreds, '$VAR'('SPEC_PRED'), '$VAR'('GENL_PRED')], [relationAll, '$VAR'('SPEC_PRED'), '$VAR'('COL')]], [relationAll, '$VAR'('GENL_PRED'), '$VAR'('COL')]])), 'BaseKB', vStrDef).
 9293assertedTinyKB_implies( trueSentence(forAll('$VAR'('ISA_CONSTR'), implies(argIsa('$VAR'('PRED'), '$VAR'('N'), '$VAR'('ISA_CONSTR')), genls('$VAR'('ISA_CONSTR'), 'CycLTerm')))), quotedArgument('$VAR'('PRED'), '$VAR'('N')), 'BaseKB', vStrDef).
 9294assertedTinyKB_implies( trueSentence(forAll('$VAR'('INST'), implies(isa('$VAR'('INST'), '$VAR'('COL')), admittedArgument('$VAR'('INST'), '$VAR'('NUM'), '$VAR'('RELN'))))), admittedAllArgument('$VAR'('COL'), '$VAR'('NUM'), '$VAR'('RELN')), 'UniversalVocabularyMt', vStrMon).
 9295assertedTinyKB_implies( trueSentence('$VAR'('SENT')), sentenceTruth('$VAR'('SENT'), 'True'), 'UniversalVocabularyMt', vStrMon).
 9296assertedTinyKB_implies( trueRule('$VAR'('TEMPLATE'), '$VAR'('FORMULA')), trueSentence('$VAR'('FORMULA')), 'BaseKB', vStrDef).
 9297assertedTinyKB_implies( termOfUnit('$VAR'('UNITPRODUCTFN'), 'UnitProductFn'('$VAR'('X'), '$VAR'('Y'))), multiplicationUnits('$VAR'('X'), '$VAR'('Y'), '$VAR'('UNITPRODUCTFN')), 'BaseKB', vStrDef).
 9298assertedTinyKB_implies( termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UOM1'), '$VAR'('UOM2'))), multiplicationUnits('$VAR'('PERFN'), '$VAR'('UOM2'), '$VAR'('UOM1')), 'BaseKB', vStrDef).
 9299assertedTinyKB_implies( termOfUnit('$VAR'('MEANINGINSYSTEMFN'), 'MeaningInSystemFn'('$VAR'('SYSTEM'), '$VAR'('STRING'))), synonymousExternalConcept('$VAR'('MEANINGINSYSTEMFN'), '$VAR'('SYSTEM'), '$VAR'('STRING')), 'BaseKB', vStrDef).
 9300assertedTinyKB_implies( subsetOf('$VAR'('A'), '$VAR'('B')), genls('$VAR'('A'), '$VAR'('B')), 'BaseKB', vStrDef).
 9301assertedTinyKB_implies( sentenceTruth('$VAR'('SENT'), 'True'), trueSentence('$VAR'('SENT')), 'UniversalVocabularyMt', vStrDef).
 9302assertedTinyKB_implies( relationInstanceExists('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COLL')), isa('RelationInstanceExistsFn'('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COLL')), '$VAR'('COLL')), 'BaseKB', vStrMon).
 9303assertedTinyKB_implies( relationInstanceExists('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COLL')), holds('$VAR'('PRED'), '$VAR'('THING'), 'RelationInstanceExistsFn'('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COLL'))), 'BaseKB', vStrMon).
 9304assertedTinyKB_implies( relationInstanceExists('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COL')), trueSentence(thereExists('$VAR'('INST'), and(isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('INST'))))), 'BaseKB', vStrDef).
 9305assertedTinyKB_implies( relationInstanceAll('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('COL')), trueSentence(implies(isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('PRED'), '$VAR'('THING'), '$VAR'('INST')))), 'BaseKB', vStrMon).
 9306assertedTinyKB_implies( relationInstanceAll('$VAR'('PRED'), '$VAR'('INSTANCE'), '$VAR'('COLLECTION')), conceptuallyRelated('$VAR'('COLLECTION'), '$VAR'('INSTANCE')), 'BaseKB', vStrMon).
 9307assertedTinyKB_implies( relationInstanceAll('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), requiredArg2Pred('$VAR'('COL2'), '$VAR'('PRED')), 'BaseKB', vStrDef).
 9308assertedTinyKB_implies( relationExistsInstance('$VAR'('PRED'), '$VAR'('COLL'), '$VAR'('THING')), isa('RelationExistsInstanceFn'('$VAR'('PRED'), '$VAR'('COLL'), '$VAR'('THING')), '$VAR'('COLL')), 'BaseKB', vStrMon).
 9309assertedTinyKB_implies( relationExistsInstance('$VAR'('PRED'), '$VAR'('COLL'), '$VAR'('THING')), holds('$VAR'('PRED'), 'RelationExistsInstanceFn'('$VAR'('PRED'), '$VAR'('COLL'), '$VAR'('THING')), '$VAR'('THING')), 'BaseKB', vStrMon).
 9310assertedTinyKB_implies( relationExistsInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING')), trueSentence(thereExists('$VAR'('INST'), and(isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('PRED'), '$VAR'('INST'), '$VAR'('THING'))))), 'BaseKB', vStrDef).
 9311assertedTinyKB_implies( relationExistsAll('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL')), relationExistsMinAll('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), 1), 'BaseKB', vStrDef).
 9312assertedTinyKB_implies( relationExistsAll('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2')), requiredArg2Pred('$VAR'('COL2'), '$VAR'('PRED')), 'BaseKB', vStrDef).
 9313assertedTinyKB_implies( relationAllInstance('$VAR'('PRED'), '$VAR'('COLLECTION'), '$VAR'('INSTANCE')), conceptuallyRelated('$VAR'('COLLECTION'), '$VAR'('INSTANCE')), 'BaseKB', vStrMon).
 9314assertedTinyKB_implies( relationAllInstance('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('_COL2')), requiredArg1Pred('$VAR'('COL1'), '$VAR'('PRED')), 'BaseKB', vStrMon).
 9315assertedTinyKB_implies( relationAllExists('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL')), relationAllExistsMin('$VAR'('SLOT'), '$VAR'('UNIV_COL'), '$VAR'('EXIST_COL'), 1), 'BaseKB', vStrDef).
 9316assertedTinyKB_implies( relationAllExists('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('_COL2')), requiredArg1Pred('$VAR'('COL1'), '$VAR'('PRED')), 'BaseKB', vStrDef).
 9317assertedTinyKB_implies( relationAll('$VAR'('PRED'), '$VAR'('COL')), trueSentence(implies(isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('PRED'), '$VAR'('INST')))), 'BaseKB', vStrMon).
 9318
 9319assertedTinyKB_not(and(trueSentence('$VAR'('VALUE')), equals('False', '$VAR'('VALUE'))), 'UniversalVocabularyMt', vStrDef).
 9320assertedTinyKB_not(and(trueSentence('$VAR'('SENT')), sentenceTruth('$VAR'('SENT'), 'False')), 'UniversalVocabularyMt', vStrDef).
 9321
 9322assertedTinyKB_not(and(relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING')), trueSentence(thereExists('$VAR'('INST'), and(isa('$VAR'('INST'), '$VAR'('COL')), not(holds('$VAR'('PRED'), '$VAR'('INST'), '$VAR'('THING'))))))), 'BaseKB', vStrDef).
 9323assertedTinyKB_not(and(relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING')), trueSentence(thereExists('$VAR'('COLINST'), and(isa('$VAR'('COLINST'), '$VAR'('COL')), not(holds('$VAR'('PRED'), '$VAR'('COLINST'), '$VAR'('THING'))))))), 'BaseKB', vStrDef).
 9324assertedTinyKB_not(and(relationAllExists('$VAR'('RELATION'), '$VAR'('COL1'), '$VAR'('COL2')), relationAllExistsCount('$VAR'('RELATION'), '$VAR'('COL1'), '$VAR'('COL2'), 0)), 'BaseKB', vStrDef).
 9325assertedTinyKB_not(and(quantitySubsumes('$VAR'('SUPER'), '$VAR'('SUB')), maxQuantValue('$VAR'('SUPER'), '$VAR'('SUPERMAX')), greaterThan('$VAR'('SUBMAX'), '$VAR'('SUPERMAX')), maxQuantValue('$VAR'('SUB'), '$VAR'('SUBMAX'))), 'BaseKB', vStrDef).
 9326assertedTinyKB_not(and(opaqueArgument('$VAR'('REL'), '$VAR'('N')), arity('$VAR'('REL'), '$VAR'('ARITY')), greaterThan('$VAR'('N'), '$VAR'('ARITY'))), 'BaseKB', vStrDef).
 9327
 9328assertedTinyKB_not(and(negationPreds('$VAR'('NEGPRED'), '$VAR'('PRED')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING')), trueSentence(thereExists('$VAR'('INST'), and(isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('NEGPRED'), '$VAR'('INST'), '$VAR'('THING')))))), 'BaseKB', vStrMon).
 9329assertedTinyKB_not(and(negationPreds('$VAR'('NEGPRED'), '$VAR'('PRED')), isa('$VAR'('INST'), '$VAR'('COL')), holds('$VAR'('NEGPRED'), '$VAR'('INST'), '$VAR'('THING')), relationAllInstance('$VAR'('PRED'), '$VAR'('COL'), '$VAR'('THING'))), 'BaseKB', vStrMon).
 9330assertedTinyKB_not(and(negationPreds('$VAR'('NEG_PRED'), '$VAR'('PRED')), holds('$VAR'('NEG_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'), '$VAR'('ARG5')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'), '$VAR'('ARG5'))), 'BaseKB', vStrMon).
 9331assertedTinyKB_not(and(negationPreds('$VAR'('NEG_PRED'), '$VAR'('PRED')), holds('$VAR'('NEG_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'), '$VAR'('ARG4'))), 'BaseKB', vStrMon).
 9332assertedTinyKB_not(and(negationPreds('$VAR'('NEG_PRED'), '$VAR'('PRED')), holds('$VAR'('NEG_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'), '$VAR'('ARG3'))), 'BaseKB', vStrMon).
 9333assertedTinyKB_not(and(negationPreds('$VAR'('NEG_PRED'), '$VAR'('PRED')), holds('$VAR'('NEG_PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2'))), 'BaseKB', vStrMon).
 9334assertedTinyKB_not(and(negationPreds('$VAR'('NEG_PRED'), '$VAR'('PRED')), holds('$VAR'('NEG_PRED'), '$VAR'('ARG1')), holds('$VAR'('PRED'), '$VAR'('ARG1'))), 'BaseKB', vStrMon).
 9335assertedTinyKB_not(and(negationInverse('$VAR'('BINPRED1'), '$VAR'('BINPRED2')), holds('$VAR'('BINPRED1'), '$VAR'('ARG1'), '$VAR'('ARG2')), holds('$VAR'('BINPRED2'), '$VAR'('ARG2'), '$VAR'('ARG1'))), 'BaseKB', vStrDef).
 9336assertedTinyKB_not(and(minQuantValue('$VAR'('SUPER'), '$VAR'('SUPERMIN')), quantitySubsumes('$VAR'('SUPER'), '$VAR'('SUB')), minQuantValue('$VAR'('SUB'), '$VAR'('SUBMIN')), greaterThan('$VAR'('SUPERMIN'), '$VAR'('SUBMIN'))), 'BaseKB', vStrDef).
 9337assertedTinyKB_not(and(minQuantValue('$VAR'('INTERVAL1'), '$VAR'('MIN1')), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), maxQuantValue('$VAR'('INTERVAL2'), '$VAR'('MAX2')), greaterThan('$VAR'('MIN1'), '$VAR'('MAX2'))), 'BaseKB', vStrDef).
 9338assertedTinyKB_not(and(microtheoryDesignationArgnum('$VAR'('RELN'), '$VAR'('NUM')), sentenceDesignationArgnum('$VAR'('RELN'), '$VAR'('NUM'))), 'BaseKB', vStrDef).
 9339assertedTinyKB_not(and(isa('$VAR'('REL'), 'PartiallyCommutativeRelation'), arity('$VAR'('REL'), 5), different('$VAR'('J'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgs('$VAR'('REL'), '$VAR'('J'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9340assertedTinyKB_not(and(isa('$VAR'('REL'), 'PartiallyCommutativeRelation'), arity('$VAR'('REL'), 4), different('$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgs('$VAR'('REL'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9341assertedTinyKB_not(and(isa('$VAR'('REL'), 'PartiallyCommutativeRelation'), arity('$VAR'('REL'), 3), different('$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgs('$VAR'('REL'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9342assertedTinyKB_not(and(isa('$VAR'('REL'), 'PartiallyCommutativeRelation'), arity('$VAR'('REL'), 2), different('$VAR'('M'), '$VAR'('N')), commutativeInArgs('$VAR'('REL'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9343assertedTinyKB_not(and(isa('$VAR'('PRED'), 'IrreflexiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('OBJ'), '$VAR'('OBJ'))), 'BaseKB', vStrMon).
 9344assertedTinyKB_not(and(isa('$VAR'('PRED'), 'IrreflexiveBinaryPredicate'), equals('$VAR'('OBJ1'), '$VAR'('OBJ2')), holds('$VAR'('PRED'), '$VAR'('OBJ1'), '$VAR'('OBJ2'))), 'BaseKB', vStrMon).
 9345assertedTinyKB_not(and(isa('$VAR'('PRED'), 'AsymmetricBinaryPredicate'), isa('$VAR'('PRED'), 'SymmetricBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('ANYTHING1'), '$VAR'('ANYTHING2'))), 'BaseKB', vStrMon).
 9346assertedTinyKB_not(and(isa('$VAR'('PRED'), 'AsymmetricBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG1'))), 'BaseKB', vStrMon).
 9347assertedTinyKB_not(and(isa('$VAR'('PRED'), 'AntiTransitiveBinaryPredicate'), isa('$VAR'('PRED'), 'TransitiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('_A'), '$VAR'('B')), holds('$VAR'('PRED'), '$VAR'('B'), '$VAR'('_C'))), 'BaseKB', vStrDef).
 9348assertedTinyKB_not(and(isa('$VAR'('PRED'), 'AntiTransitiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('X'), '$VAR'('Y')), holds('$VAR'('PRED'), '$VAR'('X'), '$VAR'('Z')), holds('$VAR'('PRED'), '$VAR'('Y'), '$VAR'('Z'))), 'BaseKB', vStrDef).
 9349assertedTinyKB_not(and(isa('$VAR'('PRED'), 'AntiSymmetricBinaryPredicate'), admittedArgument('$VAR'('ARG1'), 1, '$VAR'('PRED')), admittedArgument('$VAR'('ARG1'), 2, '$VAR'('PRED')), different('$VAR'('ARG1'), '$VAR'('ARG2')), holds('$VAR'('PRED'), '$VAR'('ARG2'), '$VAR'('ARG1')), holds('$VAR'('PRED'), '$VAR'('ARG1'), '$VAR'('ARG2')), admittedArgument('$VAR'('ARG2'), 1, '$VAR'('PRED')), admittedArgument('$VAR'('ARG2'), 2, '$VAR'('PRED'))), 'BaseKB', vStrDef).
 9350assertedTinyKB_not(and(isa('$VAR'('OBJ'), '$VAR'('COL1')), isa('$VAR'('OBJ'), '$VAR'('COL2')), genls('$VAR'('COL2'), '$VAR'('COL3')), disjointWith('$VAR'('COL1'), '$VAR'('COL3'))), 'BaseKB', vStrDef).
 9351assertedTinyKB_not(and(isa('$VAR'('OBJ'), '$VAR'('COL1')), isa('$VAR'('OBJ'), '$VAR'('COL2')), disjointWith('$VAR'('COL1'), '$VAR'('COL2'))), 'BaseKB', vStrMon).
 9352assertedTinyKB_not(and(isa('$VAR'('INST_1'), '$VAR'('COL1')), isa('$VAR'('INST_2A'), '$VAR'('COL2')), different('$VAR'('INST_2A'), '$VAR'('INST_2B')), isa('$VAR'('INST_2B'), '$VAR'('COL2')), holds('$VAR'('PRED'), '$VAR'('INST_1'), '$VAR'('INST_2B')), holds('$VAR'('PRED'), '$VAR'('INST_1'), '$VAR'('INST_2A')), relationAllExistsMax('$VAR'('PRED'), '$VAR'('COL1'), '$VAR'('COL2'), 1)), 'UniversalVocabularyMt', vStrMon).
 9353assertedTinyKB_not(and(isa('$VAR'('INST1'), '$VAR'('TYPE1')), isa('$VAR'('INST2'), '$VAR'('TYPE2')), holds('$VAR'('PRED'), '$VAR'('INST1'), '$VAR'('INST2')), relationAllExistsCount('$VAR'('PRED'), '$VAR'('TYPE1'), '$VAR'('TYPE2'), 0)), 'BaseKB', vStrDef).
 9354assertedTinyKB_not(and(holdsIn('$VAR'('TIME'), '$VAR'('PROP')), holdsIn('$VAR'('TIME'), not('$VAR'('PROP')))), 'BaseKB', vStrDef).
 9355assertedTinyKB_not(and(greaterThan('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2')), quantityIntersects('$VAR'('INTERVAL1'), '$VAR'('INTERVAL2'))), 'BaseKB', vStrDef).
 9356assertedTinyKB_not(and(genlPreds('$VAR'('SPEC'), '$VAR'('GENL')), arity('$VAR'('SPEC'), '$VAR'('SPEC_ARITY')), different('$VAR'('GENL_ARITY'), '$VAR'('SPEC_ARITY')), arity('$VAR'('GENL'), '$VAR'('GENL_ARITY'))), 'BaseKB', vStrMon).
 9357assertedTinyKB_not(and(disjointWith('$VAR'('COL1'), '$VAR'('COL2')), trueSentence(thereExists('$VAR'('THING'), and(isa('$VAR'('THING'), '$VAR'('COL1')), isa('$VAR'('THING'), '$VAR'('COL2')))))), 'BaseKB', vStrMon).
 9358assertedTinyKB_not(and(disjointWith('$VAR'('ARGTYPE1'), '$VAR'('ARGTYPE2')), argIsa('$VAR'('PRED'), '$VAR'('ARGNUM'), '$VAR'('ARGTYPE1')), argIsa('$VAR'('PRED'), '$VAR'('ARGNUM'), '$VAR'('ARGTYPE2'))), 'BaseKB', vStrMon).
 9359assertedTinyKB_not(and(differentSymbols('$VAR'('A'), '$VAR'('B')), equalSymbols('$VAR'('A'), '$VAR'('B'))), 'BaseKB', vStrMon).
 9360assertedTinyKB_not(and(different('$VAR'('THING1'), '$VAR'('THING2')), equals('$VAR'('THING1'), '$VAR'('THING2'))), 'BaseKB', vStrDef).
 9361assertedTinyKB_not(and(arity('$VAR'('REL'), 5), different('$VAR'('J'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgsAndRest('$VAR'('REL'), '$VAR'('J'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9362assertedTinyKB_not(and(arity('$VAR'('REL'), 4), different('$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgsAndRest('$VAR'('REL'), '$VAR'('K'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9363assertedTinyKB_not(and(arity('$VAR'('REL'), 3), different('$VAR'('L'), '$VAR'('M'), '$VAR'('N')), commutativeInArgsAndRest('$VAR'('REL'), '$VAR'('L'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9364assertedTinyKB_not(and(arity('$VAR'('REL'), 2), different('$VAR'('M'), '$VAR'('N')), commutativeInArgsAndRest('$VAR'('REL'), '$VAR'('M'), '$VAR'('N'))), 'BaseKB', vStrDef).
 9365assertedTinyKB_not(and(arg2Isa('$VAR'('PRED'), '$VAR'('COL1')), disjointWith('$VAR'('COL1'), '$VAR'('COL2')), isa('$VAR'('INST'), '$VAR'('COL2')), holds('$VAR'('PRED'), '$VAR'('_X'), '$VAR'('INST'))), 'BaseKB', vStrMon).
 9366assertedTinyKB_not(and(arg2Isa('$VAR'('PRED'), '$VAR'('ARG2ISA')), disjointWith('$VAR'('ARG2ISA'), '$VAR'('ARG2TYPE')), relationExistsAll('$VAR'('PRED'), '$VAR'('ARG1TYPE'), '$VAR'('ARG2TYPE'))), 'BaseKB', vStrMon).
 9367assertedTinyKB_not(and(arg2Isa('$VAR'('PRED'), '$VAR'('ARG2ISA')), disjointWith('$VAR'('ARG2ISA'), '$VAR'('ARG2TYPE')), relationAllExists('$VAR'('PRED'), '$VAR'('ARG1TYPE'), '$VAR'('ARG2TYPE'))), 'BaseKB', vStrMon).
 9368assertedTinyKB_not(and(arg2Genl('$VAR'('PRED'), '$VAR'('ARG2TYPE')), disjointWith('$VAR'('ARG2TYPE'), '$VAR'('GROUPMEMBERTYPE')), relationAllInstance('$VAR'('PRED'), '$VAR'('GROUPTYPE'), '$VAR'('GROUPMEMBERTYPE'))), 'BaseKB', vStrMon).
 9369assertedTinyKB_not(and(arg1Isa('$VAR'('PRED'), '$VAR'('ARG1ISA')), disjointWith('$VAR'('ARG1ISA'), '$VAR'('ARG1TYPE')), relationAllExists('$VAR'('PRED'), '$VAR'('ARG1TYPE'), '$VAR'('ARG2TYPE'))), 'BaseKB', vStrMon).
 9370
 9371exactlyAssertedEL_with_vars(collectionExpansion, 'TransitiveBinaryPredicate', implies(and(holds((':ARG1'), '$VAR'('X'), '$VAR'('Y')), holds((':ARG1'), '$VAR'('Y'), '$VAR'('Z'))), holds((':ARG1'), '$VAR'('X'), '$VAR'('Z'))), 'UniversalVocabularyMt', vStrDef).
 9372exactlyAssertedEL_with_vars(collectionExpansion, 'SymmetricBinaryPredicate', implies(holds((':ARG1'), '$VAR'('X'), '$VAR'('Y')), holds((':ARG1'), '$VAR'('Y'), '$VAR'('Z'))), 'UniversalVocabularyMt', vStrDef).
 9373exactlyAssertedEL_with_vars(collectionExpansion, 'ReflexiveBinaryPredicate', holds((':ARG1'), '$VAR'('X'), '$VAR'('X')), 'UniversalVocabularyMt', vStrDef).
 9374exactlyAssertedEL_with_vars(collectionExpansion, 'IrreflexiveBinaryPredicate', not(holds((':ARG1'), '$VAR'('X'), '$VAR'('X'))), 'UniversalVocabularyMt', vStrDef).
 9375exactlyAssertedEL_with_vars(collectionExpansion, 'AsymmetricBinaryPredicate', implies(holds((':ARG1'), '$VAR'('X'), '$VAR'('Y')), not(holds((':ARG1'), '$VAR'('Y'), '$VAR'('Z')))), 'UniversalVocabularyMt', vStrDef).
 9376
 9377exactlyAssertedEL_with_vars(expansion, requiredArg2Pred, implies(and(isa((':ARG2'), 'BinaryPredicate'), isa('$VAR'('INS_1'), (':ARG1'))), thereExists('$VAR'('INS'), holds((':ARG2'), '$VAR'('INS'), '$VAR'('INS_1')))), 'BaseKB', vStrDef).
 9378exactlyAssertedEL_with_vars(expansion, requiredArg1Pred, implies(and(isa((':ARG2'), 'BinaryPredicate'), isa('$VAR'('INS_1'), (':ARG1'))), thereExists('$VAR'('INS'), holds((':ARG2'), '$VAR'('INS_1'), '$VAR'('INS')))), 'BaseKB', vStrDef).
 9379exactlyAssertedEL_with_vars(expansion, relationInstanceExists, thereExists('$VAR'('ARG'), and(isa('$VAR'('ARG'), (':ARG3')), holds((':ARG1'), (':ARG2'), '$VAR'('ARG')))), 'BaseKB', vStrDef).
 9380exactlyAssertedEL_with_vars(expansion, relationInstanceAll, implies(isa('$VAR'('INS'), (':ARG3')), holds((':ARG1'), (':ARG2'), '$VAR'('INS'))), 'BaseKB', vStrMon).
 9381exactlyAssertedEL_with_vars(expansion, relationExistsMinAll, implies(isa('$VAR'('ARG2'), (':ARG3')), thereExistAtLeast((':ARG4'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), (':ARG2')), holds((':ARG1'), '$VAR'('ARG'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9382exactlyAssertedEL_with_vars(expansion, relationExistsMaxAll, implies(isa('$VAR'('ARG2'), (':ARG3')), thereExistAtMost((':ARG4'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), (':ARG2')), holds((':ARG1'), '$VAR'('ARG'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9383exactlyAssertedEL_with_vars(expansion, relationExistsInstance, thereExists('$VAR'('OBJ'), and(isa('$VAR'('OBJ'), (':ARG2')), holds((':ARG1'), '$VAR'('OBJ'), (':ARG3')))), 'BaseKB', vStrDef).
 9384exactlyAssertedEL_with_vars(expansion, relationExistsCountAll, implies(isa('$VAR'('ARG2'), (':ARG3')), thereExistExactly((':ARG4'), '$VAR'('ARG1'), and(isa('$VAR'('ARG1'), (':ARG2')), holds((':ARG1'), '$VAR'('ARG1'), '$VAR'('ARG2'))))), 'BaseKB', vStrDef).
 9385exactlyAssertedEL_with_vars(expansion, relationExistsAll, implies(isa('$VAR'('TERM'), (':ARG3')), holds((':ARG1'), 'RelationExistsAllFn'('$VAR'('TERM'), (':ARG1'), (':ARG2'), (':ARG3')), '$VAR'('TERM'))), 'BaseKB', vStrMon).
 9386exactlyAssertedEL_with_vars(expansion, relationAllInstance, implies(isa('$VAR'('INS'), (':ARG2')), holds((':ARG1'), '$VAR'('INS'), (':ARG3'))), 'BaseKB', vStrMon).
 9387exactlyAssertedEL_with_vars(expansion, relationAllExistsMin, implies(isa('$VAR'('ARG1'), (':ARG2')), thereExistAtLeast((':ARG4'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), (':ARG3')), holds((':ARG1'), '$VAR'('ARG1'), '$VAR'('ARG'))))), 'BaseKB', vStrDef).
 9388exactlyAssertedEL_with_vars(expansion, relationAllExistsMax, implies(isa('$VAR'('ARG1'), (':ARG2')), thereExistAtMost((':ARG4'), '$VAR'('ARG'), and(isa('$VAR'('ARG'), (':ARG3')), holds((':ARG1'), '$VAR'('ARG1'), '$VAR'('ARG'))))), 'BaseKB', vStrDef).
 9389exactlyAssertedEL_with_vars(expansion, relationAllExistsCount, implies(isa('$VAR'('TERM'), (':ARG2')), thereExistExactly((':ARG4'), '$VAR'('OTHER'), and(isa('$VAR'('OTHER'), (':ARG3')), holds((':ARG1'), '$VAR'('TERM'), '$VAR'('OTHER'))))), 'BaseKB', vStrDef).
 9390exactlyAssertedEL_with_vars(expansion, relationAllExists, implies(isa('$VAR'('TERM'), (':ARG2')), holds((':ARG1'), '$VAR'('TERM'), 'RelationAllExistsFn'('$VAR'('TERM'), (':ARG1'), (':ARG2'), (':ARG3')))), 'BaseKB', vStrMon).
 9391exactlyAssertedEL_with_vars(expansion, relationAll, implies(isa('$VAR'('OBJ'), (':ARG2')), holds((':ARG1'), '$VAR'('OBJ'))), 'BaseKB', vStrDef).
 9392exactlyAssertedEL_with_vars(expansion, negationInverse, not(and(holds((':ARG1'), '$VAR'('ARG1'), '$VAR'('ARG2')), holds((':ARG2'), '$VAR'('ARG2'), '$VAR'('ARG1')))), 'BaseKB', vStrDef).
 9393exactlyAssertedEL_with_vars(expansion, mtVisible, trueSubL('ExpandSubLFn'((':ARG1'), 'RELEVANT-MT?'('QUOTE'((':ARG1'))))), 'UniversalVocabularyMt', vStrMon).
 9394exactlyAssertedEL_with_vars(expansion, genlMt, implies(ist((':ARG2'), '$VAR'('ASSERTION')), ist((':ARG1'), '$VAR'('ASSERTION'))), 'BaseKB', vStrMon).
 9395exactlyAssertedEL_with_vars(expansion, genlInverse, implies(holds((':ARG1'), '$VAR'('ARG1'), '$VAR'('ARG2')), holds((':ARG2'), '$VAR'('ARG2'), '$VAR'('ARG1'))), 'BaseKB', vStrDef).
 9396exactlyAssertedEL_with_vars(expansion, equiv, and(implies((':ARG1'), (':ARG2')), implies((':ARG2'), (':ARG1'))), 'BaseKB', vStrDef).
 9397exactlyAssertedEL_with_vars(expansion, disjointWith, not(and(isa('$VAR'('OBJ'), (':ARG1')), isa('$VAR'('OBJ'), (':ARG2')))), 'BaseKB', vStrDef).
 9398exactlyAssertedEL_with_vars(expansion, 'Percent', 'QuotientFn'((':ARG1'), 100), 'UniversalVocabularyMt', vStrMon).
 9399exactlyAssertedEL_with_vars(expansion, 'interArgGenl1-2', implies(and(genls('$VAR'('INDEP_SPEC'), (':ARG2')), holds((':ARG1'), '$VAR'('INDEP_SPEC'), '$VAR'('DEP_SPEC'))), genls('$VAR'('DEP_SPEC'), (':ARG3'))), 'BaseKB', vStrDef).
 9400exactlyAssertedEL_with_vars(expansion, 'genls-SpecDenotesGenlInstances', implies(quotedIsa('$VAR'('OBJ'), (':ARG1')), isa('$VAR'('OBJ'), (':ARG2'))), 'UniversalVocabularyMt', vStrDef).
 9401exactlyAssertedEL_with_vars(expansion, 'genls-GenlDenotesSpecInstances', implies(isa('$VAR'('OBJ'), (':ARG1')), quotedIsa('$VAR'('OBJ'), (':ARG2'))), 'UniversalVocabularyMt', vStrDef).
 9402
 9403assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa1-3'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), dot_holds(['$VAR'('PRED'), '$VAR'('INDEP_INS'), '$VAR'('_ANY_ARG_2'), '$VAR'('DEP_INS')|'$VAR'('_ARGS')])), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9404assertedTinyKB_implies( and(isa('$VAR'('INDEP_INS'), '$VAR'('INDEP_COL')), 'interArgIsa1-2'('$VAR'('PRED'), '$VAR'('INDEP_COL'), '$VAR'('DEP_COL')), dot_holds(['$VAR'('PRED'), '$VAR'('INDEP_INS'), '$VAR'('DEP_INS')|'$VAR'('_ARGS')])), isa('$VAR'('DEP_INS'), '$VAR'('DEP_COL')), 'BaseKB', vStrDef).
 9405assertedTinyKB_implies( and(resultGenl('$VAR'('FUNC'), '$VAR'('COL')), equals('$VAR'('VALUE'), 'NART'(['$VAR'('FUNC')|'$VAR'('ARGS')]))), genls('$VAR'('VALUE'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9406assertedTinyKB_implies( genlMt('$VAR'('SPEC'), '$VAR'('GENL')), 'NART'('NART'(['MtUnionFn', '$VAR'('SPEC')|'$VAR'('OTHER_MTS')]), '$VAR'('GENL')), 'UniversalVocabularyMt', vStrDef).
 9407assertedTinyKB_implies( elementOf('$VAR'('MT_DIM'), 'NART'(['TheSet'|'$VAR'('MT_DIMS')])), genlMt('NART'(['MtSpace'|'$VAR'('MT_DIMS')]), '$VAR'('MT_DIM')), 'UniversalVocabularyMt', vStrDef).
 9408assertedTinyKB_implies( elementOf('$VAR'('A'), '$VAR'('B')), isa('$VAR'('A'), '$VAR'('B')), 'BaseKB', vStrDef).
 9409assertedTinyKB_implies( dot_holds([commutativeInArgs, '$VAR'('_PRED')|'$VAR'('ARGS')]), dot_holds([different|'$VAR'('ARGS')]), 'BaseKB', vStrMon).
 9410assertedTinyKB_implies( and(resultIsa('$VAR'('FUNC'), '$VAR'('COL')), equals('$VAR'('VALUE'), 'NART'(['$VAR'('FUNC')|'$VAR'('ARGS')]))), isa('$VAR'('VALUE'), '$VAR'('COL')), 'BaseKB', vStrMon).
 9411assertedTinyKB_implies( isa('$VAR'('UNIT'), 'UnitOfMeasure'), equals('NART'(['$VAR'('UNIT')|'$VAR'('ARGS')]), 'NART'(['$VAR'('UNIT'), 'NART'(['Unity'|'$VAR'('ARGS')])])), 'BaseKB', vStrDef).
 9412exactlyAssertedEL_with_vars(expansion, implies, or((':ARG2'), not((':ARG1'))), 'BaseKB', vStrDef).
 9413
 9414exactlyAssertedEL_with_vars(expansion, genlPreds, implies(dot_holds([(':ARG1'), '?ARGS']), dot_holds([(':ARG2'), '?ARGS'])), 'BaseKB', vStrDef).
 9415exactlyAssertedEL_with_vars(expansion, quotedIsa, isa('QuasiQuote'((':ARG1')), (':ARG2')), 'BaseKB', vStrDef).
 9416exactlyAssertedEL_with_vars(expansion, negationPreds, not(and(dot_holds([(':ARG1'), '?ARGS']), dot_holds([(':ARG2'), '?ARGS']))), 'BaseKB', vStrDef).
 9417exactlyAssertedEL_with_vars(expansion, xor, or(and((':ARG1'), not((':ARG2'))), and((':ARG2'), not((':ARG1')))), 'BaseKB', vStrDef).
 9418exactlyAssertedEL_with_vars(genlMt, 'NART'(['MtSpace'|'$VAR'('_MT_DIMS')]), 'UniversalVocabularyMt', 'UniversalVocabularyMt', vStrMon).
 9419assertedTinyKB_implies( ist('NART'(['MtSpace'|'$VAR'('OTHER_MT_DIMS')]), '$VAR'('SENTENCE')), ist('NART'(['MtSpace', '$VAR'('MT_DIM')|'$VAR'('OTHER_MT_DIMS')]), '$VAR'('SENTENCE')), 'UniversalVocabularyMt', vStrDef).
 9420assertedTinyKB_implies( ist('NART'(['MtSpace', '$VAR'('MT_DIM')|'$VAR'('OTHER_MT_DIMS')]), '$VAR'('SENTENCE')), ist('NART'(['MtSpace'|'$VAR'('OTHER_MT_DIMS')]), '$VAR'('SENTENCE')), 'UniversalVocabularyMt', vStrDef).
 9421assertedTinyKB_implies( and(evaluate('$VAR'('QUOTIENTFN'), 'QuotientFn'('NART'(['$VAR'('UNIT1')|'$VAR'('ARGS')]), 'NART'(['$VAR'('UNIT2'), 1]))), termOfUnit('$VAR'('PERFN'), 'PerFn'('$VAR'('UNIT1'), '$VAR'('UNIT2')))), equals('$VAR'('QUOTIENTFN'), 'NART'(['$VAR'('PERFN')|'$VAR'('ARGS')])), 'UniversalVocabularyMt', vStrMon).
 9422assertedTinyKB_implies( and(dot_holds(['$VAR'('SPEC')|'$VAR'('ARGS')]), genlPreds('$VAR'('SPEC'), '$VAR'('GENL'))), dot_holds(['$VAR'('GENL')|'$VAR'('ARGS')]), 'BaseKB', vStrDef).
 9423
 9424exactlyAssertedEL_with_vars(equals, 'TheEmptyList', 'TheList', 'BaseKB', vStrMon).
 9425exactlyAssertedEL_with_vars(equals, '$VAR'('X'), '$VAR'('X'), 'LogicalTruthMt', vStrDef).
 9426exactlyAssertedEL_with_vars(equals, '$VAR'('X'), '$VAR'('X'), 'BaseKB', vStrMon).
 9427exactlyAssertedEL_with_vars(equals, '$VAR'('NUM'), 'Unity'('$VAR'('NUM')), 'BaseKB', vStrDef).
 9428
 9429exactlyAssertedEL_with_vars(unitMultiplicationFactor, '$VAR'('UNIT'), '$VAR'('UNIT'), 1, 'BaseKB', vStrMon).
 9430
 9431exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg6Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 6, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 6, '$VAR'('COL')), arg6Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9432exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg5Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 5, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 5, '$VAR'('COL')), arg5Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9433exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg4Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 4, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 4, '$VAR'('COL')), arg4Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9434exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg3Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 3, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 3, '$VAR'('COL')), arg3Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9435exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg2Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 2, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 2, '$VAR'('COL')), arg2Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9436
 9437exactlyAssertedEL_with_vars(trueRule, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), and(implies(arg1Isa('$VAR'('RELN'), '$VAR'('COL')), argIsa('$VAR'('RELN'), 1, '$VAR'('COL'))), implies(argIsa('$VAR'('RELN'), 1, '$VAR'('COL')), arg1Isa('$VAR'('RELN'), '$VAR'('COL')))), 'UniversalVocabularyMt', vStrDef).
 9438exactlyAssertedEL_with_vars(termOfUnit, 'NART'(['CollectionRuleTemplateFn', 'HypotheticalContext']), 'CollectionRuleTemplateFn'('HypotheticalContext'), 'BaseKB', vStrMon).
 9439exactlyAssertedEL_with_vars(termOfUnit, 'NART'(['CollectionRuleTemplateFn', 'ArgIsaPredicate']), 'CollectionRuleTemplateFn'('ArgIsaPredicate'), 'BaseKB', vStrMon).
 9440exactlyAssertedEL_with_vars(subsetOf, 'TheEmptySet', '$VAR'('SET'), 'BaseKB', vStrMon).
 9441
 9442assertedTinyKB_TODO(genls, '$VAR'('X'), '$VAR'('X'), 'LogicalTruthMt', vStrMon).
 9443assertedTinyKB_TODO(or, trueSentence('$VAR'('SENT')), sentenceTruth('$VAR'('SENT'), 'False'), 'UniversalVocabularyMt', vStrMon).
 9444assertedTinyKB_TODO(or, different('$VAR'('THING1'), '$VAR'('THING2')), equals('$VAR'('THING1'), '$VAR'('THING2')), 'BaseKB', vStrDef).
 9445assertedTinyKB_TODO(implies, and(different('$VAR'('COL_1'), '$VAR'('COMMON_NEAR')), genls('$VAR'('COMMON_NEAR'), '$VAR'('COL_1')), genls('$VAR'('COMMON_NEAR'), '$VAR'('COL_2')), different('$VAR'('COL_2'), '$VAR'('COMMON_NEAR'))), or(nearestCommonSpecs('$VAR'('COL_1'), '$VAR'('COL_2'), '$VAR'('COMMON_NEAR')), elementOf('$VAR'('COMMON_NEAR'), 'TheSetOf'('$VAR'('COMMON_FARTHER'), thereExists('$VAR'('COMMON_FAR'), and(genls('$VAR'('COMMON_FAR'), '$VAR'('COL_1')), genls('$VAR'('COMMON_FAR'), '$VAR'('COL_2')), genls('$VAR'('COMMON_FARTHER'), '$VAR'('COMMON_FAR')), different('$VAR'('COL_1'), '$VAR'('COMMON_FAR')), different('$VAR'('COL_2'), '$VAR'('COMMON_FAR')), different('$VAR'('COMMON_FAR'), '$VAR'('COMMON_FARTHER'))))))), 'BaseKB', vStrDef).
 9446assertedTinyKB_TODO(implies, equals('True', '$VAR'('VALUE')), trueSentence('$VAR'('VALUE')), 'UniversalVocabularyMt', vStrDef).
 9447assertedTinyKB_TODO(implies, equals('$VAR'('X'), '$VAR'('Y')), equals('$VAR'('Y'), '$VAR'('X')), 'LogicalTruthMt', vStrMon).
 9448assertedTinyKB_TODO(implies, isa('$VAR'('OBJ_1'), '$VAR'('DIFF_NEAR')), or(elementOf('$VAR'('OBJ_2'), 'TheSetOf'('$VAR'('ITEM_1'), isa('$VAR'('ITEM_1'), '$VAR'('DIFF_NEAR')))), nearestDifferentIsa('$VAR'('OBJ_1'), '$VAR'('OBJ_2'), '$VAR'('DIFF_NEAR')), elementOf('$VAR'('DIFF_NEAR'), 'TheSetOf'('$VAR'('DIFF_FARTHER'), thereExists('$VAR'('DIFF_FAR'), and(isa('$VAR'('OBJ_1'), '$VAR'('DIFF_FAR')), genls('$VAR'('DIFF_FAR'), '$VAR'('DIFF_FARTHER')), different('$VAR'('DIFF_FAR'), '$VAR'('DIFF_FARTHER')), not(elementOf('$VAR'('OBJ_2'), 'TheSetOf'('$VAR'('ITEM_2'), isa('$VAR'('ITEM_2'), '$VAR'('DIFF_NEAR')))))))))), 'BaseKB', vStrMon).
 9449assertedTinyKB_TODO(implies, isa('$VAR'('OBJ'), '$VAR'('NEAR_COL')), or(nearestIsa('$VAR'('OBJ'), '$VAR'('NEAR_COL')), elementOf('$VAR'('NEAR_COL'), 'TheSetOf'('$VAR'('FARTHER_COL'), thereExists('$VAR'('FAR_COL'), and(isa('$VAR'('OBJ'), '$VAR'('FAR_COL')), genls('$VAR'('FAR_COL'), '$VAR'('FARTHER_COL')), different('$VAR'('FAR_COL'), '$VAR'('FARTHER_COL'))))))), 'BaseKB', vStrDef).
 9450assertedTinyKB_TODO(implies, isa('$VAR'('PRED'), 'ReflexiveBinaryPredicate'), holds('$VAR'('PRED'), '$VAR'('OBJ'), '$VAR'('OBJ')), 'BaseKB', vStrMon).
 9451assertedTinyKB_TODO(genls, 'CycLDenotationalTerm-Assertible', 'CycLExpression-Assertible', 'UniversalVocabularyMt', vStrDef).
 9452assertedTinyKB_TODO(implies, knownSentence('$VAR'('SENT')), quotedIsa('$VAR'('SENT'), 'CycLAssertion'), 'BaseKB', vStrDef).
 9453
 9454assertedTinyKB_InCode(coExtensional, 'CycLExpression', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 9455assertedTinyKB_InCode(isa, '$VAR'('OBJ'), 'Thing', 'UniversalVocabularyMt', vStrMon).
 9456assertedTinyKB_InCode(implies, isa('Quote'('EscapeQuote'('$VAR'('X'))), '$VAR'('COL')), quotedIsa('$VAR'('X'), '$VAR'('COL')), 'BaseKB', vStrDef).
 9457assertedTinyKB_InCode(genls, 'List', 'List', 'UniversalVocabularyMt', vStrMon).
 9458assertedTinyKB_InCode(relationAllExists, arity, tPred, 'PositiveInteger', 'BaseKB', vStrDef).
 9459
 9460assertedTinyKB_NEVER(genls, 'CharacterString', 'List', 'UniversalVocabularyMt', vStrDef).
 9461assertedTinyKB_NEVER(coExtensional, 'List', 'List', 'UniversalVocabularyMt', vStrMon).
 9462assertedTinyKB_NEVER(genls, 'SubLSExpression', 'CharacterString', 'UniversalVocabularyMt', vStrDef).
 9463assertedTinyKB_NEVER(genls, 'CycLExpression', 'CycLTerm', 'UniversalVocabularyMt', vStrDef).
 9464assertedTinyKB_NEVER(genls, 'CycLExpression', 'CycLTerm', 'CoreCycLMt', vStrDef).
 9465
 9466:- set_prolog_flag(do_renames,restore). 9467
 9468
 9469
 9470% :- fixup_exports.