1f% ===================================================================
    2% File 'parser_e2c.pl'
    3% Purpose: Attempto Controlled English to CycL conversions from SWI-Prolog  
    4% This implementation is an incomplete proxy for CycNL and likely will not work as well
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: 'parser_e2c.pl' 1.0.0
    8% Revision:  $Revision: 1.3 $
    9% Revised At:   $Date: 2002/06/06 15:43:15 $
   10% ===================================================================
   11
   12:-module(parser_e2c,[]
   13        % e2c/1,
   14         % e2c/2,
   15         % do_renames_e2c/2
   16         % idGen/1
   17         ).
   18
   19:- use_module(library(multimodal_dcg)).  
   20:- use_module(library(logicmoo_util_body_textstr)).   21:- use_module(library(logicmoo_util_body_reorder)).   22
   23
   24:- install_constant_renamer_until_eof.   25:- set_prolog_flag(do_renames_sumo,never).   26
   27
   28% expand_file_search_path(pldata(assertions),From),[module(baseKB),derived_from(From)]
   29
   30:- baseKB:kb_shared((('abbreviationString-PN'/2),
   31        ('adjSemTrans-Restricted'/5),
   32        ('countryName-LongForm'/2),
   33        ('countryName-ShortForm'/2),
   34        ('lightVerb-TransitiveSemTrans'/3),
   35        ('prepReln-Action'/4),
   36        ('prepReln-Object'/4),
   37        ('termPOS-Strings'/3),
   38        ('termStrings-GuessedFromName'/2),
   39        ('verbPrep-Passive'/3),
   40        ('verbPrep-Transitive'/3),
   41        ('verbPrep-TransitiveTemplate'/3),
   42        (abbreviationForCompoundString/4),
   43        (abbreviationForLexicalWord/3),
   44        (abbreviationForMultiWordString/4),
   45        (abbreviationForString/2),
   46        (acronymString/2),
   47        (adjSemTrans/4),
   48        (adjSemTransTemplate/3),
   49        (balanceBinding/2),
   50        (compoundSemTrans/5),
   51        (compoundString/4),
   52        (compoundVerbSemTrans/4),
   53        (denotation/4),
   54        (denotationPlaceholder/4),
   55        (denotationRelatedTo/4),
   56        (derivationalAffixBasePOS/2),
   57        (formerName/2),
   58        (genFormat/3),
   59        (genPhrase/4),
   60        (getSurfaceFromChars/3),
   61        (headMedialString/5),
   62        (hyphenString/4),
   63        (initialismString/2),
   64        (multiWordSemTrans/5),
   65        (multiWordString/4),
   66        (nicknames/2),
   67        (nonCompositionalVerbSemTrans/3),
   68        (nounPrep/3),
   69        (partOfSpeech/3),
   70        (phoneticVariantOfPrefix/3),
   71        (phoneticVariantOfSuffix/3),
   72        (posBaseForms/2),
   73        (posForms/2),
   74        (preferredGenUnit/3),
   75        (preferredNameString/2),
   76        (preferredTermStrings/2),
   77        (prepSemTrans/4),
   78        (prettyName/2),
   79       %(reduceWordList/2),
   80        (regularSuffix/3),
   81        (scientificName/2),
   82        (stringToWords/2),
   83        (termStrings/2),
   84        (unitOfMeasurePrefixString/2),
   85        (verbSemTrans/4),
   86       % cyckb_t_e2c/3,
   87       % cyckb_t_e2c/4,
   88        (verbSemTransTemplate/3))).   89
   90/*
   91:- require((
   92 stringArg/2,
   93 stringArgUC/3,
   94 balanceBinding/2,
   95 reduceWordList/2,
   96 strings_match/0,
   97 dictionary/3,
   98 cycStringToString/2,
   99 dcgStartsWith1/3,
  100 call_tabled/1,
  101 theText//1,
  102 reorderBody/2,
  103 reorderBody/3,
  104 reorderBody/4,
  105 t_l:noreorder/0,
  106 idioms/3,
  107 do_body_reorder/4,
  108 dstringify/2,
  109 module/2)).
  110*/
  111
  112:- baseKB:kb_shared(((
  113 abbreviationForString/2,
  114 abbreviationStringPn/2,
  115 acronymString/2,
  116 adjSemTrans/4,
  117 adjSemTransRestricted/5,
  118 adjSemTransTemplate/3,
  119 argIsa/3,
  120 compoundSemTrans/5,
  121 compoundString/4,
  122 compoundVerbSemTrans/4,
  123 countryNameLongform/2,
  124 countryNameShortform/2,
  125 denotation/4,
  126 denotationPlaceholder/4,
  127 denotationRelatedTo/4,
  128 derivationalAffixBasePOS/2,
  129 genFormat/3,
  130 genlPreds/2,
  131 genPhrase/4,
  132 getSurfaceFromChars/3,
  133 headMedialString/5,
  134 hyphenString/4,
  135 initialismString/2,
  136 lightVerbTransitivesemtrans/3,
  137 multiWordSemTrans/5,
  138 multiWordString/4,
  139 nameString/2,
  140 nicknames/2,
  141 nonCompositionalVerbSemTrans/3,
  142 nounPrep/3,
  143 phoneticVariantOfPrefix/3,
  144 phoneticVariantOfSuffix/3,
  145 posBaseForms/2,
  146 posForms/2,
  147 preferredGenUnit/3,
  148 preferredNameString/2,
  149 preferredTermStrings/2,
  150 prepRelnAction/4,
  151 prepRelnObject/4,
  152 prepSemTrans/4,
  153 prettyName/2,
  154 regularSuffix/3,
  155 scientificName/2,
  156 stringToWords/2,
  157 termPOSStrings/3,
  158 termStrings/2,
  159 termStringsGuessedfromname/2,
  160 unitOfMeasurePrefixString/2,
  161 verbPrepPassive/3,
  162 verbPrepTransitive/3,
  163 verbPrepTransitivetemplate/3,
  164 verbSemTrans/4,
  165 verbSemTransTemplate/3, 
  166 wnS/6))).  167
  168:- thread_local(t_l:noreorder/0).  169
  170disable_current_module_expansion(M):-
  171  system:forall((member(F/A,[term_expansion/2, term_expansion/4,goal_expansion/2, goal_expansion/4]),
  172            functor(P,F,A),
  173            predicate_property(M:P,clause_count(N)),
  174            N>0,
  175         \+ predicate_property(M:P,imported_from(_)),
  176         \+ predicate_property(M:P,static)),
  177     (( writeq(M:F/A),nl,M:multifile(M:F/A),
  178        M:dynamic(M:F/A),
  179        M:call(asserta,((P :- (!,fail))),Ref),
  180        call(asserta,on_end(erase(Ref)))))).
  181
  182:- if(current_prolog_flag(logicmoo_simplify_te,true)).  183:- disable_current_module_expansion(baseKB).  184:- forall(current_module(M),disable_current_module_expansion(M)).  185:- endif.  186
  187
  188:- (current_prolog_flag(qcompile,PrevValue)->true;PrevValue=false),
  189   call(assert,on_fin(set_prolog_flag(qcompile,PrevValue))),
  190   set_prolog_flag(qcompile,large).  191
  192
  193%:- set_prolog_flag(logicmoo_virtualize,true).
  194
  195
  196/*
  197:- (rtrace,kb_shared(prefixString/2)).
  198:-kb_shared('suffixString'/2).
  199:-kb_shared('variantOfSuffix'/2).
  200*/
  201
  202/*
  203:-dynamic('prefixString'/2).
  204:-dynamic('suffixString'/2).
  205:-dynamic('variantOfSuffix'/2).
  206*/
  207
  208% ==============================================================================
  209%:- kb_shared kbp_t_list_prehook/2.
  210
  211% do_renames_e2c(_,_):- !,fail.
  212do_renames_e2c(I,O):- is_ftVar(I),!,I=O.
  213do_renames_e2c(I,O):- atomic(I),do_renames(I,O),!.
  214do_renames_e2c(A,B):- compound_name_arguments(A,P,ARGS),maplist(do_renames_e2c,[P|ARGS],[T|L]),compound_name_arguments(B,T,L).
  215 
  216%:- rtrace.
  217cyckb_t_e2c(P,A,B):- !,call_u(t(P,A,B)).
  218%:- break.
  219cyckb_t_e2c(P,A,B):- maplist(do_renames_e2c,[P,A,B],[P1,A1,B1]),!,call_u(t(P1,A1,B1)).
  220cyckb_t_e2c(P,A,B,C):- !,call_u(t(P,A,B,C)).
  221cyckb_t_e2c(P,A,B,C):-  maplist(do_renames_e2c,[P,A,B,C],[P1,A1,B1,C1]),!,call_u(t(P1,A1,B1,C1)).
  222
  223% :- assert_until_eof((term_expansion(I,O):- ( I\=(:- _),do_renames_e2c(I,O)->I\=@=O))).
  224
  225% :- kb_shared thglobal:use_cyc_database/0.
  226
  227% :- ensure_loaded(logicmoo('logicmoo_util/logicmoo_util_all.pl')).
  228
  229:- meta_predicate do_dcg(?,?,?,?,?).  230:- meta_predicate isPOS(?,?,?,?,?).  231
  232% :- register_module_type(utility).
  233
  234:-thread_local t_l:allowTT/0.  235:-thread_local t_l:omitCycWordForms/0.  236
  237/*
  238
  239 (parse-a-question-completely "Did George W. Bush fall off a bicycle?" #$RKFParsingMt 
  240 '(:wff-check? t)
  241 )
  242
  243*/
  244
  245% idGen(X):-flag(idGen,X,X+1).
  246
  247%:- ensure_loaded(logicmoo(mpred/mpred_loader)).
  248
  249% :- file_begin(pl).
  250
  251% :- retractall(prevent_transform_moo_preds).
  252
  253% Semantic Interpretation
  254/* from Bratko chapter 17 page 455.
  255   This comes from Pereira and Warren paper, AI journal, 1980 */
  256
  257
  258% ===================================================================
  259
  260to_simple_wl(L,[L]):-var(L),!.
  261to_simple_wl([L|T],[L|T]):-!.
  262to_simple_wl(L,[L]):-!.
  263
  264:- export(lmfs:e2c_in_file/4).  265
  266lmfs:e2c_in_file(Head,Vars,In,Out):- 
  267     do_body_textstr(Head,Vars,In,Mid),
  268     do_body_reorder(Head,Vars,Mid,Out).     
  269
  270enable_e2c :- enable_in_file(e2c_in_file).
  271disable_e2 :- disable_in_file(e2c_in_file).
  272%:- enable_body_reorder.
  273:- use_module(library(logicmoo_util_body_textstr)).  274:- enable_body_textstr.  275% :- enable_e2c.
  276
  277
  278notground(V):-notrace(not(ground(V))).
  279term_atoms(Term,Vs):-findall(A,(arg(_,Term,A),non_blankWord(A),A\=@=[],atom(A)),Vs).
  280
  281words_append(L,R,LRS):-stringToWords(L,LS),stringToWords(R,RS),stringToWords(LRS,LRLIST),append(LS,RS,LRLIST).
  282words_concat(PreAffix,Affix,String):- reduceWordList(PreAffix,A),reduceWordList(Affix,B),reduceWordList(String,C),!,
  283   term_atoms(atom_concat(A,B,C),Vs),length(Vs,L),!,L > 1,atom_concat_er(A,B,C), !,non_blankWord(A),!,non_blankWord(B),non_blankWord(C).
  284
  285atom_concat_er(A,B,C):-atom(A),atom(B),atom_concat(Other,B,A),C=A,non_blankWord(Other),!.
  286atom_concat_er(A,B,C):-atom(A),atom(B),atom_concat(A,Other,B),C=B,non_blankWord(Other),!.
  287atom_concat_er(A,B,C):-atom(A),atom(B),atom_concat(A,B,C),!.
  288
  289
  290get_pl_type(Term,var):-var(Term),!.
  291get_pl_type([],list(nil)):-!.
  292get_pl_type(Term,atom):-atom(Term),!.
  293get_pl_type(Term,string):-string(Term),!.
  294get_pl_type(Term,number(int)):-integer(Term),!.
  295get_pl_type(Term,number(float)):-float(Term),!.
  296get_pl_type(Term,number(other)):-number(Term),!.
  297get_pl_type(List,list(proper)):-is_list(List),!.
  298get_pl_type([_|_],list(improper)):-!.
  299get_pl_type(C,compound(F,A)):-functor(C,F,A).
  300
  301:-dynamic(textCached/2).  302
  303
  304:- include(pldata(posm_cached_data)).  305
  306% :- break.
  307
  308/*
  309'nonCompositionalVerbSemTrans'('End-TheWord', 'Agreement', ['and', ['isa', ':ACTION', 'EndingAnAgreement'], ['performedBy', ':ACTION', ':SUBJECT'], ['objectActedOn', ':ACTION', ':OBJECT']]).
  310
  311'lightVerb-TransitiveSemTrans'('Do-TheWord', 'CommercialActivity', ['and', ['isa', ':ACTION', 'CommercialActivity'], ['performedBy', ':ACTION', ':SUBJECT']]).
  312'multiWordStringDenotesArgInReln'([service], 'Provide-TheWord', 'AgentiveNoun', 'providerOfService', 2).
  313'nounSemTrans'('Hire-TheWord', 0, 'RegularNounFrame', ['and', ['isa', '?HIRE', 'EmployeeHiring'], ['objectActedOn', '?HIRE', ':NOUN']]).
  314'multiWordStringDenotesArgInReln'([service], 'Provide-TheWord', 'AgentiveNoun', 'providerOfService', 2).
  315'headMedialString'([intended], 'Recipient-TheWord', [of, communication], 'SimpleNoun', 'communicationTarget').
  316'agentiveNounSemTrans'('Emit-TheWord', 0, 'RegularNounFrame', ['emitter', '?X', ':NOUN']).
  317'adjSemTrans'('Cloud-TheWord', 0, 'RegularAdjFrame', ['weather', ':NOUN', 'Cloudy']).
  318'relationIndicators'('abbreviationForMultiWordString', 'Form-TheWord', 'Verb').
  319%'genNatTerm-compoundString'('TransportViaFn', 'Transport-TheWord', [via], 'MassNoun', 'singular').
  320%'genTemplate'('transferredThing', ['ConcatenatePhrasesFn', ['TermParaphraseFn-NP', ':ARG2'], ['BestHeadVerbForInitialSubjectFn', 'Be-TheWord'], ['BestNLPhraseOfStringFn', 'transferred in'], ['TermParaphraseFn-NP', ':ARG1']]).
  321%'lightVerb-TransitiveSemTrans'('Do-TheWord', 'CommercialActivity', ['and', ['isa', ':ACTION', 'CommercialActivity'], ['performedBy', ':ACTION', ':SUBJECT']]).
  322%'genTemplate-Constrained'('isa', ['quotedCollection', ':ARG2'], ['NPIsNP-NLSentenceFn', ['BestCycLPhraseFn', ':ARG1'], ['BestDetNbarFn-Indefinite', ['TermParaphraseFn', ':ARG2']]]).
  323
  324*/
  325:-dynamic(e2c_result/1).  326:-export(e2c_result/1).  327:-export((dm1/0,dm2/0,dm3/0)).  328
  329dm1:-
  330  % mmake,
  331   e2c("I am happy when I am seeing two books sitting on a shelf",F),portray_clause(F),
  332   forall(clause(e2c_result(Text),O),retractall((e2c_result(Text):-O))),
  333   forall(descriptionTest(_,Texts),forall(member(Text,Texts),doE2CTest(Text))),
  334   findall(((was(LEN,TEXT):-PROPS)),(is_wordage_cache(TEXT, wordage(_,PROPS)),length(PROPS,LEN)),LIST),sort(LIST,SET),reverse(SET,RSET),
  335   forall(member(R,RSET),portray_clause(R)).
  336
  337doE2CTest(Text):- atomic(Text),atom_contains(Text,'  '),!.
  338doE2CTest(Text):- clause(e2c_result(Text),_),!.
  339doE2CTest(Text):- e2c(Text,F),call(asserta,(e2c_result(Text):- F)),portray_clause(F),!.
  340
  341% dm1:-e2c("I"),e2c("I am happy"),e2c("I saw wood"),e2c("I see two books"), e2c("I see two books sitting on a shelf").
  342dm2:-e2c("AnyTemplate1 affects the NPTemplate2").
  343dm3:-e2c("AnyTemplate1 at AnyTemplate2").
  344
  345mostSpec(TTT,'NLWordForm',TTT).
  346mostSpec(_TTT,TT,TT).
  347
  348nodeTrans(v,'Verb').
  349nodeTrans(a,'Adjective').
  350nodeTrans(n,'Noun').
  351nodeTrans(p,'Pronoun').
  352nodeTrans(pn,'ProperNoun').
  353nodeTrans('-','NLWordForm').
  354nodeTrans(np,'NounPhrase').
  355nodeTrans(v,'Verb').
  356nodeTrans(vp,'VerbPhrase').
  357nodeTrans(state,'TemporallyExistingThing').
  358nodeTrans(property,'Role').
  359nodeTrans(event,'Situation').
  360nodeTrans(action,'Action').
  361nodeTrans(thing,'SpatialThing').
  362nodeTrans(person,'Person').
  363nodeTrans(location,'SubcollectionOfWithRelationFromTypeFn'('EnduringThing-Localized',toLocation,'Translocation')).
  364nodeTrans(destination,'Location-Underspecified').
  365
  366
  367nodeTrans(ss,'TheSentenceSubject').
  368nodeTrans(pp,'PrepositionalPhrase').
  369
  370nodeTrans(s,'NLSentence').
  371nodeTrans(whnp,'WHPronoun').
  372%:- rtrace.
  373nodeTrans(P,S):-dstringify(P,S),!.
  374nodeTrans(P,string([P])).
 phrase(:RuleSet, ?List)
 phrase(:RuleSet, ?List, ?Rest)
Interface to DCGs
  382/*
  383:- meta_predicate
  384	phrase_orig(//, ?),
  385	phrase_orig(//, ?, ?).
  386:- noprofile((phrase_orig/2,
  387	      phrase_orig/3)).
  388
  389phrase_orig(RuleSet, Input) :-
  390	phrase(RuleSet, Input, []).
  391phrase_orig(RuleSet, Input, Rest) :-
  392	phrase_input(Input),
  393	phrase_input(Rest),
  394	(   strip_module(RuleSet, M, Plain),
  395	    nonvar(Plain),
  396	    dcg_special(Plain)
  397	->  dcg_body(Plain, _, q(M,M,_), S0, S, Body, _),
  398	    Input = S0, Rest = S,
  399	    call(M:Body)
  400	;   call(RuleSet, Input, Rest)
  401	).
  402*/
  403
  404% ===================================================================
  405% posm_cached(CycWord, String,POS,Form,CycL)
  406:-dynamic lex/3,  lexMap/3.  407%:-at_initialization(convertCycKb).
  408:-dynamic(posm_cached).  409:-dynamic(posm_cached/5).  410:-dynamic(real_posm_cached/5).  411:-dynamic(real_posm_cachedTT/5).  412
  413dont_cache.
  414posm_cached.
  415
  416posm_cached(CycWord,String,POS,Form,CycL):-posm_c_gen(String,POS,Form,CycL),fillInPosAndForm(String,CycWord,Form,POS).
  417
  418% ===================================================================
  419
  420% :- enable_body_textstr.
  421% :- enable_body_reorder.
  422
  423% ============================================================================
  424% posMeans
  425% ============================================================================
  426
  427posMeans(String,POS,Form,CycL):- dont_cache,!, posm_c_gen( String,POS,Form,CycL).
  428posMeans(String,POS,Form,CycL):- posm_cached,!, posm_cached(_CycWord,String,POS,Form,CycL).
  429
  430
  431posMeans(String,POS,Form,CycL):-
  432      cache_the_posms,
  433      call(asserta,posm_cached),
  434      posMeans(String,POS,Form,CycL).
  435
  436
  437:-export(cache_the_posms/0).  438cache_the_posms:-!.
  439cache_the_posms:- t_l:noreorder,
  440 locally(thglobal:use_cyc_database,
  441     (retractall(posm_cached(_CW, _Phrase,POS, _Form, _CycL)),
  442      posm_c_gen( String,POS,Form,CycL),
  443      push_to_cache(posm_c_gen( String,POS,Form,CycL)), 
  444      fail)).
  445   
  446cache_the_posms:-!.
  447
  448
  449push_to_cache(posm_c_gen(String,POS,Form,CycL)):- CycWord = _ ,
  450   once((correctArgIsas(posm_cached(CycWord,String,POS,Form,CycL),vv('CycWord','CharacterString','POS','Form','CycL'),Out),
  451      (clause(Out,true);(dmsg(Out),assert_if_new(Out))))).  
  452
  453correctArgIsas(posm_cached(CycWord,String,POS,Form,CycL), _ ,posm_cached(CycWord,String,POS,Form,CycL)):- stringToWords(String,String),!.
  454correctArgIsas(X, _ ,X).
  455% ============================================================================
  456% General Parts Of Speech and Meanings
  457% ============================================================================
  458
  459:-disable_body_textstr.  460% :- enable_body_textstr.
  461
  462multiStringMatch([W|List],[W|_]):-is_list(List),!.
  463multiStringMatch(W,[W|_]):-atom(W),!.
  464multiStringMatch([W|_],[W|_]):-atom(W),!.
  465multiStringMatch([W|_],[W|_]).
  466multiStringMatch(W,[W|_]).
  467
  468
  469% ============================================================================
  470% POSM_GEN_CACHE MULTI
  471% ============================================================================
  472posm_c_gen_multi(String,POS,Form,CycL):-no_repeats(posm_c_gen_multi_0(String,POS,Form,CycL)).
  473
  474
  475%'multiWordString'([health, care], 'Organize-TheWord', 'SimpleNoun', 'MedicalCareOrganization').
  476posm_c_gen_multi_0(String,POS,Form,CycL):- 
  477   reorderBody('multiWordString'(Words, CycWord,POS, CycL), fillInPosAndForm(Eng,CycWord,Form,POS), String^words_append(Words,Eng,String)).
  478
  479%'genPhrase'('MedicalCareProvider', 'AgentiveNoun', 'agentive-Sg', [health, care, provider]).
  480posm_c_gen_multi_0( String,POS,Form,CycL):- 'genPhrase'(CycL,POS,Form, String).
  481
  482%'compoundString'('Movement-TheWord', [of, fluid], 'MassNoun', 'FluidFlowEvent').
  483posm_c_gen_multi_0( String,POS,Form,CycL):- reorderBody('compoundString'(CycWord,Words,POS, CycL),Eng^fillInPosAndForm(Eng,CycWord,Form,POS),String^words_append(Eng,Words,String)).
  484
  485%'prepCollocation'('Beset-TheWord', 'Adjective', 'By-TheWord').      
  486posm_c_gen_multi_0( String,POS,Form2,'PrepCollocationFn'(CycWord1,POS,CycWord2)):- 
  487      reorderBody(POS^'prepCollocation'(CycWord1,POS, CycWord2),
  488	 stringToCycWord(Eng1,CycWord1),Form2^meetsForm(Eng2,CycWord2,Form2), String^words_append(Eng1,Eng2,String)).
  489
  490%'headMedialString'([dimensionless], 'Unit-TheWord', [of, measure], 'SimpleNoun', 'DimensionlessUnitOfMeasure').
  491posm_c_gen_multi_0( String,POS,Form,CycL):- reorderBody('headMedialString'(WordsBef,CycWord,WordsAft,POS, CycL),
  492	 fillInPosAndForm(Eng,CycWord,Form,POS),PhrasingLeft^words_append(WordsBef,Eng,PhrasingLeft),String^words_append(PhrasingLeft,WordsAft,String)).
  493
  494
  495% ============================================================================
  496% POSM_GEN_CACHE PLUS MULTI
  497% ============================================================================
  498
  499%TODO 'abbreviationForString'([scatology], [scat]).  
  500%TODO 'abbreviationForMultiWordString'([political], 'Science-TheWord', 'massNumber', [poli, sci]).
  501%TODO 'abbreviationForLexicalWord'('Kilogram-TheWord', 'singular', [kg]).
  502
  503
  504%'initialismString'('CodeOfConduct', [coc]).
  505posm_c_gen( StrVar,'SimpleNoun',normal,Proper) :- 
  506  stringArgUC(StrVar,CycStr,
  507      (('initialismString'(Proper,CycStr);
  508      'formerName'(Proper, CycStr);
  509      'scientificName'(Proper, CycStr);
  510      'termStrings-GuessedFromName'(Proper, CycStr);
  511      'nameString'(Proper, CycStr)))).
  512
  513%'abbreviationString-PN'('India', ['IND']).
  514posm_c_gen( StrVar,'ProperNoun',normal,Proper) :- 
  515  stringArgUC(StrVar,CycStr,
  516      (('initialismString'(Proper,CycStr);
  517      'abbreviationString-PN'(Proper, CycStr);
  518      'preferredNameString'(Proper, CycStr);
  519      'countryName-LongForm'(Proper, CycStr);
  520      'countryName-ShortForm'(Proper, CycStr)))).
  521
  522posm_c_gen(String,POS,Form,CycL):- nonvar(String), String=[_|_],!,posm_c_gen_multi(String,POS,Form,CycL).
  523
  524posm_c_gen(Eng,POS,Form,CycL):-posm_c_gen_unify(_CycWord,Eng,POS,Form,CycL).
  525
  526posm_c_gen_unify(CycWord,Eng,POS,Form,CycL):- cwposm_build(CycWord,POS,CycL),
  527   ignore((var(Form)->meetsForm(Eng,CycWord,Form);true)),
  528   once(meetsPos(Eng,CycWord,POS);((var(Eng)->stringToCycWord_0(Eng,CycWord);fail))).
  529   
  530% posm_c_gen( Eng,POS,Form,CycL):-posTT(CycWord,Eng,POS,Form),tthold('denotation',CycWord,POS, _Num, CycL).
  531
  532% ============================================================================
  533% POSM_GEN_CACHE CYCWORDS
  534% ============================================================================
  535
  536%'denotation'('Capacity-TheWord', 'SimpleNoun', 0, 'Volume').
  537cwposm_build(CycWord, POS,CycL):-'denotation'(CycWord,POS, _Num, CycL).
  538
  539%'preferredGenUnit'('on-Physical', 'Preposition-Directional-Telic', 'On-TheWord').
  540cwposm_build(CycWord, POS,CycL):-'preferredGenUnit'(CycL,POS, CycWord).
  541
  542%'denotationRelatedTo'('Can-TheWord', 'Verb', 0, 'PreservingFood').
  543%cwposm_build(CycWord, POS,'DenotationRelatedToFn'(CycL)):-'denotationRelatedTo'(CycWord,POS, _ , CycL).
  544cwposm_build(CycWord, POS,CycL):-'denotationRelatedTo'(CycWord,POS, _ , CycL).
  545
  546cwposm_build(CycWord,_MISSING_POS, meaningOfWord(CycWord)):-
  547   not('denotation'(CycWord, _ , _ , CycL)),
  548  not('denotationRelatedTo'(CycWord, _ , _ , CycL)), not('preferredGenUnit'(CycL, _ , CycWord)).
  549   
  550%'relationIndicators'('catalyst', 'Catalyst-TheWord', 'Verb').
  551
  552%'lex'(Form, CycWord, String):- ttholds('TT-lex',Form, CycWord, String).
  553%'lexMap'(PosForms, CycWord,POS):- ttholds('TT-lexMap',PosForms, CycWord,POS).
  554
  555
  556
  557% 'prepCollocation'('Beset-TheWord', 'Adjective', 'By-TheWord').
  558posTT(_CycWord, _Phrase, _POS, _Form:_PosForms):- fail.
  559     % 'TT-lex'(Form, CycWord, String),not('lex'(_ , _ , String)),
  560     %  'TT-lexMap'(PosForms, CycWord,POS).
  561
  562%'termStrings-GuessedFromName'('GenlsFormat', 'Genls Format').
  563%   'nounPrep'('Offspring-TheWord', 'Of-TheWord', ['children', ':NOUN', ':OBLIQUE-OBJECT']),
  564
  565
  566
  567%:-disable_body_textstr.
  568% % :- enable_body_textstr.
  569
  570:- listing(posm_c_gen/4).  571
  572% ==========================================================
  573% String FORM and POS DCG
  574% ==========================================================
  575isForm(Form) --> isForm(Form,_).
  576isForm(Form,CycWord) --> isForm(Form,CycWord,_).
  577isForm(Form,CycWord,[String]) --> theText([String]),{notrace(meetsForm(String,CycWord,Form)),!}.
  578isForm(Form,CycWord,[S,W|String]) --> theText([S,W|String]),{notrace(meetsForm([S,W|String],CycWord, Form))},theText(String).
  579
  580
  581isPOS(POS) --> isPOS(POS,_, _).
  582isPOS(POS,CycWord) --> isPOS(POS,CycWord, _).
  583isPOS(POS,CycWord,[String]) --> theText([String]),{notrace(meetsPos([String],CycWord,POS))}.
  584isPOS(POS,CycWord,[S,W|String]) --> theText([S,W]),{notrace(meetsPos([S,W|String],CycWord,POS))},theText(String).
  585
  586
  587theGenPhraseTemplate(Template,CycL)--> {!, fail, dmsg(warn(phraseToTemplate(Template,CycL))),!,fail }.
  588
  589
  590pos_cycl(POS,CycL) --> {'genPhrase'(CycL,POS,_Form,Template)},theGenPhraseTemplate(Template,CycL).
  591
  592pos_cycl(POS,CycL) --> {'termPOS-Strings'(CycL,POS,String)},theText(String).
  593
  594pos_cycl(POS,CycL) --> isCycWord(CycWord), {'compoundString'(CycWord,String,POS,CycL)}, theText(String).
  595
  596pos_cycl(POS,CycL) --> theText([S]),{'multiWordString'([S|String], CycWord,POS,CycL)}, theText(String), isCycWord(CycWord).
  597
  598pos_cycl(POS,CycL) --> theText([S]),{'headMedialString'([S|String], CycWord,POS,Right,CycL)}, theText(String),isCycWord(CycWord), theText(Right).
  599
  600pos_cycl(POS,CycL) -->  theText([String]), {concat_atom([Left,Right],'-',String), 'hyphenString'([Left], RightWord,POS,CycL), phrase(isCycWord(RightWord),[Right])}.
  601
  602
  603% ==========================================================
  604% PhraseType / POS
  605% ==========================================================
  606
  607goodStart(verb_phrase,'Verb').
  608goodStart(verb_phrase,'BeAux').
  609
  610goodStart(noun_phrase,'Adjective').
  611goodStart(noun_phrase,'Determiner').
  612goodStart(noun_phrase,'Noun').
  613goodStart(noun_phrase,'Pronoun').
  614goodStart(noun_phrase,'SubjectPronoun').
  615
  616canStart(PhraseType,POS):-goodStart(PhraseType,POS),!.
  617
  618cantStart(PhraseType,POS):-canStart(PhraseType,POS),!,fail.
  619cantStart(PhraseType,POS):-goodStart(OtherPhraseType,POS),OtherPhraseType\=@=PhraseType,!.
  620cantStart(PhraseType,POS):-dmsg(cantStart(PhraseType,POS)),!.
  621
  622% ==========================================================
  623% String / Word
  624% ==========================================================
  625
  626% TODO  cycWordForISA
  627cycWordForISA(_CycWord,_EventIsa):-fail.  
  628
  629genlPreds_different(Child,Form):-genlPreds(Child,Form), Child\=@=Form.
  630
  631% peace atal beh - 695-1297
  632%isCycWord(CycWord) --> {var(CycWord),!,trace}.
  633isCycWord(CycWord) --> {notrace(stringToCycWord(String,CycWord))},literal(String).
  634
  635
  636% ==========================================================
  637% meetsPos
  638% ==========================================================
  639meetsPos(String,CycWord,POS):-  sanify_string(String,Sane),no_repeats(meetsPos_0(Sane,CycWord,POS)).
  640
  641meetsPos_0(String,CycWord,POS):- stack_check,one_must(meetsPos_1(String,CycWord,POS),
  642     one_must(meetsPos_2(String,CycWord,POS),
  643     one_must(meetsPos_3(String,CycWord,POS),
  644     one_must(meetsPos_4(String,CycWord,POS),
  645     meetsPos_5(String,CycWord,POS))))).
  646meetsPos_0(_String,_CycWord,POS):- var(POS),!,fail.
  647meetsPos_0(String,CycWord,FormNotPOS):- is_speechPartPred_any(FormNotPOS),!,meetsForm(String,CycWord,FormNotPOS).
  648meetsPos_0(String,CycWord,POS):-'genls'(Child,POS),Child\=@=POS, meetsPos_0(String,CycWord,Child).
  649
  650meetsPos_1(String,CycWord,POS):- has_wordage(String),!,is_wordage_prop(String, pos(_, CycWord, POS)).
  651
  652meetsPos_2(String,CycWord,POS):- stringArgUC(String,CycString,'partOfSpeech'(CycWord,POS,CycString)).
  653meetsPos_2(String,CycWord,POS):- reorderBody(meetsForm(String,CycWord,Form),POS^speechPartPreds_transitive(POS, Form)).
  654
  655meetsPos_3([String],CycWord,POS):- atom(String),stringAtomToPOS([String],CycWord,POS).
  656
  657meetsPos_4(String,CycWord,POS):- locally(t_l:allowTT,meetsPos_2(String,CycWord,POS)).
  658
  659meetsPos_5(String,CycWord,POS):-  member(POS,['Noun','Adjective','Verb','Adverb']), stringArg(String,'wnS'(CycWord, _ , String,POS, _ , _)).
  660meetsPos_5(String,CycWord,'Adjective'):- 'wnS'(CycWord, _ , String, 'AdjectiveSatellite', _ , _). 
  661 
  662
  663stringAtomToPOS(String,CycWord,'Verb'):- meetsPosVerb(String,CycWord).
  664
  665stringAtomToPOS(String,nartR('WordWithPrefixFn', CycAffix, CycWord),POS):- 
  666     'derivationalAffixBasePOS'(CycAffix,POS),
  667     'prefixString'(CycAffix, Affix),
  668      words_concat(Affix, BaseString ,String),
  669      stringToCycWord([BaseString],CycWord).
  670
  671stringAtomToPOS(String,nartR('WordWithSuffixFn', CycWord, CycAffix),POS):-
  672     reorderBody(
  673     'denotation'(nartR('WordWithSuffixFn', CycWord, CycAffix), POS,_,_),
  674      String^('suffixString'(CycAffix,Affix),words_concat(BaseString,Affix,String),stringToCycWord([BaseString],CycWord))).
  675     
  676'suffixString'(CycAffix,Affix):-'variantOfSuffix'(CycAffix,Affix).
  677'variantOfSuffix'(CycAffix,Affix):- 'phoneticVariantOfSuffix'(CycAffix,Affix,_BaseType).
  678
  679'prefixString'(CycAffix,Affix):-'variantOfPrefix'(CycAffix,Affix).
  680'variantOfPrefix'(CycAffix,Affix):- 'phoneticVariantOfPrefix'(CycAffix,Affix,_BaseType).
  681
  682%meetsPos(String,CycWord,'Noun'):-atom(String),meetsPosNoun(String,CycWord).
  683
  684% TODO require infinitive
  685meetsPosVerb(String,CycWord):- stringArgUC(String,CycString,meetsPosVerb_0(CycString,CycWord)).
  686meetsPosVerb_0(String,CycWord):-reorderBody(String^atom_concat(S,'d',String),atom_concat(_,'e',S),CycWord^meetsPos([S],CycWord,'Verb')).
  687meetsPosVerb_0(String,CycWord):-reorderBody(String^atom_concat(S,'ed',String),CycWord^meetsPos([S],CycWord,'Verb')). 
  688meetsPosVerb_0(String,CycWord):-reorderBody(String^atom_concat(S,'ded',String),CycWord^meetsPos([S],CycWord,'Verb')). % like embedded
  689meetsPosVerb_0(String,CycWord):-reorderBody(String^atom_concat(S,'s',String),CycWord^meetsPos([S],CycWord,'Verb')). % TODO add or require intransitivity and infinitive
  690% ==========================================================
  691% **61*+18056377249*11*30#
  692
  693% Wordnet
  694wordToWNPOS(CycWord,WNWord,POS):- 'denotationPlaceholder'(CycWord,POS, _ , WNWord).
  695%'synonymousExternalConcept'('AbandoningSomething', 'WordNet-1995Version', 'V01269572', 'WordNetMappingMt', v(v('AbandoningSomething', 'WordNet-1995Version', 'V01269572'), A)).	 
  696
  697% ==========================================================
  698% String to WordsList - Form /POS
  699% ==========================================================
  700stringToWordsListForm(String,[CycWord|Words],FormOrPOS):- 
  701       stringArgUC(String,CycString,'abbreviationForCompoundString'(CycWord,WordList,FormOrPOS,CycString)),
  702	 stringToWords(WordList,Words).
  703
  704stringToWordsListPOS(String,CycWords,POS):- 
  705      stringArgUC(String,CycString,'abbreviationForMultiWordString'(List,CycWord,POS,CycString)),
  706      stringToWordsListForm(List,Words, _),
  707      append(Words,[CycWord],CycWords).
  708
  709
  710% ==========================================================
  711% String to CycWord 
  712% ==========================================================
  713cycWordToPossibleStrings(CycWord,StringAtom):- call_tabled(cycWordToPossibleStrings_0(CycWord,StringAtom)).
  714cycWordToPossibleStrings_0(_,[StringAtom]):- nonvar(StringAtom),StringAtom='',!,fail. 
  715cycWordToPossibleStrings_0(CycWord,String):- cyckb_t_e2c(Form,CycWord,CycString),is_speechPartPred_any(Form),cycStringToString(CycString,String).
  716cycWordToPossibleStrings_0(CycWord,StringAtom):- atom(CycWord),stringToCycWord_0(StringAtom2,CycWord),[StringAtom] = StringAtom2.
  717
  718stringToCycWord_never([String],_):-String=='',!,fail.
  719stringToCycWord_never([String],CycWord):-ground(stringToCycWord_never(String,CycWord)),
  720   once(cycWordToPossibleStrings(CycWord,_)),!,
  721   not(((cycWordToPossibleStrings(CycWord,StringSample),equals_icase(StringSample,String)))),!.
  722
  723is_stringWord(String):-stringToCycWord(String,_CycWord).
  724
  725stringToCycWord([EMPTY],_CycWord):- is_blankWord(EMPTY),!,fail.
  726stringToCycWord(String,CycWord):-
  727 not(stringToCycWord_never(String,CycWord)),
  728  locally(t_l:allowTT,
  729   one_must(stringToCycWord_0(String,CycWord),
  730      one_must(stringToCycWord_1(String,CycWord),
  731         stringToCycWord_2(String,CycWord)))),notPrefixOrSuffix(CycWord).
  732
  733
  734stringToCycWord_0(String,CycWord):-  meetsForm_1(String,CycWord,_).
  735stringToCycWord_0(String,CycWord):-  meetsPos_2(String,CycWord,_).
  736
  737stringToCycWord_1([String],CycWord):- atom(String),not(compound(CycWord)),once(toPropercase(String,UString)),atom_concat(UString,'-TheWord',CycWord),cyckb_t_e2c(_,CycWord,_),!.
  738
  739stringToCycWord_2(String,CycWord):- var(String),nonvar(CycWord),cycWordToPossibleStrings(CycWord,String).
  740
  741cycWordPosForm_Likely(POS,CycWord,Form):-        
  742	 (('preferredGenUnit'(_CycL,POS, CycWord);
  743	 'posBaseForms'(CycWord,POS);
  744	 'posForms'(CycWord,POS);
  745	 'denotation'(CycWord,POS, _Arg, _CycL))),      
  746	 speechPartPreds_transitive(POS, Form).
  747
  748sanify_string(String,Sane):- if_defined(isT(nameString(isa,Y)),fail),atom(Y), \+ atom(String),!,trace_or_throw(sanify_string(String,Sane)).
  749sanify_string(String,String):- \+ compound(String).
  750sanify_string(String,String):- sanify_string_list(String).
  751
  752% sanify_string([_|Tring]):-length(Tring,RLen),!,between(0,1,RLen).
  753sanify_string_list([_]).
  754sanify_string_list([_,_]).
  755sanify_string_list([_,_,_]).
  756
  757%pos(String,CycWord,Form,POS):- 'lex'(Form, CycWord, String),'lexMap'(_PosForms, CycWord,POS).
  758fillInPosAndForm(String,CycWord,Form,POS):- ignore(pos_0(String,CycWord,Form,POS)).
  759
  760
  761% pos_0(String,CycWord,Form,POS):-  pos_4(String,CycWord,Form,POS).
  762
  763pos_0(String,CycWord,Form,POS):- (nonvar(String);nonvar(CycWord)),!,meetsForm_1(Form,CycWord,String),speechPartPreds_transitive(POS, Form).
  764pos_0(String,CycWord,Form,POS):- speechPartPreds_transitive(POS, Form), meetsForm_1(Form,CycWord,String).
  765
  766% ==========================================================
  767% speechPartPreds HACKS
  768% ==========================================================
  769is_speechPartPred_tt_ever(Form):- atom(Form),atom_concat(infl,_,Form),
  770  call_tabled(findall_nodupes(F,((el_holds(isa,F,'Predicate','iThoughtTreasureMt',
  771    [amt('iThoughtTreasureMt')|_]),atom(F),atom_concat(infl,_,F))),Forms)),!,member(Form,Forms).
  772
  773:-export(is_speechPartPred_tt/1).  774is_speechPartPred_tt(Form):- t_l:allowTT,!,is_speechPartPred_tt_ever(Form).
  775
  776speechPartPreds_transitive(POS,Form):-speechPartPreds_asserted(POS,Form).
  777speechPartPreds_asserted(POS, Form):- is_speechPartPred_tt(Form),posName(POS),atom_contains(Form,POS).
  778speechPartPreds_asserted(POS, Form):- cyckb_t_e2c('basicSpeechPartPreds',POS, Form).
  779speechPartPreds_asserted(POS, Form):- cyckb_t_e2c('mostSpecificSpeechPartPreds',POS, Form).
  780speechPartPreds_asserted(POS, Form):- cyckb_t_e2c('speechPartPreds',POS, Form).
  781%speechPartPreds_asserted(SPOS, SForm):- speechPartPreds_transitive0(SPOS, SForm),must_det((nonvar(SForm),nonvar(SPOS))).
  782%speechPartPreds_asserted(SPOS, SForm):- reorderBody('speechPartPreds'(POS, Form),SPOS^pred_or_same('genls',POS,SPOS),SForm^pred_or_same('genlPreds',Form,SForm)).
  783
  784pred_or_same(_,POS,POS).
  785pred_or_same(Pred,POS,SPOS):- (nonvar(SPOS);nonvar(POS)),!,cyckb_t_e2c(Pred,POS,SPOS).
  786% pred_or_same(Pred,POS,SPOS):-cyckb_t_e2c(Pred,POS,MPOS),cyckb_t_e2c(Pred,MPOS,SPOS).
  787
  788:- expire_tabled_list(all).  789
  790is_speechPartPred(Form):-is_speechPartPred_nontt(Form).
  791is_speechPartPred(Form):-is_speechPartPred_tt(Form).
  792
  793is_speechPartPred_any(Form):-is_speechPartPred_nontt_ever(Form).
  794is_speechPartPred_any(Form):-is_speechPartPred_tt_ever(Form).
  795
  796is_speechPartPred_nontt(Form):- not(t_l:omitCycWordForms),!,is_speechPartPred_nontt_ever(Form).
  797is_speechPartPred_nontt_ever(Form):- call_tabled(no_repeats(Form,(is_speechPartPred_0(Form),not(is_speechPartPred_tt_ever(Form))))).
  798
  799is_speechPartPred_0(Form):-is_speechPartPred_1(Form).
  800is_speechPartPred_0(Form):-is_speechPartPred_1(FormP),cyckb_t_e2c(genlPreds,Form,FormP).
  801
  802is_speechPartPred_1('baseForm').
  803is_speechPartPred_1(Form):-speechPartPreds_asserted(_,Form).
  804is_speechPartPred_1(Form):-cyckb_t_e2c(isa,Form,'SpeechPartPredicate').
  805is_speechPartPred_1(Form):-cyckb_t_e2c(genlPreds,Form,'wordStrings').
  806is_speechPartPred_1(Form):-argIsa(Form,1, 'LexicalWord'),cyckb_t_e2c(arity,Form,2).
  807is_speechPartPred_1(Form):-argIsa(Form,1, 'EnglishWord'),cyckb_t_e2c(arity,Form,2).
  808
  809:- listing(is_speechPartPred_1/1).  810/*
  811is_speechPartPred_1(baseForm).
  812is_speechPartPred_1(A) :-
  813        speechPartPreds_asserted(_, A).
  814is_speechPartPred_1(A) :-
  815        cyckb_t_e2c(isa, A, rtSpeechPartPredicate).
  816is_speechPartPred_1(A) :-
  817        cyckb_t_e2c(genlPreds, A, wordStrings).
  818is_speechPartPred_1(A) :-
  819        argIsa(A, 1, xtLexicalWord),
  820        cyckb_t_e2c(arity, A, 2).
  821is_speechPartPred_1(A) :-
  822        argIsa(A, 1, xtEnglishWord),
  823        cyckb_t_e2c(arity, A, 2).
  824*/
  825
  826is_SpeechPart(POS):-cyckb_t_e2c(isa,POS,'SpeechPart').
  827
  828
  829:- baseKB:ain((argIsa(Form,1, 'LexicalWord') :- loop_check(parser_e2c:is_speechPartPred_tt(Form)))).  830:- baseKB:ain((argIsa(Form,2, 'CharacterString'):- loop_check(parser_e2c:is_speechPartPred_tt(Form)))).  831
  832% ==========================================================
  833% meetsForm(String,CycWord,Form)
  834% ==========================================================
  835
  836%baseKB:ain((meetsForm80(String,RootString,form80(MainPlusTrans,main+tv)):-fail,nop((String,RootString,form80(MainPlusTrans,main+tv))))).
  837
  838% ==========================================================
  839% meetsForm(String,CycWord,Form)
  840% ==========================================================
  841
  842% cycstring(_).
  843
  844meetsForm(String,CycWord,Form):-  no_repeats(meetsForm_0(String,CycWord,Form)).
  845
  846meetsForm_0(String,CycWord,Form):- one_must( meetsForm_1(String,CycWord,Form),meetsForm_2(String,CycWord,Form)).
  847meetsForm_0(_String,_CycWord,Form):- var(Form),!,fail.
  848meetsForm_0(String,CycWord,Form):- is_SpeechPart(Form),!,meetsPos(String,CycWord,Form).
  849meetsForm_0(String,CycWord,Form):- genlPreds_different(Child,Form),meetsForm_1(String,CycWord,Child).
  850
  851meetsForm_1(String,CycWord,Form):- has_wordage(String),is_wordage_prop(String, form(_, CycWord, _)),!,is_wordage_prop(String, form(_, CycWord, Form)).
  852% meetsForm_1(String,CycWord,Form):-nonvar(String),stringListToWordForm(String,CycWord,Form).
  853%'abbreviationForLexicalWord'('Kilogram-TheWord', 'singular', [kg])
  854meetsForm_1(String,CycWord,Form):-  stringArgUC(String, CycString,'abbreviationForLexicalWord'(CycWord,Form,CycString)).
  855meetsForm_1(String,CycWord,Form):- 
  856                      stringArgUC(String, CycString, (((once(nonvar(CycWord);atom(CycString))),                        
  857                                 cyckb_t_e2c(Form,CycWord,CycString),is_speechPartPred(Form),notPrefixOrSuffix(CycWord)))).
  858meetsForm_1([String],CycWord,Form):- stringAtomToWordForm([String],CycWord,Form).
  859
  860meetsForm_2(String,CycWord,POS):- locally(t_l:allowTT,meetsForm_1(String,CycWord,POS)).
  861
  862stringAtomToWordForm([String],CycWord,Form):- nonvar(CycWord),!,stringAtomToWordForm([String],NewCycWord,Form),!,CycWord=NewCycWord.
  863stringAtomToWordForm([String],CycWord,Form):- nonvar(String),!,           
  864	    'regularSuffix'(Form, Before, Affix), Affix\=@='',
  865	    words_concat(BaseString,Affix,[String]),
  866	    meetsForm([BaseString],CycWord,Before).
  867stringAtomToWordForm([String],CycWord,Form):- 
  868	    'regularSuffix'(Form,Before,Affix),  Affix\=@='',
  869            meetsForm([BaseString],CycWord,Before),
  870	    words_concat(BaseString,Affix,[String]).
  871
  872  
  873	    
  874% speechPartPreds_transitive(POS, Form),meetsPos(String,CycWord,POS)
  875
  876%'suffixString'('Y_AdjectiveProducing-TheSuffix', y, 'GeneralEnglishMt', v(v('Y_AdjectiveProducing-TheSuffix', y), A)).
  877
  878%'variantOfSuffix'('Able-TheSuffix', ible, 'GeneralEnglishMt', v(v('Able-TheSuffix', ible), A)).
  879%'variantOfSuffix'('Al_AdjectiveProducing-TheSuffix', ual, 'GeneralEnglishMt', v(v('Al_AdjectiveProducing-TheSuffix', ual), A)).
  880
  881%'compoundStringDenotesArgInReln'('Actor-TheWord', [remaining, afterwards], 'CountNoun', 'postActors', 2, 'GeneralEnglishMt', v(v('Actor-TheWord', 'CountNoun', 'postActors', afterwards, remaining), A)).
  882%'multiWordStringDenotesArgInReln'([unchanged], 'Actor-TheWord', 'SimpleNoun', 'unchangedActors', 2, 'GeneralEnglishMt', v(v('Actor-TheWord', 'SimpleNoun', 'unchangedActors', unchanged), A)).
  883
  884
  885
  886/*
  887% Adjectives
  888meetsForm_1(String,CycWord,'regularDegree'):-'regularDegree'(CycWord,String).
  889meetsForm_1(String,CycWord,'comparativeDegree'):-'comparativeDegree'(CycWord,String).
  890meetsForm_1(String,CycWord,'superlativeDegree'):-'superlativeDegree'(CycWord,String).
  891meetsForm_1(String,CycWord,'nonGradableAdjectiveForm'):-'nonGradableAdjectiveForm'(CycWord,String).
  892
  893% Nouns
  894meetsForm_1(String,CycWord,'singular'):-'singular'(CycWord,String).
  895meetsForm_1(String,CycWord,'plural'):-'plural'(CycWord,String).
  896%meetsForm_1(String,CycWord,'nonPlural-Generic'):-'nonPlural-Generic'(CycWord,String).
  897
  898meetsForm_1(String,CycWord,'agentive-Mass'):-'agentive-Mass'(CycWord,String).
  899meetsForm_1(String,CycWord,'agentive-Pl'):-'agentive-Pl'(CycWord,String).
  900meetsForm_1(String,CycWord,'agentive-Sg'):-'agentive-Sg'(CycWord,String).
  901%meetsForm_1(String,CycWord,'singular-Feminine'):-'singular-Feminine'(CycWord,String).
  902%meetsForm_1(String,CycWord,'singular-Masculine'):-'singular-Masculine'(CycWord,String).
  903%meetsForm_1(String,CycWord,'singular-Neuter'):-'singular-Neuter'(CycWord,String).
  904meetsForm_1(String,CycWord,'massNumber'):-'massNumber'(CycWord,String).
  905meetsForm_1(String,CycWord,'pnSingular'):-'pnSingular'(CycWord,String).
  906meetsForm_1(String,CycWord,'pnMassNumber'):-'pnMassNumber'(CycWord,String).
  907
  908
  909% Adverbs
  910meetsForm_1(String,CycWord,'regularAdverb'):-'regularAdverb'(CycWord,String).
  911meetsForm_1(String,CycWord,'superlativeAdverb'):-'superlativeAdverb'(CycWord,String).
  912
  913% Verbs
  914meetsForm_1(String,CycWord,'infinitive'):-'infinitive'(CycWord,String).
  915meetsForm_1(String,CycWord,'perfect'):-'perfect'(CycWord,String).
  916meetsForm_1(String,CycWord,'presentParticiple'):-'presentParticiple'(CycWord,String).
  917meetsForm_1(String,CycWord,'pastTense-Universal'):-'pastTense-Universal'(CycWord,String).
  918meetsForm_1(String,CycWord,'presentTense-Universal'):-'presentTense-Universal'(CycWord,String).
  919meetsForm_1(String,CycWord,'firstPersonSg-Present'):-'firstPersonSg-Present'(CycWord,String).
  920meetsForm_1(String,CycWord,'secondPersonSg-Present'):-'secondPersonSg-Present'(CycWord,String).
  921meetsForm_1(String,CycWord,'nonThirdSg-Present'):-'nonThirdSg-Present'(CycWord,String).
  922meetsForm_1(String,CycWord,'thirdPersonSg-Present'):-'thirdPersonSg-Present'(CycWord,String).
  923*/
  924
  925
  926
  927% ==========================================================
  928
  929varnameIdea(X,Y):-varnameIdea2(X,Y),!.
  930varnameIdea2([String|_],Subj):-!,varnameIdea2(String,Subj).
  931varnameIdea2('?TargetAgent','?TargetAgent').
  932varnameIdea2('TargetAgent','?TargetAgent').
  933varnameIdea2('?Speaker','?Speaker').
  934varnameIdea2(String,Subj):-atom(String),var(Subj),atom_concat('?',String,Sym),gensym(Sym,Subj).
  935varnameIdea2(_String,_Subj).
  936  
  937
  938%:-posMeans(CycWord,String,POS,Form,CycL).
  939
  940
  941clean_posm_cache:-
  942      t_l:noreorder,
  943      retractall(posm_cached(CycWord,String,POS,Form,[null])),
  944      retractall(posm_cached(CycWord,[] ,   POS,Form,CycL)),
  945      retractall(real_posm_cached(CycWord, _ ,POS,Form,CycL)),
  946      retractall(real_posm_cachedTT(CycWord, _ ,POS,Form,CycL)),
  947      posm_cached(CycWord,String,POS,Form,CycL),
  948      once(partition_cache(CycWord,String,POS,Form,CycL)),
  949      fail.
  950
  951clean_posm_cache:-tell(foo2),
  952   t_l:noreorder,
  953   listing(real_posm_cached),
  954   listing(real_posm_cachedTT),
  955   told.
  956
  957save_posm_cache
  958   :-tell(pldata(posm_cached_data)),
  959   listing(posm_cached),
  960   told.
  961
  962
  963
  964
  965partition_cache(CycWord,String,POS,Form:'posForms',CycL):-!,partition_cache(CycWord,String,POS,Form,CycL).
  966
  967partition_cache(CycWord,String,POS,Form,CycL):-
  968      t_l:noreorder,
  969   atom(CycWord),
  970      atom_concat('TT', _ ,CycWord),!,
  971      partition_cacheTT(CycWord,String,POS,Form,CycL).
  972
  973
  974% ======================================================
  975% Partitinion CycNL
  976% ======================================================
  977
  978% will look like.. posm_cached('Skill-TheWord', [skilled], 'MassNoun', 'regularDegree':'posForms', meaningOfWord('Skill-TheWord')).
  979
  980partition_cache(CycWord,String,POS,Form,meaningOfWord(CycWord)):-!,t_l:noreorder,
  981   posm_cached(CycWord,String, _ , _ ,CycL),not(CycL=meaningOfWord(_)),
  982   assert_if_new(real_posm_cached(CycWord,String,POS,Form,CycL)).
  983      
  984   %real_posm_cached('Type-TheWord', [of, geographical, entity, classified, by, hierarchy], 'SimpleNoun', form, 'GeographicalEntityByHierarchy').
  985partition_cache(CycWord,String,POS,form,CycL):-!,
  986  t_l:noreorder,
  987      posm_cached(CycWord,BPhraseing,POS,Not_form, _Old_Meaning),not(Not_form=form),
  988      append(BPhraseing,String,OPhrasing),
  989      partition_cache(CycWord,OPhrasing,POS,Not_form,CycL).
  990      
  991
  992partition_cache(CycWord,String,POS,Form,CycL):-!,
  993   assert_if_new(real_posm_cached(CycWord,String,POS,Form,CycL)).
  994
  995% ======================================================
  996% Partitinion TT CycNL
  997% posm_cached('TTWord-RATP', ['RATP'], 'Noun', 'TTPred-inflNounFemininePluralUnchecked', 'TT-company-RATP')
  998% ======================================================
  999
 1000% Delete copies of cycNL from TT
 1001partition_cacheTT(_CycWord,String,_POS, _Form, _CycL):-
 1002   posm_cached(OCycWord,String, _ , _ , _ ),
 1003   atom(OCycWord),
 1004   not(atom_concat('TT', _ ,OCycWord)),!.
 1005
 1006partition_cacheTT(CycWord,String,POS,Form,meaningOfWord(CycWord)):-
 1007   posm_cached(CycWord,String, _ , _ ,CycL),not(CycL=meaningOfWord(_)),!,
 1008   assert_if_new(real_posm_cachedTT(CycWord,String,POS,Form,CycL)).
 1009
 1010partition_cacheTT(CycWord,String,POS,Form,CycL):-!,
 1011   assert_if_new(real_posm_cachedTT(CycWord,String,POS,Form,CycL)).
 1012
 1013
 1014
 1015%:-clean_posm_cache.
 1016
 1017
 1018% testE2C:-make,halt.
 1019codesToForms(Codes,[],Codes):-!.
 1020codesToForms(Codes,[List|More],Out):-!,
 1021      codesToForms(Codes,List,M),!,
 1022      codesToForms(M,More,Out),!.
 1023
 1024codesToForms(Codes,lowercase,Out):-!,toLowercase(Codes,Out).
 1025codesToForms(Codes,uppercase,Out):-!,toUppercase(Codes,Out).
 1026codesToForms(Codes,cyclist,Out):-!,getSurfaceFromChars(Codes,Out, _).
 1027codesToForms(Codes,cyclistvars,Out:V):-!,getSurfaceFromChars(Codes,Out,V).
 1028codesToForms(Codes,cycl,Out):-!,getSurfaceFromChars(Codes,O,_V),balanceBinding(O,Out).
 1029codesToForms(Codes,cyclvars,Out:V):-!,getSurfaceFromChars(Codes,O,V),balanceBinding(O,Out).
 1030codesToForms(Codes,words,Out):-!,to_word_list(Codes,Out).
 1031codesToForms(Codes,idioms(D),Out):-!,idioms(D,Codes,Out).
 1032codesToForms(Codes,Pred,Out):-atom(Pred),!,Call=..[Pred,Codes,Out],!,Call.
 1033
 1034dirrect_order([start,tomcat]).
 1035%dirrect_order([start,tomcat]):-shell('/opt/tomcat/bin/startup.sh'),fmt([ok,done]).
 1036
 1037% =======================================================
 1038%'semTransPredForPOS'('Verb', 'verbSemTrans', 'EnglishMt', v(v('Verb', 'verbSemTrans'), A)).
 1039% =================================================================
 1040apply_frame(Formula,Subj,Event,Obj,Target,CycL):-
 1041      varnameIdea('ACTION',Event),
 1042      varnameIdea('SUBJECT',Subj),
 1043      varnameIdea('OBJECT',Obj),
 1044      varnameIdea('OBLIQUE',Target),
 1045      vsubst(Formula,':SUBJECT',Subj,Formula1),
 1046      vsubst(Formula1,':NOUN',Subj,Formula2),
 1047      vsubst(Formula2,':ACTION',Event,Formula3),
 1048      vsubst(Formula3,':OBJECT',Obj,Formula4),
 1049      vsubst(Formula4,':EVENT',Event,Formula5),
 1050      vsubst(Formula5,':OBLIQUE-OBJECT',Target,Formula6),
 1051      vsubst(Formula6,':ARG1',Subj,Formula7),
 1052      vsubst(Formula7,':VERB',Event,Formula8),
 1053      vsubst(Formula8,':ARG2',Obj,Formula9),
 1054      vsubst(Formula9,':EVENT',Event,Formula10),
 1055      vsubst(Formula10,':ARG3',Target,CycL).
 1056
 1057contains_obliqe(Formula):-flatten(Formula,Flat),member(':OBLIQUE-OBJECT',Flat).
 1058
 1059%:- rtrace.
 1060
 1061:- op(500,xfy,'&'). 
 1062:- op(510,xfy,('=>')). 1063:- op(100,fx,('`')). 1064
 1065	 
 1066:-export((fdelete/3)). 1067
 1068% ===============================================================================================
 1069	             	 	
 1070fdelete([],_,[]):-!.
 1071
 1072fdelete([Replace|Rest],[H|T],Out):-
 1073	functor(Replace,F, _),memberchk(F,[H|T]),!,
 1074       fdelete(Rest,[H|T],Out),!.
 1075
 1076fdelete([Replace|Rest],[H|T],[Replace|Out]):-!,
 1077       fdelete(Rest,[H|T],Out),!.
 1078
 1079fdelete([Replace|Rest],F,Out):-
 1080	functor(Replace,F, _),!,%F=FF,
 1081       fdelete(Rest,F,Out),!.
 1082
 1083fdelete([Replace|Rest],F,[Replace|Out]):-
 1084       fdelete(Rest,F,Out),!.
 1085
 1086%:-ensure_loaded(opencyc_chatterbot_data).
 1087
 1088
 1089
 1090
 1091
 1092/* Prediate:  descriptionTest/2 
 1093interpreted.
 1094file('c:/development/opensim4opencog/bin/cynd/startrek/mudreader.pl').
 1095line_count(33).
 1096number_of_clauses(1).
 1097Pattern: descriptionTest(_G1470,_G1471). 
 1098 */
 1099descriptionTest('NpcCol1000-Geordi684',["Lieutenant","Commander","Geordi","LaForge","Geordi LaForge","Lieutenant Commander Geordi LaForge is standing here","Geordi is the Chief Engineer of the Enterprise","He's blind, so he wears a special VISOR that lets him see things","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 3","mudMaxHitPoints: 12d12+3200","#$PunchingSomething mudBareHandDamage: 9d9+42","Geordi","Geordi LaForge","Lieutenant Commander Geordi LaForge is standing here","Geordi is the Chief Engineer of the Enterprise","He's blind, so he wears a special VISOR that lets him see things"]).
 1100descriptionTest('NpcCol1002-Worf720',["Lieutenant","Worf","Klingon","Lieutenant Worf","Lieutenant Worf is here, looking pretty mean","Worf is the first Klingon to have joined Starfleet","He's Chief of Security of the Enterprise, and he's plenty strong","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 2","mudMaxHitPoints: 12d12+3400","#$PunchingSomething mudBareHandDamage: 9d9+60","Worf","Lieutenant Worf","Lieutenant Worf is here, looking pretty mean","Worf is the first Klingon to have joined Starfleet","He's Chief of Security of the Enterprise, and he's plenty strong"]).
 1101descriptionTest(vacuum(1),["Lieutenant","Commander","Data","Android"]).
 1102descriptionTest(v12,["Data","Lieutenant Commander Data is here, trying to be more human","Data is the only android on the Enterprise, and the only android in all of Starfleet","He stowed super-human strength, and is extremely tough","ACT_NICE_THIEF","AWARE","NOBACKSTAB","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOSUMMON","NOSLEEP","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 1","mudMaxHitPoints: 18d18+4000","#$PunchingSomething mudBareHandDamage: 10d10+75","Data","CycLBot","CycBot","CycBot1","Data","Lieutenant Commander Data is here, trying to be more human","Data is the only android on the Enterprise, and the only android in all of Starfleet","He stowed super-human strength, and is extremely tough"]).
 1103descriptionTest(explorer(player1),["Lieutenant","Commander","Human","Player",
 1104            "Explorer Player",
 1105            "ACT_NICE_THIEF","AWARE","NOBACKSTAB","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOSUMMON",
 1106            "NOSLEEP","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 1","mudMaxHitPoints: 18d18+4000",
 1107            "#$PunchingSomething mudBareHandDamage: 10d10+75","Player","Player","Human",
 1108            "Logged on player character"]).
 1109descriptionTest('NpcCol1002-Worf720',["Lieutenant","Worf","Klingon","Lieutenant Worf","Lieutenant Worf is here, looking pretty mean","Worf is the first Klingon to have joined Starfleet","He's Chief of Security of the Enterprise, and he's plenty strong","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 2","mudMaxHitPoints: 12d12+3400","#$PunchingSomething mudBareHandDamage: 9d9+60","Worf","Lieutenant Worf","Lieutenant Worf is here, looking pretty mean","Worf is the first Klingon to have joined Starfleet","He's Chief of Security of the Enterprise, and he's plenty strong"]).
 1110descriptionTest('NpcCol1003-Dr-Crusher677',["Doctor","Beverly","Crusher","Doctor Crusher","Lieutenant Beverly Crusher is here, looking for someone to heal","Doctor Crusher is the Enterprise's Chief Medical Officer","Wesley is her son","Her husband was killed years ago in an accident on another starship which was also commanded by Captain Picard","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 3","mudMaxHitPoints: 12d12+3200","#$PunchingSomething mudBareHandDamage: 9d9+42","Dr. Crusher","Doctor Crusher","Lieutenant Beverly Crusher is here, looking for someone to heal","Doctor Crusher is the Enterprise's Chief Medical Officer","Wesley is her son","Her husband was killed years ago in an accident on another starship which was also commanded by Captain Picard"]).
 1111descriptionTest('NpcCol1004-Troi712',["Counselor","Deanna","Troi","Counselor Troi","Counselor Deanna Troi is here","Counselor Troi is the ship's main counselor","She's half betazoid, which means that she can read people's minds","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 3","mudMaxHitPoints: 12d12+3200","#$PunchingSomething mudBareHandDamage: 9d9+42","Troi","Counselor Troi","Counselor Deanna Troi is here","Counselor Troi is the ship's main counselor","She's half betazoid, which means that she can read people's minds"]).
 1112descriptionTest('NpcCol1005-Riker707',["Commander","William","Riker","Commander Riker","Commander William Riker is here, staring at you","Commander Riker is the Enterprise's first officer","He's in charge of keeping the crew in line","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 2","mudMaxHitPoints: 12d12+3200","#$PunchingSomething mudBareHandDamage: 9d9+52","Riker","Commander Riker","Commander William Riker is here, staring at you","Commander Riker is the Enterprise's first officer","He's in charge of keeping the crew in line"]).
 1113descriptionTest('NpcCol1006-Picard701',["Captain","Jean","Luc","Jean-Luc","Picard","Captain Picard","Captain Jean-Luc Picard is standing here, watching you","Captain Picard is a very important man","He's in charge of Starfleet's flagship, the Enterprise","He's very smart, and very wise","Don't mess with him!","ACT_NICE_THIEF","AWARE","NOBACKSTAB","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOSUMMON","NOSLEEP","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_SANCTUARY","NPC_NOTRACK","+mudToHitArmorClass0: 0","mudMaxHitPoints: 20d20+5000","#$PunchingSomething mudBareHandDamage: 12d12+75","Picard","Captain Picard","Captain Jean-Luc Picard is standing here, watching you","Captain Picard is a very important man","He's in charge of Starfleet's flagship, the Enterprise","He's very smart, and very wise","Don't mess with him!"]).
 1114descriptionTest('NpcCol1007-Guinan689',["Guinan","Guinan","Guinan is here, tending the bar","Guinan is a strange being","She's lived for thousands of years and experienced many things, but now she's decided to work on the Enterprise as a bartender","ACT_SENTINEL","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 4","mudMaxHitPoints: 12d12+2600","#$PunchingSomething mudBareHandDamage: 9d9+36","Guinan","Guinan","Guinan is here, tending the bar","Guinan is a strange being","She's lived for thousands of years and experienced many things, but now she's decided to work on the Enterprise as a bartender"]).
 1115descriptionTest('NpcCol1008-OBrien696',["Chief","O'Brien","Transporter","Chief O'Brien","Chief O'Brien is here, waiting to teleport you somewhere","Chief O'Brien is the transporter chief on the Enterprise","It's his job to make sure everyone arrives(and leaves) in one piece, instead of trillions of atoms","ACT_SENTINEL","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 4","mudMaxHitPoints: 12d12+2600","#$PunchingSomething mudBareHandDamage: 9d9+36","O'Brien","Chief O'Brien","Chief O'Brien is here, waiting to teleport you somwhere","Chief O'Brien is the transporter chief on the Enterprise","It's his job to make sure everyone arrives(and leaves) in one piece, instead of trillions of atoms"]).
 1116descriptionTest('NpcCol1009-Wesley716',["Wesley","Crusher","Wesley","Wesley Crusher is here, eagerly trying to earn your praise","Wesley Crusher is not even an official officer, but he serves as an acting Ensign on the bridge","He got this position only because Captain Picard feels guilty about killing his father","ACT_STAY_ZONE","ACT_WIMPY","wimpy mobile will try to flee when it gets low on hit points. A mobile which is both aggressive and wimpy will not attack a player that is awake","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 12d12+1400","#$PunchingSomething mudBareHandDamage: 9d9+24","Wesley","Wesley","Wesley Crusher is here, eagerly trying to earn your praise","Wesley Crusher is not even an official officer, but he serves as an acting Ensign on the bridge","He got this position only because Captain Picard feels guilty about killing his father"]).
 1117descriptionTest('NpcCol1010-Livingston726',["Livingston","fish","Livingston","Livingston the fish is here, swimming about in his tank","Livingston is Captain Picard's pet fish","He's some sort of exotic breed, and he's expensive to feed and keep alive","ACT_SENTINEL","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 12d12+800","#$PunchingSomething mudBareHandDamage: 9d9+14","Livingston","Livingston","Livingston the fish is here, swimming about in his tank","Livingston is Captain Picard's pet fish","He's some sort of exotic breed, and he's expensive to feed and keep alive"]).
 1118descriptionTest('NpcCol1011-Spot727',["spot","the","cat","Spot","Spot, Data's pet cat, is sitting here looking at you","Spot is Data's orange coloured cat","Data is always trying to become more human, so he thinks that having a pet might help him achieve his goal","ACT_SENTINEL","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 12d12+800","#$PunchingSomething mudBareHandDamage: 9d9+14","Spot","Spot","Spot, Data's pet cat, is sitting here looking at you","Spot is Data's orange coloured cat","Data is always trying to become more human, so he thinks that having a pet might help him achieve his goal"]).
 1119descriptionTest('NpcCol1012-Ensign728',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1120descriptionTest('NpcCol1012-Ensign732',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1121descriptionTest('NpcCol1012-Ensign736',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1122descriptionTest('NpcCol1012-Ensign740',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1123descriptionTest('NpcCol1012-Ensign744',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1124descriptionTest('NpcCol1012-Ensign748',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1125descriptionTest('NpcCol1012-Ensign752',["ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Ensign","the ensign","A nervous looking ensign is standing here, watching you","These ensigns make up the backbone of the Enterprise","They clean things, do jobs the higher ups won't even consider doing, and get yelled at all the time"]).
 1126descriptionTest('NpcCol1013-Alexander671',["alexander","rozhenko","alexander rozhenko","Alexander Rozhenko is here, practicing laughing hour","Alexander Rozhenko is Worf's son","His mother was half human and half Klingon, so Alexander is 3/4 Klingon","He's quite small, but since he's a Klingon he's very strong","ACT_STAY_ZONE","MEMORY","HELPER","ACT_FRIEND","NOCHARM","NOBASH","NOBLIND","NPC_DETECT_INVIS","NPC_NOTRACK","+mudToHitArmorClass0: 6","mudMaxHitPoints: 8d8+1600","#$PunchingSomething mudBareHandDamage: 8d8+26","Alexander","alexander rozhenko","Alexander Rozhenko is here, practicing laughing hour","Alexander Rozhenko is Worf's son","His mother was half human and half Klingon, so Alexander is 3/4 Klingon","He's quite small, but since he's a Klingon he's very strong"]).
 1127descriptionTest('ArtifactCol1000-Phaser676',["standard","issue","starfleet","phaser","a standard issue phaser","A standard issue Starfleet phaser has been left here","damageNumberDice 5","damageSizeDice 5","WeaponBlasting","These phasers are the standard weapon of Starfleet officers. It offers decent damage for its fairly small size","Phaser","a standard issue phaser"]).
 1128descriptionTest('ArtifactCol1000-Phaser776',["standard","issue","starfleet","phaser","a standard issue phaser","A standard issue Starfleet phaser has been left here","damageNumberDice 5","damageSizeDice 5","WeaponBlasting","These phasers are the standard weapon of Starfleet officers. It offers decent damage for its fairly small size","Phaser","a standard issue phaser"]).
 1129descriptionTest('ArtifactCol1000-Phaser700',["standard","issue","starfleet","phaser","a standard issue phaser","A standard issue Starfleet phaser has been left here","damageNumberDice 5","damageSizeDice 5","WeaponBlasting","These phasers are the standard weapon of Starfleet officers. It offers decent damage for its fairly small size","Phaser","a standard issue phaser"]).
 1130descriptionTest('ArtifactCol1000-Phaser724',["standard","issue","starfleet","phaser","a standard issue phaser","A standard issue Starfleet phaser has been left here","damageNumberDice 5","damageSizeDice 5","WeaponBlasting","These phasers are the standard weapon of Starfleet officers. It offers decent damage for its fairly small size","Phaser","a standard issue phaser"]).
 1131descriptionTest('ArtifactCol1001-5-Phaser-Rifle705',["phaser","rifle","a phaser rifle","A large phaser rifle is lying here","damageNumberDice 7","damageSizeDice 6","WeaponBlasting","This phaser rifle looks pretty powerful. These weapons are used mainly on assault type missions, where power is important","5 Phaser Rifle","a phaser rifle"]).
 1132descriptionTest('ArtifactCol1002-Red-Uniform704',["burgandy","starfleet","command","uniform","a burgandy Starfleet command uniform","A neatly folded burgandy Starfleet command uniform is lying here","armorLevel: 10","These uniforms are worn by command officers on Federation starships. It's kind of tight, but it looks pretty good","Red Uniform","a burgandy Starfleet command uniform"]).
 1133descriptionTest('ArtifactCol1002-Red-Uniform710',["burgandy","starfleet","command","uniform","a burgandy Starfleet command uniform","A neatly folded burgandy Starfleet command uniform is lying here","armorLevel: 10","These uniforms are worn by command officers on Federation starships. It's kind of tight, but it looks pretty good","Red Uniform","a burgandy Starfleet command uniform"]).
 1134descriptionTest('ArtifactCol1002-Red-Uniform719',["burgandy","starfleet","command","uniform","a burgandy Starfleet command uniform","A neatly folded burgandy Starfleet command uniform is lying here","armorLevel: 10","These uniforms are worn by command officers on Federation starships. It's kind of tight, but it looks pretty good","Red Uniform","a burgandy Starfleet command uniform"]).
 1135descriptionTest('ArtifactCol1002-Red-Uniform739',["burgandy","starfleet","command","uniform","a burgandy Starfleet command uniform","A neatly folded burgandy Starfleet command uniform is lying here","armorLevel: 10","These uniforms are worn by command officers on Federation starships. It's kind of tight, but it looks pretty good","Red Uniform","a burgandy Starfleet command uniform"]).
 1136descriptionTest('ArtifactCol1002-Red-Uniform743',["burgandy","starfleet","command","uniform","a burgandy Starfleet command uniform","A neatly folded burgandy Starfleet command uniform is lying here","armorLevel: 10","These uniforms are worn by command officers on Federation starships. It's kind of tight, but it looks pretty good","Red Uniform","a burgandy Starfleet command uniform"]).
 1137descriptionTest('ArtifactCol1003-Gold-Uniform675',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1138descriptionTest('ArtifactCol1003-Gold-Uniform775',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1139descriptionTest('ArtifactCol1003-Gold-Uniform687',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1140descriptionTest('ArtifactCol1003-Gold-Uniform699',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1141descriptionTest('ArtifactCol1003-Gold-Uniform723',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1142descriptionTest('ArtifactCol1003-Gold-Uniform731',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1143descriptionTest('ArtifactCol1003-Gold-Uniform735',["gold","starfleet","engineering","uniform","a gold Starfleet engineering uniform","A neatly folded gold Starfleet engineering uniform is lying here","armorLevel: 10","These uniforms are worn by engineering officers on Federation starships. It's kind of tight, but it looks pretty good","Gold Uniform","a gold Starfleet engineering uniform"]).
 1144descriptionTest('ArtifactCol1004-Blue-Uniform680',["blue","starfleet","medical","uniform","a blue Starfleet medical uniform","A neatly folded blue Starfleet medical uniform is lying here","armorLevel: 10","These uniforms are worn by medical officers on Federation starships. It's kind of tight, but it looks pretty good","Blue Uniform","a blue Starfleet medical uniform"]).
 1145descriptionTest('ArtifactCol1004-Blue-Uniform715',["blue","starfleet","medical","uniform","a blue Starfleet medical uniform","A neatly folded blue Starfleet medical uniform is lying here","armorLevel: 10","These uniforms are worn by medical officers on Federation starships. It's kind of tight, but it looks pretty good","Blue Uniform","a blue Starfleet medical uniform"]).
 1146descriptionTest('ArtifactCol1004-Blue-Uniform747',["blue","starfleet","medical","uniform","a blue Starfleet medical uniform","A neatly folded blue Starfleet medical uniform is lying here","armorLevel: 10","These uniforms are worn by medical officers on Federation starships. It's kind of tight, but it looks pretty good","Blue Uniform","a blue Starfleet medical uniform"]).
 1147descriptionTest('ArtifactCol1004-Blue-Uniform751',["blue","starfleet","medical","uniform","a blue Starfleet medical uniform","A neatly folded blue Starfleet medical uniform is lying here","armorLevel: 10","These uniforms are worn by medical officers on Federation starships. It's kind of tight, but it looks pretty good","Blue Uniform","a blue Starfleet medical uniform"]).
 1148descriptionTest('ArtifactCol1004-Blue-Uniform755',["blue","starfleet","medical","uniform","a blue Starfleet medical uniform","A neatly folded blue Starfleet medical uniform is lying here","armorLevel: 10","These uniforms are worn by medical officers on Federation starships. It's kind of tight, but it looks pretty good","Blue Uniform","a blue Starfleet medical uniform"]).
 1149descriptionTest('ArtifactCol1005-Boots673',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1150
 1151
 1152
 1153descriptionTest('ArtifactCol1005-Boots773',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1154descriptionTest('ArtifactCol1005-Boots678',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1155descriptionTest('ArtifactCol1005-Boots685',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1156descriptionTest('ArtifactCol1005-Boots697',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1157descriptionTest('ArtifactCol1005-Boots702',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1158descriptionTest('ArtifactCol1005-Boots708',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1159descriptionTest('ArtifactCol1005-Boots713',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1160descriptionTest('ArtifactCol1005-Boots717',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1161descriptionTest('ArtifactCol1005-Boots721',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1162descriptionTest('ArtifactCol1005-Boots729',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1163descriptionTest('ArtifactCol1005-Boots733',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1164descriptionTest('ArtifactCol1005-Boots737',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1165descriptionTest('ArtifactCol1005-Boots741',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1166descriptionTest('ArtifactCol1005-Boots745',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1167descriptionTest('ArtifactCol1005-Boots749',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1168descriptionTest('ArtifactCol1005-Boots753',["starfleet","black","boots","a pair of Starfleet black boots","A pair of Starfleet black boots are sitting here","armorLevel: 5","These boots must be worn by all Starfleet officers while on duty. They're quite light, and offer good protection for the feet","Boots","a pair of Starfleet black boots"]).
 1169descriptionTest('ArtifactCol1006-Comm-Badge674',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1170descriptionTest('ArtifactCol1006-Comm-Badge774',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1171descriptionTest('ArtifactCol1006-Comm-Badge679',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1172descriptionTest('ArtifactCol1006-Comm-Badge686',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1",
 1173                     "These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1174descriptionTest('ArtifactCol1006-Comm-Badge698',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1175descriptionTest('ArtifactCol1006-Comm-Badge703',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1176descriptionTest('ArtifactCol1006-Comm-Badge709',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1177descriptionTest('ArtifactCol1006-Comm-Badge714',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1178descriptionTest('ArtifactCol1006-Comm-Badge718',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1179descriptionTest('ArtifactCol1006-Comm-Badge722',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1180descriptionTest('ArtifactCol1006-Comm-Badge730',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1181descriptionTest('ArtifactCol1006-Comm-Badge734',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1182descriptionTest('ArtifactCol1006-Comm-Badge738',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1183descriptionTest('ArtifactCol1006-Comm-Badge742',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1184descriptionTest('ArtifactCol1006-Comm-Badge746',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1185descriptionTest('ArtifactCol1006-Comm-Badge750',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1186descriptionTest('ArtifactCol1006-Comm-Badge754',["starfleet","comm","com","communication","badge","a Starfleet communication badge","A Starfleet communication badge is lying here","armorLevel: 1","These communication badges must be worn by all officers while on a starship. It looks like a silver arrow head on top of a golden coloured oval: ____/____ / /   | /  | _/ _/_ _/ // \\ ","Comm Badge","a Starfleet communication badge"]).
 1187descriptionTest('ArtifactCol1007-Sash725',["worf's","worf","sash","Worf's sash","Worf's silver chain sash has been left here","armorLevel: 8","Worf's sash is some sort of Klingon clothing. Worf always wears it, which makes you wonder how you managed to get a hold of it..","Sash","Worf's sash"]).
 1188descriptionTest('ArtifactCol1008-VISOR688',["geordi","geordi's","visor","Geordi's VISOR","Geordi's VISOR is lying here","armorLevel: 2","Geordi's VISOR was made specially for him, because he's blind. This piece of equipment allows him to see things, but differently than normal eyes. I wonder how Geordi is managing, now that you've stolen his only way of seeing?","VISOR","Geordi's VISOR"]).
 1189descriptionTest('ArtifactCol1009-Medical-Tricorder681',["medical","tricorder","a medical Tricorder","A medical Tricorder is lying here, ready to be used","mudLevelOf: 10","chargeCapacity: 5","chargeRemaining: 5","This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it","Medical Tricorder","a medical Tricorder"]).
 1190descriptionTest('ArtifactCol1009-Medical-Tricorder682',["medical","tricorder","a medical Tricorder","A medical Tricorder is lying here, ready to be used","mudLevelOf: 10","chargeCapacity: 5","chargeRemaining: 5","This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it","Medical Tricorder","a medical Tricorder"]).
 1191descriptionTest('ArtifactCol1009-Medical-Tricorder683',["medical","tricorder","a medical Tricorder","A medical Tricorder is lying here, ready to be used","mudLevelOf: 10","chargeCapacity: 5","chargeRemaining: 5","This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it","Medical Tricorder","a medical Tricorder"]).
 1192descriptionTest('ArtifactCol1009-Tricorder759',["medical","tricorder","a medical Tricorder","A medical Tricorder is lying here, ready to be used","mudLevelOf: 10","chargeCapacity: 5","chargeRemaining: 5","This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it","Tricorder","a medical Tricorder"]).
 1193descriptionTest('ArtifactCol1009-Tricorder760',["medical","tricorder",
 1194                     "a medical Tricorder","A medical Tricorder is lying here, ready to be used",
 1195                     "mudLevelOf: 10",
 1196                     "chargeCapacity: 5",
 1197                     "chargeRemaining: 5",
 1198                     "This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it",
 1199                     "Tricorder","a medical Tricorder"]).
 1200descriptionTest('ArtifactCol1009-Tricorder761',["medical","tricorder","a medical Tricorder","A medical Tricorder is lying here, ready to be used","mudLevelOf: 10","chargeCapacity: 5","chargeRemaining: 5","This medical Tricorder is used to heal small wounds and cuts. While it isn't made for major injuries, it can help you limp home. To use, hold it and then use it","Tricorder","a medical Tricorder"]).
 1201descriptionTest('ArtifactCol1010-Dilithium-Crystal756',["dilithium","crystal","a dilithium crystal","A shard of dilithium crystal is lying here","maybe a #$LightingDevice","Dilithium crystals are used to power warp cores of starships. This particular crystal is glowing brightly, and gives off a blue-ish tinge","Dilithium Crystal","a dilithium crystal"]).
 1202descriptionTest('ArtifactCol1010-Dilithium-Crystal757',["dilithium","crystal","a dilithium crystal","A shard of dilithium crystal is lying here","maybe a #$LightingDevice","Dilithium crystals are used to power warp cores of starships. This particular crystal is glowing brightly, and gives off a blue-ish tinge","Dilithium Crystal","a dilithium crystal"]).
 1203descriptionTest('ArtifactCol1010-Dilithium-Crystal758',["dilithium","crystal","a dilithium crystal","A shard of dilithium crystal is lying here","maybe a #$LightingDevice","Dilithium crystals are used to power warp cores of starships. This particular crystal is glowing brightly, and gives off a blue-ish tinge","Dilithium Crystal","a dilithium crystal"]).
 1204descriptionTest('ArtifactCol1011-5-Picards-Flute706',["picard","picard's","flute","Picard's flute","Captain Picard's wooden flute is sitting here","Captain Picard recieved this flute when he lost his memory and was stuck on some strange world. Now, he plays it to relieve stress","5 Picard's Flute","Picard's flute"]).
 1205descriptionTest('ArtifactCol1012-Trombone711',["riker","riker's","trombone","Riker's trombone","Commander Riker's trombone has been placed here","Commander Riker considers himself to be a talented jazz musician. He practices on this trombone all the time","Trombone","Riker's trombone"]).
 1206descriptionTest('ArtifactCol1020-Tea690',["tea","cup","a small cup","A small cup of tea is sitting here","Tea","a small cup"]).
 1207descriptionTest('ArtifactCol1021-Synthehol691',["wine","bottle","synthehol","a synthehol","A bottle of synthehol is standing here","Synthehol","a synthehol"]).
 1208descriptionTest('ArtifactCol1022-Ferengi-Ale692',["ale","ferengi","bottle","a Ferengi bottle","A bottle of Ferengi ale is sitting here","Ferengi Ale","a Ferengi bottle"]).
 1209descriptionTest('ArtifactCol1023-Romulan-Whisky693',["whisky","whiskey","romulan","bottle","a Romulan bottle","A bottle of Romulan whiskey is sitting here","Romulan Whisky","a Romulan bottle"]).
 1210descriptionTest('ArtifactCol1024-Lemonade-Prune-Juice694',["lemonade","prune","juice","glass","a small glass","A small glass of prune juice is sitting here","Lemonade","Prune Juice","a small glass"]).
 1211descriptionTest('ArtifactCol1025-Vulcan-Beer695',["beer","vulcan","bottle","a Vulcan bottle","A bottle of Vulcan beer is standing here","Vulcan Beer","a Vulcan bottle"]).
 1212descriptionTest('iArea1000',["Main Engineering","You find yourself in the middle of main engineering","The room is longer than it is wide, and it has fairly low ceilings","Computer terminals cover all the walls, and a large table built into the floor sits in the middle of the room","At the far end of the room you see the warp core, a large pulsating vertical tube"]).
 1213descriptionTest('iArea1002',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape"]).
 1214descriptionTest('iArea1001',["Geordi's Quarters","You're in the middle of Geordi's quarters","The room is sparsely decorated, due to the fact that Geordi is blind","A small personal computer sits on a desk against the western wall, in between two windows that look out into space","A neatly made bed has been placed against the northern wall"]).
 1215descriptionTest('iArea1005',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape","You notice a tiny computer panel embedded into the wall"]).
 1216descriptionTest('iArea1003',["Data's Quarters","You're in the middle of Data's quarters","Some easils and paintings have been left scattered around the southern part of the room, while a huge computer screen showing a cross section of the Enterprise covers the entire northern wall","In front of the screen is a large desk, which is covered in computer controls","You can't see a bed in this room, but you figure it's because Data doesn't sleep"]).
 1217descriptionTest('iArea1004',["The Brig","You're in the dimly lit Brig","This is where all the criminals and prisoners are kept while on board the Enterprise","Three fairly large cells can been seen in the southern part of the room, and they're all empty","A computer control panel is situated in the northwestern corner of the room, which is where the force fields for the cells are controlled",'The panel says:
 1218
 1219***************************************************
 1220*                                                 *
 1221*            NCC-1701-D - ENTERPRISE              *
 1222*                                                 *
 1223*              *****                              *
 1224*      **********************                     *
 1225*      ***********************  _________         *
 1226*              *****        ***(___  ____(        *
 1227*                            ***** \\ \\*           *
 1228*                             **********          *
 1229*                                                 *
 1230*          You are currently on deck 1            *
 1231*                                                 *
 1232***************************************************
 1233']).
 1234descriptionTest('iArea1008',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape","You see the holodeck's control panel beside the holodeck door, and it has some information on it"]).
 1235descriptionTest('iArea1006',["Transporter Room","You're in the Enterprise transporter room","A computer terminal is sitting near the southern wall, where the transporter chief can control the transporters","Eight round transport pads have been arranged in a circle, on a raised platform against the northern wall"]).
 1236descriptionTest('iArea1042',["Transporter Beam","You find yourself in a transporter beam","All you can see is blue flashing light","It feels as though your body is racing around at high speeds","As you try to look down at your body, you realize that there's nothing there!"]).
 1237descriptionTest('iArea1007',["School","You step through the doors and find yourself in a large school room","Various tables and chairs are set up all around the room, and many paintings and drawings have been attached to the walls","Several computer consoles with a children's interface on them can be seen on the tables"]).
 1238descriptionTest('iArea1010',["Turbolift","You're in the turbolift","The turbolift walls have been rounded off, making it in the shape of a tube","Several vertical rows of lights make this place very well lit","From here, you can access the other decks on the Enterprise"]).
 1239descriptionTest('iArea1009',["Holodeck 2","You're now on Holodeck 2","The room is just a large cube, with jet black walls and a yellow grid painted on the floors, the walls, and the ceiling","This is where different programs can be loaded and experienced, which seem totally real","Right now, this holodeck is not functioning",'
 1240***************************************************
 1241*                                                 *
 1242*            NCC-1701-D - "ENTERPRISE"            *
 1243*                    HOLODECK 2                   *
 1244*                                                 *
 1245*              STATUS : Inactive                  *
 1246*     CURRENT PROGRAM : N/A                       *
 1247*            SAFETIES : N/A                       *
 1248*                                                 *
 1249*    NOTE: Starfleet is not responsible for       *
 1250*          any injuries incurred while on this    *
 1251*          holodeck!                              *
 1252*                                                 *
 1253* WARNING: While the safeties are disabled, you   *
 1254*          CAN be injured, or even killed.        *
 1255*                                                 *
 1256***************************************************']).
 1257descriptionTest('iArea1011',["Turbolift","You're in the turbolift","The turbolift walls have been rounded off, making it in the shape of a tube","Several vertical rows of lights make this place very well lit","From here, you can accessthe other decks on the Enterprise"]).
 1258descriptionTest('iArea1013',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape","You notice a tiny computer panel embedded into the wall"]).
 1259descriptionTest('iArea1032',["Turbolift","You're in the turbolift","The turbolift walls have been rounded off, making it in the shape of a tube","Several vertical rows of lights make this place very well lit","From here, you can access the other decks on the Enterprise"]).
 1260descriptionTest('iArea1012',["Cargo Bay 1","You're in the main cargo bay of the Enterprise","It's quite a large room, with a very high ceiling and a lot of floor space","You can see several hundred plastic crates and barrels with the Starfleet insignia on them stacked right up to the ceiling"]).
 1261descriptionTest('iArea1016',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape","You see the holodeck's control panel beside the holodeck door, and it has some information on it"]).
 1262descriptionTest('iArea1014',["Riker's Quarters","You've arrived in Riker's quarters","The room is very neat and tidy, with a couch and several chairs aranged around a coffee table by the eastern wall","A small partition at the northern part of the room seperates his sleeping area with the rest of the room"]).
 1263descriptionTest('iArea1015',["Sick Bay","You're in the middle of the Enterprise's Sick Bay","About a dozen beds are arranged along the walls of the room, while several carts covered with medical supplies are scattered around the room","A large glass window in the northern part of the room separates the doctor's office with the rest of the room",'
 1264***************************************************
 1265*                                                 *
 1266*            NCC-1701-D - "ENTERPRISE"            *
 1267*                    HOLODECK 4                   *
 1268*                                                 *
 1269*              STATUS : Active                    *
 1270*     CURRENT PROGRAM : Sherlock Holmes (19th     *
 1271*                       century London)           *
 1272*            SAFETIES : Disabled                  *
 1273*                                                 *
 1274*    NOTE: Starfleet is not responsible for       *
 1275*          any injuries incurred while on this    *
 1276*          holodeck!                              *
 1277*                                                 *
 1278* WARNING: While the safeties are disabled, you   *
 1279*          CAN be injured, or even killed.        *
 1280*                                                 *
 1281*             ---ENTER WHEN READY---              *
 1282*                                                 *
 1283*************************************************** ']).
 1284descriptionTest('iArea1019',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape"]).
 1285descriptionTest('iArea1017',["Holodeck 4 Entrance - A Narrow Alley","You emerge into a dark narrow alley","Tall dark brick buildings block your way north and south","You can see that the windows on the buildings are fairly high, and some have been boarded up","The smell from the rotting food and garbage mixing with the foul water on the ground is unbearable","You can hear the sounds of a bustling marketpace to the east","The archway leading out of the holodeck is west"]).
 1286descriptionTest('iArea1018',["Crusher's Quarters","You're in Doctor Crusher's quarters","Several different paintings are attached to the walls, and you also notice a few sculptures","A neatly made bed is located by the northern wall, in between two large windows looking out into space"]).
 1287descriptionTest('iArea1021',["Ten Forward","You're now in Ten Forward, the entertainment room of the Enterprise","The entire northern wall is covered with windows looking out into space, while two large wooden doors with the Starfleet insignia stamped on them face south","Many round metal tables are scattered around the room, surrounded by metal chairs","A long bar spans almost the entire length of the southern part of the room, and about two dozen bar stools are sitting in front of it","It's very noisy in here, due to all the talking and laughing"]).
 1288descriptionTest('iArea1020',["Enterprise Security","You're standing in the dimly lit Enterprise Security","Weapons lockers cover all of the walls, except along the northern wall, where a large glass window protects dozens of different phasors, blaster rifles, and other high tech weapons","Three long tables surrounded by chairs stretch across the room"]).
 1289descriptionTest('iArea1022',["Shuttle Bay","You're in the main shuttle bay of the Enterprise","It's quite a large room, with a very high ceiling and a lot of floor space","You can see three different shuttle crafts sitting here, waiting to be flown","A large grey door leads into space"]).
 1290descriptionTest('iArea1024',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape","You notice a tiny computer panel embedded into the wall"]).
 1291descriptionTest('iArea1039',["Outer Space by the Enterprise","You're floating in outer space right beside the USS Enterprise","You can see stars in every direction, which provide the only light here","You feel very cold","A large grey door leads into the Enterprise's Shuttle Bay"]).
 1292descriptionTest('iArea1023',["Troi's Quarters","You're in Counselor Deanna Troi's quarters","Several different paintings have been hung from the walls, and a small couch and a recliner are positioned around a coffee table","A neatly made bed is partially hidden behind a curtain at the northern part of the room"]).
 1293descriptionTest('iArea1027',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape",
 1294"
 1295***************************************************
 1296*                                                 *
 1297*            NCC-1701-D - ENTERPRISE            *
 1298*                                                 *
 1299*              *****                              *
 1300*      **********************                     *
 1301*      ***********************  _________         *
 1302*              *****        ***(___  ____(        *
 1303*                            ***** \\ \\*           *
 1304*                             **********          *
 1305*                                                 *
 1306*          You are currently on deck 3            *
 1307*                                                 *
 1308***************************************************
 1309"]).
 1310descriptionTest('iArea1025',["Worf's Quarters","You're in Worf's quarters","A small table is sitting in the southeastern corner, and on it is a small potted plant","An impressive selection of Klingon weapons have been mounted on the northern wall, and a partition splits this room with Worf's bedroom to the east"]).
 1311descriptionTest('iArea1026',["Enterprise Gym","You emerge into the Enterprise gym","The room is quite large, with a soft grey floor","A set of lockers against the southern wall contain all of the necessary equipment needed for using the gym","A thick stack of mats have been piled high in one corner, which can be used for different activities","Captain Picard likes to come here to practice his fencing"]).
 1312descriptionTest('iArea1030',["A Corridor","You find yourself in the middle of a well lit corridor on the Enterprise","It isn't very wide, and the light beige walls have been rounded, making the corridor an oval shape"]).
 1313descriptionTest('iArea1028',["Picard's Quarters","You find yourself standing by the door of Captain Picard's quarters","He isn't very fond of visitors, but you decide to stay and have a look around","You can see several different ancient artifacts on tables and small pedestals, and a large wooden wardrobe is facing south","A comfortable looking recliner with a matching footrest sits beside the door, along with a bright reading lamp and end table","Two large windows offer a great view of space","A small partition at the northern part of the room contains Picard's sleeping area"]).
 1314descriptionTest('iArea1029',["Science Lab","You're in the Enterprise science lab","A strange looking machine sits in the middle of the room, up on a slightly raised platform","It looks as though something(or someone) could be placed inside, hooked up to the multitude of wires and cables, and have scientific tests performed on it(or them)","A complex looking computer console is facing this machine","Around the rest of the room are counterops with with the odd computer terminal"]).
 1315descriptionTest('iArea1031',["Cargo Bay 2","You're in the cargo bay 2 of the Enterprise","It's quite a large room, with a very high ceiling and a lot of floor space","You can see several hundred plastic crates and barrels with the Starfleet insignia on them stacked right up to the ceiling"]).
 1316descriptionTest('iArea1033',["Turbolift","You're in the turbolift","The turbolift walls have been rounded off, making it in the shape of a tube","Several vertical rows of lights make this place very well lit","From here, you can access the other decks on the Enterprise"]).
 1317descriptionTest('iArea1034',["Turbolift","You're in the turbolift","The turbolift walls have been rounded off, making it in the shape of a tube","Several vertical rows of lights make this place very well lit","From here, you can access the other decks on the Enterprise"]).
 1318descriptionTest('iArea1036',["Main Bridge - Upper Half","You find yourself on the upper half of the main bridge of the USS Enterprise","Directly in front of you is a thick railing that contains many different computer panels used for the tactical systems of the ship","The entire southern wall is covered with computer consoles, where the ship's main systems are controlled","Two small curved ramps on either side of the room lead north to the lower part of the bridge, and a large circular skylight shows the space outside the ship"]).
 1319descriptionTest('iArea1035',["Picard's Ready Room","You're standing in Captain Picard's ready room","A long couch has been placed beside the door, while a large U shaped desk is located by the northern wall","A small computer screen is sitting on the desk, as well as several other papers and documents","A single high window beside the desk looks into space, and a fish tank is located in the northwestern corner of the room","This is where the Captain makes all of his important decisions"]).
 1320descriptionTest('iArea1038',["Main Bridge - Lower Half","You find yourself on the lower half of the main bridge of the USS Enterprise","An enormous view screen covers almost the entire northern wall, and is currently displaying a view of the stars rushing by","Three large chairs in the northern part of the room, in front of the railing, face the screen","This is where the Captain, Commander Riker, and Counselor Troi sit","Two computer consoles with built in chairs rest about ten feet in front of the chairs, also facing the view screen","This is where the ship's pilot and information officer sit"]).
 1321descriptionTest('iArea1037',["Conference Room","You're in the conference room of the Enterprise","A large glass rectangular table sits in the middle of the room, surrounded by about a dozen comfortable looking office chairs","The entire eastern wall is covered with windows, looking out into space","This is where the senior officers of the Enterprise meet and discuss important issues"]).
 1322descriptionTest('iArea1040',["Outer Space","You're floating in outer space right above the USS Enterprise","You can see stars in every direction, which provide the only light here","You feel very cold"]).
 1323descriptionTest('iArea1041',["Outer Space","You're floating in outer space right above the USS Enterprise","You can see stars in every direction, which provide the only light here","You feel very cold"]).
 1324
 1325
 1326% =================================================================
 1327% english2Kif
 1328% Contact: $Author: dmiles $@users.sourceforge.net ;
 1329% Version: 'interface.pl' 1.0.0
 1330% Revision:  $Revision: 1.9 $
 1331% Revised At:   $Date: 2002/06/27 14:13:20 $
 1332% ===================================================================
 1333% =================================================================
 1334/*
 1335
 1336clientEvent(Channel,Agent,english(phrase([learn|Input],Codes), _)):-!,
 1337	    AS = exec_lf(and(equals('?TargetAgent','Self'),equals('?Speaker',Agent),['or'|Ors])),
 1338	    findall(Kif,english2Kif(Input,Kif),Ors),fmt(AS).
 1339
 1340clientEvent(Channel,Agent,english(phrase(Input,Codes), _)):-
 1341	    AS = exec_lf(and(equals('?TargetAgent','Self'),equals('?Speaker',Agent),['or'|Ors])),
 1342	    findall(Kif,english2Kif(Input,Kif),Ors),
 1343	    sendEvent(Channel,Agent,(AS)).
 1344*/
 1345
 1346
 1347e2c(English):- english2Kif(English).
 1348e2c(English,CycLOut):- english2Kif(English,CycLOut),!.
 1349
 1350english2Kif(Sentence):- t_l:noreorder, english2Kif(Sentence,Kif),fmt(Kif).
 1351
 1352english2Obj(Sentence):-english2Obj(Sentence,Kif),portray_clause(Kif).
 1353
 1354english2Kif(Sentence,Kif):-
 1355  locally(thglobal:use_cyc_database,
 1356      (notrace(convertToWordage(Sentence,Words)),
 1357        wordageToKif(Words,Kif))).
 1358
 1359english2Obj(Sentence,noun_phrase(A,C)):-
 1360  locally(thglobal:use_cyc_database,
 1361      (notrace(convertToWordage(Sentence,Words)),
 1362         phrase(noun_phrase(A, _ ,C),Words))).
 1363
 1364english2Kif:-english2Kif('i am happy').
 1365
 1366
 1367% ===================================================================
 1368   
 1369
 1370convertToWordage(Var,Var):-var(Var),!.
 1371convertToWordage([],['True']):-!.
 1372convertToWordage(Atom,C):- not(is_list(Atom)),!,
 1373   must_det(to_word_list(Atom,List)),
 1374   must_det(convertToWordage(List,C)),!.
 1375
 1376convertToWordage(Words,C):- 
 1377      removeBlanks(Words,WordsO),
 1378  Words \=@= WordsO,!,
 1379   must_det(convertToWordage(WordsO,C)).
 1380
 1381convertToWordage(Words,C):- fail,
 1382      must_det(idioms(e2c,Words,WordsO)), % was chat
 1383   Words \=@= WordsO,!,
 1384   must_det(convertToWordage(WordsO,C)).
 1385
 1386  
 1387convertToWordage(Words,C):-  fail,
 1388      removeRepeats(Words,WordsO),
 1389   Words \=@= WordsO,!,
 1390   must_det(convertToWordage(WordsO,C)).
 1391
 1392convertToWordage(Words,Next):-
 1393      fdelete(Words,['Hm','hm','ah','uh','Uh','Um','um'],WordsNoIT),!,
 1394      vsubst(WordsNoIT,i,'I',Next),!.
 1395
 1396convertToWordage(O,O).
 1397
 1398removeRepeats(WordsNoIT,WordsNoITO):-
 1399      removeRepeats1(WordsNoIT,M),
 1400      removeRepeats2(M,WordsNoITO),!.
 1401removeRepeats(WordsNoIT,WordsNoIT).
 1402
 1403removeBlanks([],[]):-!.
 1404removeBlanks([H|T],TT):- is_blankWord(H),!,removeBlanks(T,TT),!.
 1405removeBlanks([H|T],[H|TT]):- removeBlanks(T,TT),!.
 1406
 1407
 1408non_blankWord(Var):-var(Var),!,fail.
 1409non_blankWord(B):-is_blankWord(B),!,fail.
 1410non_blankWord(_).
 1411
 1412is_blankWord(Var):-var(Var),!,fail.
 1413is_blankWord('').
 1414is_blankWord('\n').
 1415is_blankWord([]).
 1416is_blankWord([A]):-!,is_blankWord(A).
 1417
 1418% ================================
 1419% local helpers
 1420% ================================
 1421optionalText(X) --> { length(X,L),L > 0, L < 33 } , theText(X).
 1422optionalText(_) --> [].
 1423
 1424theVariable(Atom)--> theText([Longer]),{atom_concat(':',Atom,Longer)}.
 1425theVariable(Atom)--> theText([Atom]).
 1426
 1427isShortcut(X)--> theText(X).
 1428% =================================================================
 1429% wordageToKif
 1430% =================================================================
 1431      
 1432wordageToKif(Words,ResultO):- reverse(Words,[Symbol|Rev]),reverse(Rev,Quest),!,
 1433	 wordageToKif(Symbol,Words,Quest,ResultO). %,simplifyLF(Result,ResultO).
 1434
 1435% TODO move this to to the last clause
 1436wordageToKif(_Symbol,Words,_Quest,(words(Words):-POSList)):-get_wordage_list(Words,POSList).
 1437wordageToKif(('?'),_Words,Quest,query(Kif)) :- phrase(questionmark_sent(Kif),Quest).
 1438wordageToKif(('.'),_Words,Quest,assert(Kif)) :- phrase(period_sent(Kif),Quest).
 1439wordageToKif(('!'),_Words,Quest,assert(Kif)) :- phrase(period_sent(Kif),Quest).
 1440wordageToKif(Symbol,Words,_Quest,Kif) :- not(memberchk(Symbol,[('.'),('?'),('!')])),phrase(sentence(Kif),Words).
 1441wordageToKif(_Symbol,Words,_Quest,words(Words)).
 1442wordageToKif(_Symbol,Words,_Quest,posList(POSList,Words)):-get_pos_list(Words,POSList).
 1443
 1444% =================================================================
 1445% wordageToKif
 1446% =================================================================
 1447
 1448:-export(notPrefixOrSuffix/1). 1449notPrefixOrSuffix(CycWord):- not(cyckb_t_e2c(isa, CycWord, 'LexicalPrefix')),not(cyckb_t_e2c(isa, CycWord, 'LexicalSuffix')).
 1450is_cycWord_chk(CycWord):- cyckb_t_e2c(isa,CycWord,'EnglishWord'),!.
 1451
 1452usefull_wordage(Var):-var(Var),!,fail.
 1453usefull_wordage(wordage(_,Props)):-!,usefull_wordage(Props).
 1454usefull_wordage([txt([_,_|_])]):-!,fail. 
 1455usefull_wordage(X):-member(form(_,_,_),X).
 1456
 1457
 1458get_wordage_list(Words,O):- dictionary(slang,B,A),stringToWords(B,Didnt),stringToWords(A,NewList),append_ci(Didnt,Rest,Words),append(NewList,Rest,Ws),Words\=@=Ws,!,get_wordage_list(Ws,O).
 1459
 1460
 1461get_wordage_list([],[]):-!.
 1462% get_wordage_list(Words,O):- dictionary(contractions,Didnt,NewList), append_ci(Didnt,Rest,Words),append(NewList,Rest,Ws),Words\=@=Ws,!,get_wordage_list(Ws,O).
 1463get_wordage_list([W,'\'','nt'|Rest],O):- equals_icase(W,'do'), get_wordage_list([do,not|Rest],O).
 1464get_wordage_list([W,'\'','ve'|Rest],O):-get_wordage_list([W,have|Rest],O).
 1465get_wordage_list([W,'\'','re'|Rest],O):-get_wordage_list([W,are|Rest],O).
 1466get_wordage_list([W,'\'','nt'|Rest],O):-get_wordage_list([W,not|Rest],O).
 1467get_wordage_list([W,'\'','s'|Rest],O):-get_wordage_list([W,'appostrophyS'|Rest],O).
 1468% O'Brien
 1469get_wordage_list(['O','\'',Dell|Rest],[DCG|POSList]):-atom_concat('O\'',Dell,Pre),!,must_det((get_wordage([Pre],DCG),get_wordage_list(Rest,POSList))).
 1470get_wordage_list([Word,'s'|Rest],[DCG|POSList]):-atomic_list_concat([Word,'s'],'',Pre),get_wordage([Pre],DCG),usefull_wordage(DCG),!,get_wordage_list(Rest,POSList).
 1471get_wordage_list([Word,'\'',Contr|Rest],[DCG|POSList]):-atomic_list_concat([Word,'\'',Contr],'',Pre),get_wordage([Pre],DCG),usefull_wordage(DCG),!,get_wordage_list(Rest,POSList).
 1472get_wordage_list([W|Words],[DCG|POSList]):- parse_singularly(W),get_wordage([W],DCG),usefull_wordage(DCG),!,get_wordage_list(Words,POSList).
 1473get_wordage_list([W|Words],[DCG|POSList]):- not(parse_singularly(W)),member(X,[2,1,3]),length(Pre,X),append(Pre,Rest,[W|Words]),get_wordage(Pre,DCG),usefull_wordage(DCG),!,get_wordage_list(Rest,POSList).
 1474get_wordage_list([W|Words],[w(W)|POSList]):-get_wordage_list(Words,POSList).
 1475
 1476parse_singularly(W):-string(W),string_to_atom(W,A),!,parse_singularly(A).
 1477parse_singularly(W):-not(atom(W)),!.
 1478parse_singularly(W):-atom(W),atom_length(W,L),L<3.
 1479
 1480has_wordage(String):-is_wordage_cache(String,_).
 1481is_wordage_prop(String,Prop):-is_wordage_cache(String, wordage(_,Props)),!,member(Prop,Props).
 1482is_wordage_prop(String,Prop):-is_wordage_cache(String,Props),!,member(Prop,Props).
 1483
 1484:-dynamic(is_wordage_cache/2). 1485:-export(is_wordage_cache/2). 1486get_wordage([of, the],_Props):-!,fail.
 1487
 1488get_wordage(A,Props):-atom(A),!,get_wordage([A],Props).
 1489get_wordage(Pre,Props):-is_wordage_cache(Pre,Props),!.
 1490get_wordage(Pre,Props):-do_get_wordage(Pre,Props),!,ignore((usefull_wordage(Props),call(asserta,is_wordage_cache(Pre,Props)))).
 1491do_get_wordage(Pre,wordage(Pre,More)):- 
 1492  must_det(( wo_tl(t_l:omitCycWordForms,
 1493     wo_tl(t_l:allowTT,
 1494        locally(t_l:useOnlyExternalDBs,(findall(Prop,string_props(1,Pre,Prop),UProps),get_more_props(Pre,UProps,More))))))).
 1495   
 1496
 1497
 1498get_more_props(_,Props,Props):- memberchk(form(_,_,_),Props),memberchk(pos(_,_,_),Props),!.
 1499get_more_props(Pre,Props,More):-
 1500 wo_tl(t_l:omitCycWordForms,
 1501   locally(t_l:allowTT,
 1502     locally(t_l:useOnlyExternalDBs,((findall(Prop,string_props(2,Pre,Prop),UProps),
 1503      flatten([UProps,Props],UMore),list_to_set(UMore,More)))))).
 1504
 1505:-export(list_wordage/0). 1506
 1507list_wordage:- listing(is_wordage_cache),retractall(is_wordage_cache(_,_)).
 1508
 1509% :-list_wordage.
 1510% string_props(Pass,String,posMeans(POS,Form,CycL)):-posMeans(String,POS,Form,CycL).
 1511string_props(Pass,String,tt(Pass,CycWord,Form)):- 
 1512 locally(t_l:omitCycWordForms, locally(t_l:allowTT,(meetsForm(String,CycWord,Form),atom(Form),atom_concat(infl,_,Form),notPrefixOrSuffix(CycWord)))).
 1513string_props(1,[Num],number(Num)):-number(Num).
 1514string_props(1,[Atom],number(Num)):-atom_number(Atom,Num).
 1515string_props(1,Text,txt(Text)).
 1516string_props(Pass,[Num],Props):-number(Num),atom_number(Atom,Num),!,string_props(Pass,[Atom],Props).
 1517string_props(2,String,base(CycWord)):- stringToCycWord(String,CycWord).
 1518string_props(2,[String],Props):-toLowercase(String,Lower),String\=@=Lower,string_props(3,[Lower],Props).
 1519string_props(Pass,String,form(Pass,CycWord,Form)):- Pass\=@=2, meetsForm(String,CycWord,Form),notPrefixOrSuffix(CycWord).
 1520string_props(Pass,String,pos(3,CycWord,POS)):- Pass\=@=2, meetsPos(String,CycWord,POS),notPrefixOrSuffix(CycWord).
 1521
 1522
 1523%string_props(Pass,[String],PredProps):-!,  is_speechPartPred_tt(Pred),cyckb_t_e2c(Pred,CycWord,String),pred_props(Pred,CycWord,PredProps).
 1524%string_props(Pass,String,PredProps):- is_speechPartPred_tt(Pred),cyckb_t_e2c(Pred,CycWord,String),pred_props(Pred,CycWord,PredProps).
 1525
 1526posName(POS):-
 1527  member(POS,['Preposition','Verb','Conjunction','Determiner','Pronoun','Adjective',
 1528   'Noun','Adverb','Number','Punctuation','Quantifier','QuantifyingIndexical']).
 1529posAttrib(POS):-posName(POS).
 1530posAttrib(POS):-member(POS,['Untensed','Tensed','Aux','Be','Do']).
 1531posAttrib(POS):-posAttrib_lc(POS).
 1532
 1533posAttrib_lc(POS):-member(POS,['NonSingular','NonPlural','Expletive','ThirdPerson','NonThird','SecondPerson','FirstPerson','Mass','Agentive','Gerundive',
 1534                              'Nongradable','Gradable',
 1535                       'Singular','Present','Indicative','Participle','Universal','Infinitive','Generic','Superlative','Plural',
 1536                        'Indefinite','Past','Particle','WH','Denominal',
 1537                       'Simple','Count','Proper','Active','Passive','Unchecked','Object','Possessive','Feminine','Masculine','Neuter',
 1538                       'Reciprocal','Reflexive','SubjectOrObject','Subject','PasseSimple','Future']).
 1539
 1540posSubProp(SUB,POS):-member(SUB-POS,['firstPerson'-'Pronoun','Sg'-'Singular','Pl'-'Plural','gerund'-'Gerundive','3rd'-'ThirdPerson','1st'-'FirstPerson','2nd'-'SecondPerson', 'pn'-'Proper']).
 1541posSubProp(SUB,POS):-posAttrib_lc(POS),string_lower(POS,Low),string_to_atom(Low,SUB).
 1542
 1543pred_props(Compound,_,_):-compound(Compound),!,fail.
 1544pred_props(NI,_,_):- atom_contains(NI,'NameInitial'),!,fail.
 1545pred_props(_,Compound,_):-compound(Compound),!,fail.
 1546pred_props(_,'He-TheWord',_):-!,fail.
 1547pred_props(Pred,CycWord,form(2,CycWord,Pred)).
 1548pred_props(Pred,CycWord,pos(2,CycWord,POS)):-
 1549 posAttrib(POS),
 1550 atom_contains(Pred,POS).
 1551pred_props(Pred,CycWord,pos(3,CycWord,POS)):- posSubProp(SUB,POS),atom_contains(Pred,SUB),not(atom_contains(Pred,POS)).
 1552
 1553
 1554% string_props(Pass,String,cycl(Form)):-  meetsForm(String,CycWord,Form),notPrefixOrSuffix(CycWord).
 1555
 1556:-dynamic(word_no_pos/1). 1557
 1558get_pos_list([],[]):-!.
 1559get_pos_list(Words,[DCG|POSList]):- between(1,3,X),length(Pre,X),append(Pre,Rest,Words),get_dcg(DCG,Pre),get_pos_list(Rest,POSList).
 1560get_pos_list([W|Ords],[w(W)|POSList]):-assert_if_new(word_no_pos(W)),get_pos_list(Ords,POSList).
 1561   
 1562get_dcg(DCG,Pre):- dcgPredicate(baseKB,F,_,P),once((P=..[F|ARGS],append(LDCG,[S,E],[F|ARGS]),S=Pre,E=[])),call(P),DCG=..LDCG.
 1563
 1564dcgPredicate(M,F,A,P):- module_property(M, exports(List)),member(F/A,List),is_dcg_pred(M,F,A,P).
 1565dcgPredicate(M,F,A,P):- module_property(M, exports(List)),
 1566 findall(F/A,(module_predicate(M,F,A),
 1567   not(member(F/A,List))), Private),
 1568   member(F/A,Private),is_dcg_pred(M,F,A,P).
 1569
 1570:- style_check(-singleton). 1571is_dcg_pred(M,F,A,P):-A >= 2, functor(P,F,A),M:predicate_property(P,number_of_rules(N)),N>0,!, M:clause(P,B),compound(B),arg(A,P,LA),var(LA),\+ \+ is_dcg_pred_pass2(M,F,A,P,B),!.
 1572%is_dcg_pred_pass2(M,F,A,P,B):- pred_contains_term(vcall((compound(B),functor(B,phrase,3))),B,_Match).
 1573is_dcg_pred_pass2(M,F,A,P,B):- pred_contains_term('==',B,phrase).
 1574is_dcg_pred_pass2(M,F,A,P,B):- ((P=..[F|ARGS],append(_LDCG,[S,E],[F|ARGS]), S =@= [_|_], pred_contains_term('=@=',B, _=_ ))).
 1575:- style_check(+singleton). 1576
 1577
 1578
 1579% makes pred_contains_term(vcall(Call), A, B)  work!
 1580vcall(Call,A,B):- vsubst(Call,A,B,VCall),!,VCall.
 1581pred_contains_term(Pred, A, B) :- call(Pred, A, B).
 1582pred_contains_term(Pred, A, B) :- compound(A), (functor(A,C,_);arg(_, A, C)), pred_contains_term(Pred,C, B), !.
 1583
 1584%:-disable_body_textstr.
 1585% % :- enable_body_textstr.
 1586
 1587
 1588:-discontiguous(simplifyLF/2). 1589% =======================================================
 1590% sentence(CycL, [every,man,that,paints,likes,monet],[]) 
 1591% =======================================================
 1592%sentence(S) --> conjunct(_),!,syntact(S).
 1593%sentence(S) --> interjections(_),!,syntact(S).
 1594questionmark_sent(true(CycL)) --> assertion_nl(CycL).
 1595questionmark_sent(interogative(CycL)) --> interogative(CycL).
 1596questionmark_sent(areDoing(CycL)) --> imparative(CycL).
 1597
 1598simplifyLF(true(X),X).
 1599simplifyLF(yn(X),X).
 1600
 1601period_sent(CycL) --> assertion_nl(CycL).
 1602period_sent(command(Act)) --> imparative(Act).
 1603period_sent(interogative(CycL)) --> interogative(CycL).
 1604
 1605simplifyLF(interogative(X),X).
 1606simplifyLF(command(X),X).
 1607
 1608sentence(command(Act)) --> imparative(Act).
 1609sentence(assert(CycL)) --> assertion_nl(CycL).
 1610sentence(query(CycL)) --> interogative(CycL).
 1611    
 1612simplifyLF(interogative(X),X).
 1613simplifyLF(assert(X),assert(X)).
 1614
 1615literal([E|F], C, B):-!,append([E|F],B, C).
 1616literal(E, [E|C], C).
 1617literal([], C, C).
 1618
 1619% =================================================================
 1620% interjections  TODO
 1621% =================================================================
 1622interjections(interject(W)) --> interjection(W).
 1623interjections(interjects(H,T)) --> interjection(H),interjections(T).
 1624
 1625interjection(C) --> isPOS('Interjection-SpeechPart',C).
 1626
 1627
 1628
 1629% =================================================================
 1630% imparative  TODO
 1631% =================================================================
 1632
 1633% tell me
 1634imparative(CycL) --> verb_phrase(TargetAgent,ImparitiveEvent,CycL),
 1635	 {varnameIdea('?TargetAgent',TargetAgent),varnameIdea('ImparitiveEvent',ImparitiveEvent)}.
 1636
 1637% =================================================================
 1638% interogative  TODO
 1639% =================================================================
 1640% How are you
 1641% What have you
 1642% What do you have?
 1643% What do you think?
 1644% How will you
 1645% Could the dog
 1646% could he think of it? 
 1647% are you happy
 1648% * ?
 1649interogative(CycL) --> verb_phrase(TargetAgent,ImparitiveEvent,CycL),
 1650	 {varnameIdea('?TargetAgent',TargetAgent),varnameIdea('QuestionEvent',ImparitiveEvent)}.
 1651
 1652% =================================================================
 1653% assertion_nl
 1654% =================================================================
 1655% Now lets say that the input values for the memory NN uses the pattern from the other nodes output
 1656% our naming specialist, Linda Bergstedt
 1657% it is good
 1658% the fubar licks the bowl
 1659% It should be a mix.
 1660
 1661% the dog licks the bowl
 1662assertion_nl(CycL) --> noun_phrase(Subj,CycL1,CycL),verb_phrase_after_nouns(Subj,_Event,CycL1).
 1663
 1664
 1665% gen assertion 1
 1666assertion_nl(gen_assert(Call,Result)) --> [S],
 1667	    { 'genFormat'(Predicate,[S|Template],ArgsI),atom(Predicate),
 1668	    (compound(ArgsI) -> trasfromArgs(ArgsI,Args) ; Args=[1,2]),
 1669	    length(Args,Size),functor(Call,Predicate,Size),
 1670	    placeVars(Blanks,Args,Call)},
 1671	    do_dcg(Template,Blanks,Result).
 1672
 1673assertion_nl(gen_assert(Predicate)) --> [S],
 1674	    { 'genFormat'(Predicate,S, _) }.
 1675
 1676% =================================================================
 1677% WHORDS
 1678% =================================================================
 1679
 1680% which do
 1681what_do(W,V) --> query_starter(W),isPOS('DoAux',V).
 1682
 1683% where 
 1684%query_starter(W)  --> isPOS('WHAdverb',W).
 1685% could / which
 1686query_starter(W)  --> isPOS('Modal',W);isPOS('WHWord',W).
 1687
 1688% =======================================================
 1689% Rel Clauses
 1690% =======================================================
 1691
 1692% Linda Bergstedt
 1693human_name(([First,Last])) --> capitolWord(First),capitolWord(Last).
 1694% Linda
 1695human_name(Name) --> capitolWord(Name). 
 1696
 1697capitolWord(A) --> [A],{atom(A),atom_codes(A,[C|_]),char_type(C,upper)}.
 1698
 1699% =======================================================
 1700% Nouns Phrases
 1701% =======================================================
 1702% =======================================================
 1703% TODO
 1704%'properNounSemTrans'('Egyptian-TheWord', 0, 'RegularNounFrame', 'citizens'('Egypt', ':NOUN'), 'GeneralEnglishMt', v(v('Egypt', 'Egyptian-TheWord', 'RegularNounFrame', 'citizens', ':NOUN'), A)).
 1705% =======================================================
 1706
 1707
 1708% TODO
 1709% =======================================================
 1710%'nlPhraseTypeForTemplateCategory'('PhraseFn-Bar1'('Verb'), 'PerfectiveVBarTemplate', 'AuxVerbTemplateMt', v(v('PerfectiveVBarTemplate', 'PhraseFn-Bar1', 'Verb'), A)).
 1711
 1712
 1713% TODO
 1714% =======================================================
 1715%'nounSemTrans'('Aspect-TheWord', 0, nartR('PPCompFrameFn','TransitivePPCompFrame', 'Of-TheWord'), 'hasAttributes'(':OBLIQUE-OBJECT', A), 'GeneralEnglishMt', v(v('Aspect-TheWord', 'Of-TheWord', 'PPCompFrameFn', 'TransitivePPCompFrame', 'hasAttributes', ':OBLIQUE-OBJECT'), ['?ATTR'=A|B])).
 1716
 1717% TODO
 1718% a man hapilly maried
 1719% a man who knows
 1720% a man of his word that walks
 1721% a man of his word
 1722% the cost of what the product is
 1723
 1724
 1725%noun_phrase(Subj,In,also(A,LL)) --> [A|LL],{cont ([A|LL])}.
 1726
 1727noun_phrase(_ ,_ , _) --> dcgStartsWith1(isPOS(DET)),{ cantStart(noun_phrase,DET), !,fail}. 
 1728
 1729noun_phrase(List, In, Out, [M,N,O|More], F):- 
 1730 (nth1(Loc,[M,N,O],(','));nth1(Loc,[M,N,O],'and')),
 1731   noun_phrase_list(Loc,List, In, Out, [M,N,O|More], F).
 1732
 1733% a man that walks
 1734noun_phrase(S,A,B)-->subject5(S,A,B). 
 1735
 1736noun_phrase_list(_  ,[H],In,Out) --> subject5(H,In,Out).
 1737noun_phrase_list(Loc,[H|T],In,Out) --> ([and];[(',')];[]),
 1738      subject5(H,In,Mid),([and];[(',')];[]),
 1739      noun_phrase_list(Loc,T,Mid,Out),{!}. 
 1740
 1741
 1742%rel_clause(Subj,HowDoes) -->isPOS('Complementizer',Modal,String),verb_phrase(Subj,Event,HowDoes),{varnameIdea(String,Event)}.
 1743noun_phrase_rel_clause(_Loc,Subj,In,rel_clause(In,Out)) -->  % {stack_depth(SD), SD<600},
 1744	 subject5(Subj,HowDoes,Out), 
 1745	 (isPOS('Complementizer',_ModalWord,_String);[]),
 1746	 verb_phrase(Subj,_Event,HowDoes).
 1747
 1748% =======================================================
 1749subject_isa(_SubjectIsa,Subj,Template,TemplateO) --> subject5(Subj,Template,TemplateO).
 1750
 1751
 1752% =======================================================
 1753
 1754%subject5(_ , _ , _ ) --> isPOS('Verb', _),{!,fail}, _.
 1755
 1756% a man who|that walks
 1757subject5(List, In, Out, [M,N,O|More], F) :-
 1758      nonvar(More),
 1759      (nth1(Loc,[M,N,O],'who');nth1(Loc,[M,N,O],'that')),
 1760      noun_phrase_rel_clause(Loc,List, In, Out, [M,N,O|More], F).
 1761
 1762
 1763% =======================================================
 1764% 'Determiner-Indefinite' , 'Determiner-Definite'
 1765%'determinerAgreement'('A-Half-Dozen-MWW', 'plural-Generic', ..)
 1766
 1767% all dogs
 1768subject5(Subj,In,'forAll'(Subj,AttribIsa)) --> 
 1769    ([every];[all];[forall];[each];[for,all]),
 1770    det_object(Subj,In,AttribIsa).
 1771
 1772
 1773% the happy dog
 1774%subject5(X,In,referant(X,isa(X,Subj),AttribIsa)) --> [the],      det_object(Subj,In,AttribIsa),{varnameIdea('Thing',X),!}.
 1775subject5(Subj,In,AttribIsa) --> [the],det_object(Subj,In,AttribIsa).
 1776
 1777% a dog
 1778subject5(Subj,In,'thereExists'(Subj,AttribIsa)) --> 
 1779    ([a];[an];[some];[there,is];[there,are];[there,exists]),
 1780    det_object(Subj,In,AttribIsa).
 1781
 1782% your rainbow
 1783subject5(X,A,and(ownedBy(X,Agent),isa(X,Thing),B)) --> possessive(Agent),noun_phrase(Thing,A,B),{varnameIdea('Thing',X),!}.
 1784
 1785% he
 1786subject5(PN,CycL,CycL) --> pronoun(PN),{!}.
 1787
 1788% Joe blow
 1789subject5(named(Name),CycL,CycL) --> human_name(Name),{!}.
 1790
 1791% a man
 1792
 1793% dog
 1794subject5(Subj,In,AttribIsa) --> det_object(Subj,In,AttribIsa).
 1795
 1796:- style_check(-singleton). 1797
 1798:- discontiguous(det_object//3). 1799
 1800det_object(_,_,_) --> isPOS(DET),{ cantStart(noun_phrase,DET), !,fail}. 
 1801
 1802% =======================================================
 1803%'multiWordSemTrans'([equilateral], 'Shaped-TheWord', 'Adjective', 'RegularAdjFrame', 'shapeOfObject'(':NOUN', 'EquilateralShaped'), 'EnglishMt', v(v('Adjective', 'EquilateralShaped', 'RegularAdjFrame', 'Shaped-TheWord', 'shapeOfObject', ':NOUN', equilateral), A)).
 1804det_object(Subj,In,in_and(In,Extras,Out)) --> [S],
 1805  {'multiWordSemTrans'([S|String],CycWord, 'Adjective', NextFrame,Template)},
 1806     String, isCycWord(CycWord), frame_template(NextFrame,Subj,Result,Extras),
 1807    {apply_frame(Template,Subj,_Event,_Obj,Result,Out)}.
 1808
 1809det_object(Subj,In,Out) --> 
 1810	 isPOS('Adjective',CycAdj),
 1811	 det_object_adj(CycAdj,Subj,In,Out).
 1812
 1813% =======================================================
 1814%'adjSemTrans-Restricted'('Wooden-TheWord', 0, 'RegularAdjFrame', 'Artifact', 'isa'(':NOUN', 'Wood'), 'GeneralEnglishMt', v(v('Artifact', 'RegularAdjFrame', 'Wood', 'Wooden-TheWord', 'isa', ':NOUN'), A)).
 1815det_object_adj(CycAdj,Subj,In,in_and(In,nop(frameType(FrameType)),Out)) --> 
 1816	 {'adjSemTrans-Restricted'(CycAdj, _ , FrameType, NounIsa, Template)},
 1817	subject_isa(NounIsa,Subj,Template,TemplateO),
 1818      {apply_frame(TemplateO,Subj,Event,Obj,Result,Out)}.
 1819
 1820% =======================================================
 1821%'adjSemTrans'('Tame-TheWord', 0, 'RegularAdjFrame', 'isa'(':NOUN', 'TameAnimal'), 'GeneralEnglishMt', v(v('RegularAdjFrame', 'Tame-TheWord', 'TameAnimal', 'isa', ':NOUN'), A)).
 1822%'adjSemTransTemplate'('ColorTingeAttribute', 'RegularAdjFrame', 'objectHasColorTinge'(':NOUN', ':DENOT'), 'GeneralEnglishMt', v(v('ColorTingeAttribute', 'RegularAdjFrame', 'objectHasColorTinge', ':DENOT', ':NOUN'), A)).
 1823det_object_adj(CycAdj,Subj,In,and(Extras,Out)) --> 
 1824	 {'adjSemTrans'(CycAdj, _ , FrameType, Template);
 1825	 ('adjSemTransTemplate'(AdjIsa, FrameType, Template),cycQueryIsa(CycAdj,AdjIsa))},
 1826	frame_template(NextFrame,Subj,Result,Extras),
 1827      {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 1828
 1829
 1830det_object_adj(CycAdj,Subj,In,and(Isa,hasTrait(Subj,CycL))) -->
 1831       det_object(Subj,In,Isa),{cvtWordPosCycL(CycAdj,'Adjective',CycL),!}.
 1832
 1833% =======================================================
 1834det_object(Subj,In,Isa) --> object5(Subj,In,Isa).
 1835
 1836% =======================================================
 1837det_object(PN,CycL,CycL) --> proper_object(PN).
 1838
 1839%'multiWordSemTrans'([intended, recipient, of], 'Communicate-TheWord', 'SimpleNoun', 'RegularNounFrame', 'communicationTarget'(A, ':NOUN'), 'EnglishMt', v(v('Communicate-TheWord', 'RegularNounFrame', 'SimpleNoun', 'communicationTarget', ':NOUN', intended, of, recipient), ['?X'=A|B])).
 1840object5(Subj,In,'and'(In,Out)) --> [S],
 1841   {'multiWordSemTrans'([S|String],CycWord,POS, NextFrame,Template),POS \=@= 'Adjective'},
 1842     String,isCycWord(CycWord), frame_template(NextFrame,Subj,Result,Extras),
 1843    {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 1844
 1845% =======================================================
 1846%'nounPrep'('Address-TheWord', 'Of-TheWord', ['pointOfContactInfo', ':OBLIQUE-OBJECT', 'ContactLocation', 'addressText', ':NOUN']).
 1847%'nounPrep'('Retail-TheWord', 'Of-TheWord', ['sellsProductType', ':NOUN', ':OBLIQUE-OBJECT']).
 1848%'nounPrep'('Market-TheWord', 'Of-TheWord', ['sellsProductType', ':NOUN', ':OBLIQUE-OBJECT']).
 1849%'nounPrep'('Start-TheWord', 'Of-TheWord', ['startingPoint', ':OBLIQUE-OBJECT', ':NOUN']).
 1850%'nounPrep'('City-TheWord', 'Of-TheWord', 'equals'(':OBLIQUE-OBJECT', ':NOUN'), 'EnglishMt', v(v('City-TheWord', 'Of-TheWord', 'equals', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 1851%'nounPrep'('Victim-TheWord', 'Of-TheWord', 'victim'(':OBLIQUE-OBJECT', ':NOUN'), 'EnglishMt', v(v('Of-TheWord', 'Victim-TheWord', 'victim', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 1852object5(Subject,In,and(CycL,Out)) --> isPOS('Noun',CycWord), 
 1853      {'nounPrep'(CycWord,CycWordPrep, Template)},
 1854      isCycWord(CycWordPrep),subject5(Result,In,CycL),
 1855    {apply_frame(Template,Subject,Event,Object,Result,Out)}.
 1856
 1857% the happy dog
 1858object5(Subj,CycL,and(CycL,Isa)) --> colection(Subj,Isa).
'team-mate' happy dog kickoff call
 1864colection(Subj,isaMember(Subj,W)) --> [W],{atom(W),atom_concat('', _ ,W),!}.
 1865colection(Subj,isaMember(Subj,CycL)) --> isPOS('Noun',CycWord,String),
 1866	    {cvtWordPosCycL(CycWord,'Noun',CycL),varnameIdea(String,Subj),!}.
 1867
 1868wordPosCycL(CycWord,POS,CycL):-
 1869      'denotation'(CycWord,POS, _ , CycL);'denotationRelatedTo'(CycWord,POS, _ , CycL).
 1870wordPosCycL(CycWord,POS,CycL):- 'genls'(Child,POS),wordPosCycL(CycWord,Child,CycL).
 1871wordPosCycL(CycWord, _ ,CycL):-
 1872      'denotation'(CycWord,POS, _ , CycL);'denotationRelatedTo'(CycWord,POS, _ , CycL).
 1873      
 1874
 1875cvtWordPosCycL(CycWord,POS,CycL):-wordPosCycL(CycWord,POS,CycL),!.
 1876cvtWordPosCycL(CycWord,POS,CycL):-CycL=..[POS,CycWord],!.
 1877% ==========================================================
 1878% String to CYC -POS
 1879% ==========================================================
 1880:- discontiguous(proper_object//1). 1881
 1882proper_object(CycL) --> dcgStartsWith1(isPOS(DET)),{ cantStart(noun_phrase,DET), !,fail}. 
 1883proper_object(CycL) --> theText([S,S2]),{poStr(CycL,[S,S2|String])},theText(String).
 1884proper_object(CycL) --> theText([String]),{poStr(CycL,[String])}.
 1885proper_object(multFn(Multiply,Collection)) --> [String],
 1886	 {'unitOfMeasurePrefixString'(Multiply, Affix),
 1887	 words_concat(Affix,Rest,String),!,phrase(collection3(Collection),[Rest])}.
 1888proper_object(CycL) --> pos_cycl(Noun,CycL), { goodStart(noun_phrase,Noun) } .
 1889
 1890
 1891poStr(CycL,String):- stringArg(String, poStr0(CycL,String)).
 1892poStr0(CycL,String):- strings_match,
 1893      'genlPreds'(FirstName,'nameString'),
 1894       cyckb_t_e2c(FirstName,CycL,String).
 1895
 1896poStr0(CycL,String):- strings_match,
 1897      'initialismString'(CycL,String);
 1898      'abbreviationString-PN'(CycL,String);
 1899      'preferredNameString'(CycL,String);
 1900      'countryName-LongForm'(CycL,String);
 1901      'countryName-ShortForm'(CycL,String);
 1902      'acronymString'(CycL,String);
 1903      'scientificName'(CycL,String);
 1904      'termStrings'(CycL,String);
 1905      'termStrings-GuessedFromName'(CycL,String);
 1906      'prettyName'(CycL,String);
 1907      'nameString'(CycL,String);
 1908      'nicknames'(CycL,String);
 1909      'preferredTermStrings'(CycL,String).
 1910
 1911
 1912%possessive(Agent)-->pronoun(Agent),isCycWord('Have-Contracted'),{!}.
 1913possessive(Agent)-->pronoun(Agent),isCycWord('Be-Contracted').
 1914possessive(Agent)-->isPOS('PossessivePronoun-Pre',Agent).
 1915possessive(Agent)-->isPOS('PossessivePronoun-Post',Agent).
 1916possessive(Inters)-->human_name(Inters),['\'',s].
 1917%possessive(Agent)-->pronoun(Agent).
 1918
 1919pronoun('?Speaker') --> ['i'];['I'];isCycWord('I-TheWord');isCycWord('Me-TheWord').
 1920pronoun('?He') --> isCycWord('He-TheWord').
 1921pronoun('?TargetAgent') --> isCycWord('You-TheWord').
 1922pronoun('?Where') --> isCycWord('Where-TheWord').
 1923pronoun('?How') --> isCycWord('How-TheWord').
 1924pronoun('?IT') --> isCycWord('It-TheWord').
 1925pronoun('?She') --> isCycWord('She-TheWord').
 1926
 1927pronoun(X) --> wh_pronoun(X).
 1928pronoun(ref(CycWord)) --> isPOS('Pronoun', CycWord).
 1929
 1930wh_pronoun('?Agent') --> [who].
 1931wh_pronoun('?What') --> [what].
 1932
 1933% =======================================================
 1934% Qualified Noun
 1935% =======================================================
 1936collection_noun_isa(Subj,'isa'(Subj,CycLCollection)) --> collection_noun(Subj,CycLCollection).
 1937
 1938collection_noun(Subj,CycLCollection) --> [A,B,C,D],{phraseNoun([A,B,C,D],Form,Subj,CycLCollection)}.
 1939collection_noun(Subj,CycLCollection) --> [A,B,C],{phraseNoun([A,B,C],Form,Subj,CycLCollection)}.
 1940collection_noun(Subj,CycLCollection) --> [A,B],{phraseNoun([A,B],Form,Subj,CycLCollection)}.
 1941collection_noun(Subj,CycLCollection) --> [A],{phraseNoun([A],Form,Subj,CycLCollection)}.
 1942collection_noun(Subj,'AdultMalePerson') --> [man].
 1943
 1944collection3(M)--> collection_noun('?Subj',CycLCollection).
 1945
 1946phraseNoun(Eng,Form,Subj,CycLCollection):-
 1947      phraseNoun_each(Eng,Form,CycLCollction),
 1948      eng_subj(Eng,Subj).
 1949
 1950eng_subj(Eng,Subj):-var(Subj),getVarAtomName(Subj,Atom),concat_atom([?|Eng],'',T),atom_concat(T,Atom,Subj).
 1951eng_subj(Eng,Subj):-!.
 1952
 1953getVarAtomName(Value,Name):-var(Value),!,term_to_atom(Value,Vname),atom_codes(Vname,[95, _|CODES]),atom_codes(Name,CODES),!.
 1954getVarAtomName('$VAR'(VNUM),Name):-concat_atom([VNUM],Name),!.
 1955
 1956
 1957phraseNoun_each(Eng,Form,CycL):-posMeans(Eng,'SimpleNoun',Form,CycL).
 1958phraseNoun_each(Eng,Form,CycL):-posMeans(Eng,'MassNoun',Form,CycL).
 1959phraseNoun_each(Eng,Form,CycL):-posMeans(Eng,'AgentiveNoun',Form,CycL).
 1960phraseNoun_each(Eng,Form,CycL):-posMeans(Eng,'Noun',Form,CycL).
 1961phraseNoun_each(Eng,Form,CycL):-posMeans(Eng,'QuantifyingIndexical', _ ,CycL).
 1962							 
 1963
 1964% =======================================================
 1965% Conjunctions
 1966% =======================================================
 1967% [that];[who]
 1968
 1969conjunct --> conjunct(X).
 1970conjunct(C) --> isPOS('CoordinatingConjunction',C).
 1971conjunct(and_also)--> [and];[also].
 1972
 1973disj_word --> [or];[not];[but].
 1974
 1975
 1976modal_phrase(CycAuxVerb,Subj,Event,Out)-->aux_phrase(CycAuxVerb,Subj,Event,Out).
 1977% =======================================================
 1978% Aux Phrases
 1979% =======================================================
 1980
 1981% is good, was meaningfull ,  are greatfull
 1982aux_phrase('Be-TheWord',Subj,Event,and(Frame,hasTrait(Subj,AdjFrame))) -->
 1983         isPOS('Adjective',NomicAdj),
 1984      aux_phrase('Be-TheWord',Subj,Event,Frame),
 1985      {cvtWordPosCycL(NomicAdj,'Adjective',AdjFrame)}.
 1986
 1987
 1988% can
 1989aux_phrase('Can-TheModal',Subj,Event,'can'(Subj,Frame)) --> 
 1990	  verb_phrase(Subj,Event,Frame).
 1991
 1992% do/is/be/does
 1993aux_phrase(CycAuxVerb,Subj,Event,aux_isa_for(Subj,Event,Action)) --> [],
 1994	 {cvtWordPosCycL(CycAuxVerb,'Verb',Action)}.
 1995
 1996% do <X>
 1997aux_phrase('Do-TheWord',Subj,Event,(CycL)) --> 
 1998	 verb_phrase(Subj,Event,CycL) .
 1999
 2000% =======================================================
 2001%'verbPrep-Passive'('Make-TheWord', 'Of-TheWord', 'mainConstituent'(':OBJECT', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Make-TheWord', 'Of-TheWord', 'mainConstituent', ':OBJECT', ':OBLIQUE-OBJECT'), A)).
 2002aux_phrase(CycWord,Subj,Event,CycLO) --> 
 2003      {'verbPrep-Passive'(CycWord, CycWord2, Template)},
 2004       isCycWord(CycWord2),subject5(Result,Out,CycLO),
 2005      {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 2006
 2007% =======================================================
 2008%'prepSemTrans'('Above-TheWord', 0, 'Post-NounPhraseModifyingFrame', 'above-Generally'(':NOUN', ':OBJECT'), 'GeneralEnglishMt', v(v('Above-TheWord', 'Post-NounPhraseModifyingFrame', 'above-Generally', ':NOUN', ':OBJECT'), A)).
 2009aux_phrase(CycAuxWord,Subj,Event,Out) -->
 2010      {'prepSemTrans'(CycWordPrep, _ , NextFrame, Template)},
 2011      isCycWord(CycWordPrep),subject5(Obj,Out,CycLO),
 2012    {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 2013
 2014% =======================================================
 2015% preopistional_phrase
 2016% =======================================================
 2017preopistional_phrase(Oblique,CycWord,CycL) -->
 2018	 isPOS('Preposition',CycWord), 
 2019	 noun_phrase(Oblique,Prep,CycL),{varnameIdea('Prep',Prep)}.
 2020      
 2021% =======================================================
 2022% verb_phrase
 2023% =======================================================
 2024
 2025:- style_check(-discontiguous). 2026
 2027% no verb
 2028verb_phrase(_ , _ , _ ) --> dcgStartsWith1(isPOS(DET)),{ cantStart(verb_phrase,DET), !,fail}.
 2029
 2030verb_phrase_after_nouns(Subj,Event,exists(Subj)) --> [].
 2031
 2032verb_phrase_after_nouns(Subj,Event,exists(Subj,'verb_phrase')) --> isShortcut('verb_phrase').
 2033
 2034verb_phrase_after_nouns(Subj,Event,CycL) --> verb_phrase(Subj,Event,CycL).
 2035
 2036% One verb
 2037% verb_phrase(Subj,Event,do(Subj,Verb)) --> [Verb].
 2038
 2039% known phrase
 2040verb_phrase(Subj,Event,known_phrase(CycL)) --> 
 2041	    isPOS('Verb',CycVerb),
 2042	    verb_phrase_known(CycVerb,Subj,Event,CycL).
 2043
 2044% gen phrase 2
 2045verb_phrase(Subj,Event,gen_phrase2(Call,Result)) --> [S,N],
 2046	    { 'genFormat'(Predicate,['~a',S,N|Template],ArgsI),atom(Predicate),
 2047	    (compound(ArgsI) -> trasfromArgs(ArgsI,Args) ; Args=[1,2]),
 2048	    length(Args,Size),functor(Call,Predicate,Size),
 2049	    placeVars([Subj|Blanks],Args,Call)},
 2050	    do_dcg(Template,Blanks,Result).
 2051	    
 2052% modal phrase
 2053verb_phrase(Subj,Event,modal(CycL)) --> 
 2054	    isPOS('Modal',CycWord,String),
 2055	    modal_phrase(CycWord,Subj,Event,CycL),{varnameIdea(String,Event)}.
 2056
 2057% aux phrase
 2058verb_phrase(Subj,Event,(CycL)) --> 
 2059	    isPOS('AuxVerb',CycWord,String),
 2060	    aux_phrase(CycWord,Subj,Event,CycL),{varnameIdea(String,Event)}.
 2061
 2062% adverbal phrase
 2063verb_phrase(Subj,Event,'and_adverbal'(Event,AdvCycL,CycL))  --> 
 2064	    isPOS('Adverb',CycWord),
 2065	    verb_phrase(Subj,Event,CycL),
 2066	    {cvtWordPosCycL(CycWord,'Adverb',AdvCycL)}.
 2067
 2068% unknown phrase has arity CycL + object5 %TODO rename subject5/3 to noun_phrase/3
 2069verb_phrase(Subj,Event,and_concat(CycL)) --> [Verb],
 2070	 {atom(Verb),((words_concat('',Verb,Predicate),cyckb_t_e2c('arity',Predicate,N));(cyckb_t_e2c('arity',Verb,N),Predicate=Verb)),!},
 2071	 verb_phrase_arity(N,Predicate,Subj,Event,CycL).
 2072
 2073% :-index(verb_phrase_arity(0,0,0,0,0,0,0)).
 2074%TODO rename subject5/3 to noun_phrase/3
 2075verb_phrase_arity(2,Predicate,Subj,Event,CycL) --> 
 2076	       best_subject(Obj,ACT,Mid),
 2077	       colect_noun_list(List,Mid,CycL),
 2078	       {apply_act(Predicate,Subj,[Obj|List],ACT)}.
 2079%and
 2080verb_phrase_arity(3,Predicate,Subj,Event,CycL) --> 
 2081	 best_subject(Obj,Event,Mid),
 2082	 best_subject_constituant(RES,Event,Mid,CycL),
 2083	{ACT=..[Predicate,Subj,Obj,RES]}.
 2084
 2085colect_noun_list([],In,In) --> [].
 2086colect_noun_list([H|T],In,Out) --> ([(',')];[and];[]),
 2087      best_subject(H,In,Mid),
 2088      colect_noun_list(T,Mid,Out).
 2089
 2090verb_phrase(Subj,Event,(CycL)) --> 
 2091	 isPOS('Verb',CycVerb,String),
 2092%	 best_subject(Obj,true,CycL),
 2093 %        best_subject_constituant(Target,Event,CycL,CycLO),
 2094	 {cvtWordPosCycL(CycVerb,'Verb',Verb),
 2095	 (atom(Verb),(atom_concat('',Verb,Predicate),cyckb_t_e2c('arity',Predicate,N));(cyckb_t_e2c('arity',Verb,N),Predicate=Verb)),!},
 2096	  verb_phrase_arity(N,Predicate,Subj,Event,CycL),{varnameIdea(String,Event)}.
 2097	 
 2098% gen phrase 1
 2099verb_phrase(Subj,Event,gen_phrase1(Call,Result)) --> [S],
 2100	    {S\=@=is, 'genFormat'(Predicate,['~a',S|Template],ArgsI),
 2101	    (compound(ArgsI) -> trasfromArgs(ArgsI,Args) ; Args=[1,2]),
 2102	    length(Args,Size),functor(Call,Predicate,Size),atom(Predicate),
 2103	    placeVars([Subj|Blanks],Args,Call)},
 2104	    do_dcg(Template,Blanks,Result).
 2105
 2106
 2107
 2108% unkown phrase	+ object5 %TODO rename subject5/3 to noun_phrase/3
 2109verb_phrase(Subj,Event,and(isaAction(Event,Action),'doneBy'(Event,Subj),'constituentInSituation'(Event,Obj),CycLO)) --> 
 2110	 isPOS('Verb',CycVerb,String),
 2111	 best_subject(Obj,true,CycL),
 2112	 best_subject_constituant(Target,Event,CycL,CycLO),
 2113	 {cvtWordPosCycL(CycVerb,'Verb',Action),varnameIdea(String,Event)}.
 2114														  
 2115:- style_check(+discontiguous). 2116
 2117% unkown phrase + text
 2118best_subject(Obj,Event,CycL) --> isPOS('Preposition', _),{!},best_subject(Obj,Event,CycL).
 2119best_subject(Obj,Event,CycL) --> noun_phrase(Obj,Event,CycL),{!}.
 2120best_subject(Obj,CycL,CycL) --> rest_of(Obj).
 2121
 2122best_subject_constituant(RES,Event,CycL,CycL) --> [].
 2123best_subject_constituant(Target,Event,CycL,and(CycL,CycLO,'eventOccursAt'(Event,Target))) --> 
 2124	 best_subject(Target,Event,CycLO).
 2125   
 2126%rest_of(txt([A|C])) --> [A|C].
 2127rest_of(thingFor(Rest), [A|Rest], []):-notrace(meetsPos(A,CycWord,'Determiner')),!.
 2128rest_of(thingFor(Rest), Rest, []):-Rest=[_|_].
 2129
 2130
 2131apply_act(Predicate,Subj,Obj,ACT) :- \+ ';'(is_list(Subj),is_list(Obj)),!,ACT=..[Predicate,Subj,Obj].
 2132
 2133apply_act(Predicate,Subj,[Obj],ACT):-!,ACT=..[Predicate,Subj,Obj].
 2134apply_act(Predicate,Subj,[Obj|List],each(ACT,MORE)):-
 2135      ACT=..[Predicate,Subj,Obj],apply_act(Predicate,Subj,List,MORE),!.
 2136
 2137apply_act(Predicate,[Obj],Subj,ACT):-!,ACT=..[Predicate,Obj,Subj].
 2138apply_act(Predicate,[Obj|List],Subj,each(ACT,MORE)):-
 2139      ACT=..[Predicate,Obj,Subj],apply_act(Predicate,List,Subj,MORE),!.
 2140
 2141% =======================================================
 2142% GENFORMAT Verbs TODO
 2143% =======================================================
 2144
 2145do_dcg([], _ ,nil_true) --> {!},[].
 2146do_dcg(['~a'|Template],[Subj|Blanks],(Result)) -->{!},
 2147	    noun_phrase(Subj,More,Result),
 2148      do_dcg(Template,Blanks,More).
 2149do_dcg(Template,Blanks,end_true) --> Template,{!}.
 2150do_dcg([Word|Template],[Subj|Blanks],(Result)) --> [Word],
 2151      {append(Find,['~a'|More],Template),!},
 2152      Find,noun_phrase(Subj,CycL,Result),
 2153      do_dcg(More,Blanks,CycL).
 2154
 2155/*
 2156genFormatVerb2(Term,String,More,Subj,CycLO,noun_phrase(Object,[Predicate,Subj,Object],CycLO)):-
 2157      append(String,['~a'],More),!.
 2158genFormatVerb2([2,1],Predicate,String,More,Subj,CycLO,noun_phrase(Object,[Predicate,Object,Subj],CycLO)):-
 2159      append(String,['~a'],More),!.
 2160
 2161genFormatVerb2(Call,[Subj|Blanks],String,More,CycLO,ToDO):-!.
 2162*/
 2163
 2164%trasfromArgs(Args,List).
 2165trasfromArgs('NIL',[1,2,3,4,5,6]):-!.
 2166trasfromArgs([H],[HH]):-trasfromArg(H,HH),!.
 2167trasfromArgs([H|T],[HH|TT]):-trasfromArg(H,HH),trasfromArgs(T,TT),!.
 2168
 2169trasfromArg([[]|_], _).
 2170trasfromArg([H|_],H).
 2171trasfromArg(H,H).
 2172
 2173placeVars([Subj],[N],Call):-integer(N),arg(N,Call,Subj),!.
 2174placeVars([Subj|Blanks],[N|More],Call):-integer(N),arg(N,Call,Subj),placeVars(Blanks,More,Call),!.
 2175      
 2176
 2177      	 
 2178
 2179%'genTemplate'('many-GenQuantRelnToType', 'TermParaphraseFn'([':ARG1', 'BestDetNbarFn'('TermParaphraseFn'('Many-NLAttr'), 'TermParaphraseFn-Constrained'('plural-Generic', ':ARG2')), 'ConditionalPhraseFn'('equals'(':ARG3', 'Thing'), 'BestNLPhraseOfStringFn'(something), 'BestDetNbarFn'('TermParaphraseFn'('BareForm-NLAttr'), 'TermParaphraseFn-Constrained'('nonSingular-Generic', ':ARG3')))]), 'EnglishParaphraseMt', v(v('BareForm-NLAttr', 'BestDetNbarFn', 'BestNLPhraseOfStringFn', 'ConditionalPhraseFn', 'Many-NLAttr', 'TermParaphraseFn', 'TermParaphraseFn-Constrained', 'Thing', 'equals', 'many-GenQuantRelnToType', 'nonSingular-Generic', 'plural-Generic', ':ARG1', ':ARG2', ':ARG3', something), A)).
 2180%'genTemplate'('many-GenQuant', 'TermParaphraseFn'('elementOf'('BestDetNbarFn'('TermParaphraseFn'('Many-NLAttr'), 'TermParaphraseFn-Constrained'('nonSingular-Generic', ':ARG1')), ':ARG2')), 'EnglishParaphraseMt', v(v('BestDetNbarFn', 'Many-NLAttr', 'TermParaphraseFn', 'TermParaphraseFn-Constrained', 'elementOf', 'many-GenQuant', 'nonSingular-Generic', ':ARG1', ':ARG2'), A)).
 2181%'genTemplate'('markCreated', 'ConcatenatePhrasesFn'('TermParaphraseFn-NP'(':ARG2'), 'BestHeadVerbForInitialSubjectFn'('Be-TheWord'), 'BestNLPhraseOfStringFn'([the, mark, created, by]), 'TermParaphraseFn-NP'(':ARG2')))
 2182
 2183% =======================================================
 2184% Intrans phrase                                                                    
 2185verb_phrase_known(CycWord,Subj,Event,CycLO) --> 
 2186	 [],{cvtWordPosCycL(CycWord,'Verb',CycL),
 2187	 (('argIsa'(CycL,2,Type),Rel=..[CycL,Subj,Obj],
 2188	 CycLO = and_iv(isa(Obj,Type),Rel) );
 2189	 CycLO=and_iv('bodilyDoer'(Subj,Event),event_isa(Event,CycL))),varnameIdea('Intrans',Event),varnameIdea('Thing',Obj)}.
 2190
 2191% TODO
 2192%'agentiveNounSemTrans'('Assist-TheWord', 0, 'RegularNounFrame', 'assistingAgent'(A, ':NOUN'), 'GeneralEnglishMt', v(v('Assist-TheWord', 'RegularNounFrame', 'assistingAgent', ':NOUN'), ['?X'=A|B])).
 2193%'agentiveNounSemTrans'('Emit-TheWord', 0, 'RegularNounFrame', ['emitter', '?X', ':NOUN']).	    
 2194% =======================================================
 2195%'lightVerb-TransitiveSemTrans'('Take-TheWord', 'DrugProduct', 'and'('isa'(':ACTION', 'Ingesting'), 'performedBy'(':ACTION', ':SUBJECT'), 'primaryObjectMoving'(':ACTION', ':OBJECT')), 'EnglishMt', v(v('DrugProduct', 'Ingesting', 'Take-TheWord', 'and', 'isa', 'performedBy', 'primaryObjectMoving', ':ACTION', ':OBJECT', ':SUBJECT'), A)).
 2196verb_phrase_known(CycWord,Subj,Event,'lightVerb-TransitiveSemTrans'(Out)) -->
 2197	{'lightVerb-TransitiveSemTrans'(CycWord,ObjectIsa, Template)},
 2198	subject_isa(ObjectIsa,Object,Template,TemplateO),
 2199     {apply_frame(TemplateO,Subj,Event,Object,Result,Out)}.
 2200
 2201% =======================================================
 2202%'prepReln-Action'('LosingUserRights', 'Agent', 'From-TheWord', 'fromPossessor'(':ACTION', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Agent', 'From-TheWord', 'LosingUserRights', 'fromPossessor', ':ACTION', ':OBLIQUE-OBJECT'), A)).
 2203%'prepReln-Action'('MovementEvent', 'PartiallyTangible', 'From-TheWord', 'fromLocation'(':ACTION', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('From-TheWord', 'MovementEvent', 'PartiallyTangible', 'fromLocation', ':ACTION', ':OBLIQUE-OBJECT'), A)).
 2204%'prepReln-Action'('Movement-TranslationEvent', 'SomethingExisting', 'On-TheWord', 'toLocation'(':ACTION', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Movement-TranslationEvent', 'On-TheWord', 'SomethingExisting', 'toLocation', ':ACTION', ':OBLIQUE-OBJECT'), A)).
 2205%'prepReln-Action'('Stealing-Generic', 'Agent', 'From-TheWord', 'victim'(':ACTION', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Agent', 'From-TheWord', 'Stealing-Generic', 'victim', ':ACTION', ':OBLIQUE-OBJECT'), A)).
 2206%'prepReln-Action'('TransportationEvent', 'Conveyance', 'By-TheWord', 'transporter'(':ACTION', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('By-TheWord', 'Conveyance', 'TransportationEvent', 'transporter', ':ACTION', ':OBLIQUE-OBJECT'), A)).
 2207verb_phrase_known(CycWord,Subj,Event,'prepReln-Action'(CycLO,Out)) -->
 2208      {'prepReln-Action'(EventIsa, SubjIsa, CycWordPrep, Template),cycQueryIsa(Subj,SubjIsa)},
 2209	verb_phrase_event_isa(CycWord,EventIsa,Subj,Object,Event,EventMid),
 2210      isCycWord(CycWordPrep),subject5(Result,EventMid,CycLO),
 2211    {apply_frame(Template,Subject,Event,Object,Result,Out)}.
 2212
 2213% =======================================================
 2214%'prepReln-Object'('Action', 'PartiallyTangible', 'Of-TheWord', 'objectActedOn'(':NOUN', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Action', 'Of-TheWord', 'PartiallyTangible', 'objectActedOn', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 2215%'prepReln-Object'('AnimalBodyPartType', 'Animal', 'Of-TheWord', 'anatomicalParts'(':OBLIQUE-OBJECT', ':NOUN'), 'EnglishMt', v(v('Animal', 'AnimalBodyPartType', 'Of-TheWord', 'anatomicalParts', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 2216%'prepReln-Object'('Area', 'PartiallyTangible', 'Of-TheWord', 'areaOfObject'(':OBLIQUE-OBJECT', ':NOUN'), 'EnglishMt', v(v('Area', 'Of-TheWord', 'PartiallyTangible', 'areaOfObject', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 2217%'prepReln-Object'('CapitalCityOfRegion', 'IndependentCountry', 'Of-TheWord', 'capitalCity'(':OBLIQUE-OBJECT', ':SUBJECT'), 'EnglishMt', v(v('CapitalCityOfRegion', 'IndependentCountry', 'Of-TheWord', 'capitalCity', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2218%'prepReln-Object'('Communicating', 'Agent', 'By-TheWord', 'senderOfInfo'(':NOUN', ':OBLIQUE-OBJECT'), 'EnglishMt', v(v('Agent', 'By-TheWord', 'Communicating', 'senderOfInfo', ':NOUN', ':OBLIQUE-OBJECT'), A)).
 2219verb_phrase_known(CycWord,Subj,Event,'prepReln-Object'(Out)) -->
 2220      {'prepReln-Object'(SubjIsa, ObjectIsa, CycWordPrep, Template),cycQueryIsa(Subj,SubjIsa)},
 2221	subject_isa(ObjectIsa,Object,Template,TemplateO),
 2222      isCycWord(CycWordPrep),subject5(Result,TemplateO,CycLO),
 2223    {apply_frame(CycLO,Subject,Event,Object,Result,Out)}.
 2224
 2225% =======================================================
 2226%'verbSemTrans'('Depart-TheWord', 0, nartR('PPCompFrameFn','TransitivePPCompFrame', 'From-TheWord'), 'and'('isa'(':ACTION', 'LeavingAPlace'), 'fromLocation'(':ACTION', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'GeneralEnglishMt', v(v('Depart-TheWord', 'From-TheWord', 'LeavingAPlace', 'PPCompFrameFn', 'TransitivePPCompFrame', 'and', 'doneBy', 'fromLocation', 'isa', ':ACTION', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2227verb_phrase_known(CycWord,Subj,Event,verbSemTrans(Out,Extras)) -->
 2228	 {'verbSemTrans'(CycWord, _ , NextFrame, Template)},
 2229	    frame_template(NextFrame,Object,Result,Extras),
 2230	 {apply_frame(Template,Subj,Event,Object,Result,Out)}.
 2231
 2232% =======================================================
 2233%'verbPrep-Transitive'('Ablate-TheWord', 'From-TheWord', 'and'('isa'(':ACTION', 'Ablation'), 'objectOfStateChange'(':ACTION', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT'), 'objectRemoved'(':ACTION', ':OBJECT')), 'EnglishMt', v(v('Ablate-TheWord', 'Ablation', 'From-TheWord', 'and', 'doneBy', 'isa', 'objectOfStateChange', 'objectRemoved', ':ACTION', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2234verb_phrase_known(CycWord,Subj,Event,'verbPrep-Transitive'(Out,Extras)) -->
 2235   {'verbPrep-Transitive'(CycWord, CycWord2, Template)},
 2236	 isCycWord(CycWord2),{!},subject5(Result,Out,CycLO),
 2237   {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 2238   
 2239% =======================================================
 2240%'compoundVerbSemTrans'('Give-TheWord', [off], 'TransitiveNPCompFrame', 'and'('isa'(':ACTION', 'EmittingAnObject'), 'emitter'(':ACTION', ':SUBJECT'), 'objectEmitted'(':ACTION', ':OBJECT')), 'EnglishMt', v(v('EmittingAnObject', 'Give-TheWord', 'TransitiveNPCompFrame', 'and', 'emitter', 'isa', 'objectEmitted', ':ACTION', ':OBJECT', ':SUBJECT', off), A)).
 2241verb_phrase_known(CycWord,Subj,Event,compoundVerbSemTrans(Out,Extras)) -->
 2242   [S],{'compoundVerbSemTrans'(CycWord, [S|String],NextFrame, Template)},
 2243   String,frame_template(NextFrame,Object,Result,Extras),
 2244   {apply_frame(Template,Subj,Event,Object,Result,Out)}.
 2245
 2246% =======================================================
 2247%'compoundSemTrans'('End-TheWord', [during], 'Verb', 'TransitiveNPCompFrame', 'endsDuring'(':SUBJECT', ':OBJECT'), 'EnglishMt', v(v('End-TheWord', 'TransitiveNPCompFrame', 'Verb', 'endsDuring', ':OBJECT', ':SUBJECT', during), A)).
 2248verb_phrase_known(CycWord,Subj,Event,compoundSemTrans(Out,Extras)) -->
 2249    [S],{'compoundSemTrans'(CycWord, [S|String], 'Verb', NextFrame, Template)},
 2250   String,frame_template(NextFrame,Obj,Result,Extras),
 2251   {apply_frame(Template,Subj,Event,Obj,Result,Out)}.
 2252
 2253% =======================================================
 2254%'nonCompositionalVerbSemTrans'('Separate-TheWord', 'Mixture', 'and'('isa'(':ACTION', 'SeparatingAMixture'), 'doneBy'(':ACTION', ':SUBJECT'), 'objectOfStateChange'(':ACTION', ':OBJECT')), 'EnglishMt', v(v('Mixture', 'Separate-TheWord', 'SeparatingAMixture', 'and', 'doneBy', 'isa', 'objectOfStateChange', ':ACTION', ':OBJECT', ':SUBJECT'), A)).
 2255verb_phrase_known(CycWord,Subj,Event,nonCompositionalVerbSemTrans(Out)) -->
 2256	{'nonCompositionalVerbSemTrans'(CycWord,ObjectIsa, Template)},
 2257	subject_isa(ObjectIsa,Object,Template,TemplateO),
 2258     {apply_frame(TemplateO,Subj,Event,Object,Result,Out)}.
 2259
 2260
 2261% =======================================================
 2262%'verbPrep-TransitiveTemplate'('Constructing', 'Out-Of-MWW', 'and'('isa'(':ACTION', ':DENOT'), 'inputs'(':ACTION', ':OBLIQUE-OBJECT'), 'products'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'EnglishMt', v(v('Constructing', 'Out-Of-MWW', 'and', 'doneBy', 'inputs', 'isa', 'products', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2263%'verbPrep-TransitiveTemplate'('DistributionEvent', 'To-TheWord', 'and'('isa'(':ACTION', ':DENOT'), 'toLocation'(':ACTION', ':OBLIQUE-OBJECT'), 'objectMoving'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'EnglishMt', v(v('DistributionEvent', 'To-TheWord', 'and', 'doneBy', 'isa', 'objectMoving', 'toLocation', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2264%'verbPrep-TransitiveTemplate'('Evaluating', 'For-TheWord', 'and'('isa'(':ACTION', ':DENOT'), 'performedBy'(':ACTION', ':SUBJECT'), 'evaluee-Direct'(':ACTION', ':OBJECT'), 'purposeInEvent'(':SUBJECT', ':ACTION', 'knowsAbout'(':SUBJECT', ':OBLIQUE-OBJECT'))), 'EnglishMt', v(v('Evaluating', 'For-TheWord', 'and', 'evaluee-Direct', 'isa', 'knowsAbout', 'performedBy', 'purposeInEvent', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2265%'verbPrep-TransitiveTemplate'('FusionEvent', 'With-TheWord', 'and'('isa'(':ACTION', ':DENOT'), 'inputs'(':ACTION', ':OBJECT'), 'inputs'(':ACTION', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'EnglishMt', v(v('FusionEvent', 'With-TheWord', 'and', 'doneBy', 'inputs', 'isa', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2266%'verbPrep-TransitiveTemplate'('HoldingAnObject', 'By-TheWord', 'and'('isa'(':ACTION', ':DENOT'), 'objectActedOn'(':ACTION', ':OBLIQUE-OBJECT'), 'physicalParts'(':OBJECT', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'EnglishMt', v(v('By-TheWord', 'HoldingAnObject', 'and', 'doneBy', 'isa', 'objectActedOn', 'physicalParts', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2267%'verbPrep-TransitiveTemplate'('InformationRemoving', 'From-TheWord', 'and'('isa'(':ACTION', ':DENOT'), 'informationOrigin'(':ACTION', ':OBLIQUE-OBJECT'), 'infoRemoved'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'EnglishMt', v(v('From-TheWord', 'InformationRemoving', 'and', 'doneBy', 'infoRemoved', 'informationOrigin', 'isa', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2268verb_phrase_known(CycWord,Subj,Event,'verbPrep-TransitiveTemplate'(Out,EventMidO)) -->
 2269	 {'verbPrep-TransitiveTemplate'(EventIsa, CycWordPrep, Template)},
 2270      verb_phrase_event_isa(CycWord,EventIsa,Subj,Object,Event,EventMid),
 2271      isCycWord(CycWordPrep),subject5(Result,EventMid,EventMidO),
 2272   {apply_frame(Template,Subj,Event,Object,Result,OutD),vsubst(OutD,':DENOT',EventIsa,Out)}.
 2273  
 2274% =======================================================
 2275%'verbSemTransTemplate'('InformationRemoving', nartR('PPCompFrameFn','DitransitivePPCompFrame', 'From-TheWord'), 'and'('isa'(':ACTION', ':DENOT'), 'informationOrigin'(':ACTION', ':OBLIQUE-OBJECT'), 'infoRemoved'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'GeneralEnglishMt', v(v('DitransitivePPCompFrame', 'From-TheWord', 'InformationRemoving', 'PPCompFrameFn', 'and', 'doneBy', 'infoRemoved', 'informationOrigin', 'isa', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2276%'verbSemTransTemplate'('InformationRemoving', 'TransitiveNPCompFrame', 'and'('isa'(':ACTION', ':DENOT'), 'infoRemoved'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'GeneralEnglishMt', v(v('InformationRemoving', 'TransitiveNPCompFrame', 'and', 'doneBy', 'infoRemoved', 'isa', ':ACTION', ':DENOT', ':OBJECT', ':SUBJECT'), A)).
 2277%'verbSemTransTemplate'('Killing-Biological', 'TransitiveNPCompFrame', 'and'('isa'(':ACTION', ':DENOT'), 'inputsDestroyed'(':ACTION', ':OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'GeneralEnglishMt', v(v('Killing-Biological', 'TransitiveNPCompFrame', 'and', 'doneBy', 'inputsDestroyed', 'isa', ':ACTION', ':DENOT', ':OBJECT', ':SUBJECT'), A)).
 2278%'verbSemTransTemplate'('LeavingAPlace', nartR('PPCompFrameFn','TransitivePPCompFrame', 'From-TheWord'), 'and'('isa'(':ACTION', ':DENOT'), 'fromLocation'(':ACTION', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT')), 'GeneralEnglishMt', v(v('From-TheWord', 'LeavingAPlace', 'PPCompFrameFn', 'TransitivePPCompFrame', 'and', 'doneBy', 'fromLocation', 'isa', ':ACTION', ':DENOT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2279%'verbSemTransTemplate'('Bartering', nartR('PPCompFrameFn','DitransitivePPCompFrame', 'For-TheWord'), 'thereExists'(A, 'thereExists'(B, 'and'('isa'(':ACTION', ':DENOT'), 'exchangers'(':ACTION', ':SUBJECT'), 'subEvents'(':ACTION', A), 'subEvents'(':ACTION', B), 'toPossessor'(B, ':SUBJECT'), 'objectOfPossessionTransfer'(A, ':OBLIQUE-OBJECT'), 'objectOfPossessionTransfer'(B, ':OBJECT'), 'fromPossessor'(A, ':SUBJECT'), 'reciprocalTransfers'(A, B)))), 'GeneralEnglishMt', v(v('Bartering', 'DitransitivePPCompFrame', 'For-TheWord', 'PPCompFrameFn', 'and', 'exchangers', 'fromPossessor', 'isa', 'objectOfPossessionTransfer', 'reciprocalTransfers', 'subEvents', 'thereExists', 'toPossessor', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), ['?T1'=A, '?T2'=B|C])).
 2280%'verbSemTransTemplate'('CarryingWhileLocomoting', nartR('PPCompFrameFn','DitransitivePPCompFrame', 'By-TheWord'), 'and'('isa'(':ACTION', ':DENOT'), 'transportees'(':ACTION', ':OBJECT'), 'physicalParts'(':OBJECT', ':OBLIQUE-OBJECT'), 'doneBy'(':ACTION', ':SUBJECT'), 'objectsInContact'(':ACTION', ':OBLIQUE-OBJECT', ':SUBJECT')), 'GeneralEnglishMt', v(v('By-TheWord', 'CarryingWhileLocomoting', 'DitransitivePPCompFrame', 'PPCompFrameFn', 'and', 'doneBy', 'isa', 'objectsInContact', 'physicalParts', 'transportees', ':ACTION', ':DENOT', ':OBJECT', ':OBLIQUE-OBJECT', ':SUBJECT'), A)).
 2281verb_phrase_known(CycWord,Subj,Event,verbSemTransTemplate(Out,EventMidO)) -->
 2282      {'verbSemTransTemplate'(EventIsa,NextFrame, Template)},
 2283	 verb_phrase_event_isa(CycWord,EventIsa,Subj,Object,Event,EventMid),
 2284      frame_template(NextFrame,Obj,Result,Extras),
 2285   {apply_frame(Template,Subj,Event,Object,Result,OutD),vsubst(OutD,':DENOT',EventIsa,Out)}.
 2286
 2287verb_phrase_known(CycWord,Subj,Event,auxV(Out)) --> isPOS('AuxVerb', _),
 2288      verb_phrase_known(CycWord,Subj,Event,Out).
 2289
 2290
 2291% =======================================================
 2292% verb_phrase_event_isa
 2293% =======================================================
 2294verb_phrase_event_isa(CycWord,EventIsa,Subj,Object,Event,Out) -->
 2295      {cycWordForISA(CycWord,EventIsa)},verb_phrase_known(CycWord,Subj,Event,Out).
 2296
 2297
 2298% =======================================================
 2299% frame_template
 2300% =======================================================
 2301
 2302
 2303
 2304frame_template('TransitiveNPCompFrame',Obj,Result,Extras) --> noun_phrase(Obj,true,Extras). 
 2305%$DitransitivePPCompFrame','TransitivePPCompFrame'
 2306frame_template(nartR('PPCompFrameFn',_ ,CycPrep),Obj,Result,Extras) --> isCycWord(CycPrep),{!},best_subject(Result,true,Extras).
 2307frame_template(nartR('PPCompFrameFn',_ ,CycPrep),Obj,Result,Extras) --> noun_phrase(Obj,true,Mid),isCycWord(CycPrep),{!},best_subject(Result,Mid,Extras).
 2308frame_template('RegularAdjFrame',Subj,Result,Extras) -->noun_phrase(Subj,true,Extras).
 2309
 2310
 2311% ==========================================================
 2312% String to String
 2313% ==========================================================
 2314
 2315:-disable_body_textstr. 2316% % :- enable_body_textstr.
 2317
 2318
 2319removeRepeats1([],[]):-!.
 2320removeRepeats1([H|T],[HH|TT]):- stringToString(H,HH),!,removeRepeats1(T,TT).
 2321removeRepeats1([H,H1|Rest],Out):-once(toLowercase(H,HL)),H1=HL,!,removeRepeats1([H|Rest],Out).
 2322removeRepeats1([H|Rest],[H|Out]):-removeRepeats1(Rest,Out).
 2323removeRepeats1(X,X).
 2324
 2325removeRepeats2(X,X):-!.
 2326
 2327removeRepeats2(X,O):-append(L,R,X),
 2328	    append([S,O|Me],LL,L),
 2329	    append([S,O|Me],RR,R),!,
 2330	    flatten([[S,O|Me],LL,RR],O).
 2331
 2332stringToString(Before,After):-'abbreviationForString'(After, Before).
 2333
 2334simplifyLF(Result,Result):-!.
 2335
 2336cycQueryIsa(X,Y):-fail,writeq(cycQueryIsa(X,Y)),nl.
 2337
 2338
 2339/*
 2340
 2341% ==========================================================
 2342% ==========================================================
 2343% ==========================================================
 2344% ==========================================================
 2345% ==========================================================
 2346% ==========================================================
 2347% ==========================================================
 2348% ==========================================================
 2349% ==========================================================
 2350
 2351% String Based
 2352'genTemplate'('abnormal', 'ConcatenatePhrasesFn'('TermParaphraseFn'(':ARG1'), 'BestNLPhraseOfStringFn'([-, with, the, exception, of]), 'TermParaphraseFn'(':ARG2')), 'EnglishParaphraseMt', v(v('BestNLPhraseOfStringFn', 'ConcatenatePhrasesFn', 'TermParaphraseFn', 'abnormal', -, ':ARG1', ':ARG2', exception, of, the, with), A)).
 2353'genTemplate-Constrained'('arg1Isa', 'isa'(':ARG1', 'BinaryPredicate'), 'TermParaphraseFn'('implies'('thereExists'(A, [':ARG1', B, A]), 'ConcatenatePhrasesFn'('TermParaphraseFn-NP'(B), 'BestNLPhraseOfStringFn'([must, be]), 'BestDetNbarFn-Indefinite'('TermParaphraseFn-Constrained'('nonPlural-Generic', ':ARG2'))))), 'EnglishParaphraseMt', v(v('BestDetNbarFn-Indefinite', 'BestNLPhraseOfStringFn', 'BinaryPredicate', 'ConcatenatePhrasesFn', 'TermParaphraseFn', 'TermParaphraseFn-Constrained', 'TermParaphraseFn-NP', 'arg1Isa', 'implies', 'isa', 'nonPlural-Generic', 'thereExists', ':ARG1', ':ARG2', be, must), ['?Y'=A, '?X'=B|C])).
 2354'genQuestion'('genls', 1, [what, kinds, of, '~a', are, there], [[2, ':NON-SINGULAR-GENERIC']], 'EnglishParaphraseMt', v(v('genls', ':NON-SINGULAR-GENERIC', are, kinds, of, there, what, '~a'), A)).
 2355'genQuestion'('hasAttributes', 2, ['What', attributes, does, '~a', 'have?'], [1], 'EnglishParaphraseMt', v(v('hasAttributes', 'What', attributes, does, 'have?', '~a'), A)).
 2356%'assertTemplate-Reln'(TemplateType,Predicate, Match, Template).
 2357	    %InfinitivalVPTemplate'
 2358	    % 'aspectPerfect'
 2359	    %[have, not, 'PerfectiveVPTemplate'(':VP-CONT')]
 2360	    %'NLNegFn'('NotVP-NLAttr', 'aspectPerfect'(':VP-CONT'))
 2361
 2362
 2363% meetsParam(transverb,String,CycWord):-genFormatAccess(String,CycWord).
 2364
 2365%genFormat(Verb,X,'NIL'):-'genFormat'(Verb,X, _).
 2366
 2367
 2368'genFormat'('abbreviationString-PN', abbreviation, 'NIL', 'EnglishParaphraseMt', v(v('abbreviationString-PN', 'NIL', abbreviation), A)).
 2369'genFormat'('abbreviationString-PN', ['~a', is, the, abbreviated, form, of, the, name, for, '~a'], [[2, ':QUOTE'], 1], 'EnglishParaphraseMt', v(v('abbreviationString-PN', ':QUOTE', abbreviated, for, form, is, name, of, the, '~a'), A)).
 2370'genFormat'('adjSemTrans', ['~a', is, the, semantic, translation, of, word, sense, number, '~a', of, '~a', with, the, subcategorization, frame, '~a'], [[4, ':QUOTE'], 2, [1, ':QUOTE'], [3, ':QUOTE']], 'EnglishParaphraseMt', v(v('adjSemTrans', ':QUOTE', frame, is, number, of, semantic, sense, subcategorization, the, translation, with, word, '~a'), A)).
 2371'genFormat'('adjSemTrans-Restricted', [the, semantic, translation, of, word, sense, number, '~a', of, '~a', (','), when, modifying, '~a', with, the, subcategorization, frame, '~a', (','), is, '~a'], [2, [1, ':QUOTE'], [4, ':A'], [3, ':QUOTE'], 5], 'EnglishParaphraseMt', v(v('adjSemTrans-Restricted', (','), ':A', ':QUOTE', frame, is, modifying, number, of, semantic, sense, subcategorization, the, translation, when, with, word, '~a'), A)).
 2372'genFormat'('Area1023', ['Troi', '\'', s, 'Quarters'], 'NIL', 'EnglishParaphraseMt', v(v('Area1023', '\'', 'NIL', 'Quarters', 'Troi', s), A)).
 2373'genFormat-ArgFixed'('SubcollectionOfWithRelationFromTypeFn', 2, 'surfaceParts', ['~A', on, '~A'], [[1, ':MASS-NUMBER', ':PLURAL', ':GERUND'], [3, ':PLURAL', ':MASS-NUMBER']], 'EnglishParaphraseMt', v(v('SubcollectionOfWithRelationFromTypeFn', 'surfaceParts', ':GERUND', ':MASS-NUMBER', ':PLURAL', on, '~A'), A)).
 2374'genFormat-ArgFixed'('SubcollectionOfWithRelationToFn', 2, 'containsInformationAbout', ['~A', about, '~A'], [[1, ':MASS-NUMBER', ':PLURAL', ':GERUND'], 3], 'EnglishParaphraseMt', v(v('SubcollectionOfWithRelationToFn', 'containsInformationAbout', ':GERUND', ':MASS-NUMBER', ':PLURAL', about, '~A'), A)).
 2375'genFormat-ArgFixed'('SubcollectionOfWithRelationToFn', 2, 'eventOccursAt', ['~A', in, '~A'], [[1, ':MASS-NUMBER', ':PLURAL', ':GERUND'], 3], 'EnglishParaphraseMt', v(v('SubcollectionOfWithRelationToFn', 'eventOccursAt', ':GERUND', ':MASS-NUMBER', ':PLURAL', in, '~A'), A)).
 2376'genFormat-Precise'('synonymousExternalConcept', [the, 'Cyc', concept, '~s', is, synonymous, with, the, concept, named, by, '~s', in, the, external, data, source, '~a'], [1, 3, 2], 'EnglishParaphraseMt', v(v('synonymousExternalConcept', 'Cyc', by, concept, data, external, in, is, named, source, synonymous, the, with, '~a', '~s'), A)).
 2377'genFormat-Precise'('tastes', [the, agent, '~a', can, taste, '~a'], 'NIL', 'EnglishParaphraseMt', v(v('tastes', 'NIL', agent, can, taste, the, '~a'), A)).
 2378'genFormat-Precise'('temporalBoundsIntersect', [the, temporal, interval, of, '~a', intersects, the, temporal, interval, of, '~a'], 'NIL', 'EnglishParaphraseMt', v(v('temporalBoundsIntersect', 'NIL', intersects, interval, of, temporal, the, '~a'), A)).
 2379
 2380
 2381
 2382'formalityOfWS'('Aussie-TheWord', 'ProperCountNoun', 0, 'InformalSpeech', 'GeneralEnglishMt', v(v('Aussie-TheWord', 'InformalSpeech', 'ProperCountNoun'), A)).
 2383'formalityOfWS'('Babe-TheWord', 'SimpleNoun', 1, 'InformalSpeech', 'GeneralEnglishMt', v(v('Babe-TheWord', 'InformalSpeech', 'SimpleNoun'), A)).
 2384'politenessOfWS'('Cock-TheWord', 'SimpleNoun', 1, 'VulgarSpeech', 'GeneralEnglishMt', v(v('Cock-TheWord', 'SimpleNoun', 'VulgarSpeech'), A)).
 2385
 2386% ==========================================================
 2387% WordsList Heuristics
 2388% ==========================================================
 2389'determinerAgreement'('A-Dozen-MWW', 'plural-Generic', 'EnglishMt', v(v('A-Dozen-MWW', 'plural-Generic'), A)).
 2390
 2391'denotesArgInReln'('Acquaint-TheWord', 'CountNoun', 'acquaintedWith', 2, 'GeneralEnglishMt', v(v('Acquaint-TheWord', 'CountNoun', 'acquaintedWith'), A)).
 2392'generateArgWithOutsideScope'('several-GenQuantRelnToType', 2, 'ParaphraseMt', v(v('several-GenQuantRelnToType'), A)).
 2393'generateQuantOverArg'('few-GenQuantRelnFrom', 'Few-NLAttr', 3, 'ParaphraseMt', v(v('Few-NLAttr', 'few-GenQuantRelnFrom'), A)).
 2394'genNatTerm-ArgLast'('PureFn', [pure], 'Noun', 'EnglishMt', v(v('Noun', 'PureFn', pure), A)).
 2395'genNatTerm-compoundString'('AttemptingFn', 'Try-TheWord', [to], 'Verb', 'infinitive', 'EnglishMt', v(v('AttemptingFn', 'Try-TheWord', 'Verb', 'infinitive', to), A)).
 2396'genNatTerm-multiWordString'('TreatmentFn', 'NIL', 'Treatment-TheWord', 'MassNoun', 'nonPlural-Generic', 'EnglishMt', v(v('MassNoun', 'Treatment-TheWord', 'TreatmentFn', 'nonPlural-Generic', 'NIL'), A)).
 2397%'headsPhraseOfType'('Pronoun', 'Noun', 'GeneralLexiconMt', v(v('Noun', 'Pronoun'), A)).
 2398'ncRuleConstraint'('AttackingDogs-NCR', 'NCGenlsConstraintFn'('TheNCModifier', 'Event'), 'GeneralLexiconMt', v(v('AttackingDogs-NCR', 'Event', 'NCGenlsConstraintFn', 'TheNCModifier'), A)).
 2399'ncRuleLabel'('WaterSolution-NCR', [water, solution], 'GeneralLexiconMt', v(v('WaterSolution-NCR', solution, water), A)).
 2400'ncRuleTemplate'('AnimalPopulations-NCR', 'SubcollectionOfWithRelationToTypeFn'('TheNCHead', 'groupMembers', 'TheNCModifier'), 'GeneralLexiconMt', v(v('AnimalPopulations-NCR', 'SubcollectionOfWithRelationToTypeFn', 'TheNCHead', 'TheNCModifier', 'groupMembers'), A)).
 2401'posForTemplateCategory'('Verb', 'ProgressiveVPTemplate', 'EnglishTemplateMt', v(v('ProgressiveVPTemplate', 'Verb'), A)).
 2402'posOfPhraseType'('NounPhrase', 'Noun', 'GeneralLexiconMt', v(v('Noun', 'NounPhrase'), A)).
 2403'posOfPhraseType'('PhraseFn'(A), A, 'GeneralLexiconMt', v(v('PhraseFn', '$VAR'), ['VAR1'=A|B])).
 2404'posPredForTemplateCategory'('presentParticiple', 'ProgressiveVPTemplate', 'EnglishTemplateMt', v(v('ProgressiveVPTemplate', 'presentParticiple'), A)).
 2405%'prepCollocation'('Beset-TheWord', 'Adjective', 'By-TheWord').      
 2406'prepCollocation'('Wrangle-TheWord', 'Verb', 'With-TheWord', 'EnglishMt', v(v('Verb', 'With-TheWord', 'Wrangle-TheWord'), A)).
 2407'relationIndicators'('ailmentConditionAffects', 'Infect-TheWord', 'SimpleNoun', 'EnglishMt', v(v('Infect-TheWord', 'SimpleNoun', 'ailmentConditionAffects'), A)).
 2408'requiredActorSlots'('MonetaryExchangeOfUserRights', 'buyer', 'HumanActivitiesMt', v(v('MonetaryExchangeOfUserRights', 'buyer'), A)).
 2409%'semTransArg'('adjSemTrans', 4, 'GeneralLexiconMt', v(v('adjSemTrans'), A)).
 2410%'semTransArg'('adjSemTrans-Restricted', 5, 'GeneralLexiconMt', v(v('adjSemTrans-Restricted'), A)).
 2411'subcatFrame'('Argue-TheWord', 'Verb', 0, 'TransitiveNPCompFrame', 'GeneralEnglishMt', v(v('Argue-TheWord', 'TransitiveNPCompFrame', 'Verb'), A)).
 2412'subcatFrameArity'('Post-NounPhraseModifyingFrame', 1, 'GeneralLexiconMt', v(v('Post-NounPhraseModifyingFrame'), A)).
 2413'subcatFrameDependentConstraint'('TransitiveNPCompFrame', 1, 'PhraseFn'('Noun'), 'GeneralLexiconMt', v(v('Noun', 'PhraseFn', 'TransitiveNPCompFrame'), A)).
 2414'subcatFrameDependentKeyword'('Post-NounPhraseModifyingFrame', 1, ':OBJECT', 'GeneralLexiconMt', v(v('Post-NounPhraseModifyingFrame', ':OBJECT'), A)).
 2415'subcatFrameKeywords'('MiddleVoiceFrame', ':ACTION', 'InferencePSC', v(v('MiddleVoiceFrame', ':ACTION'), A)).
 2416
 2417'psRuleArity'('PSRule-AdjPFromAdj', 1, 'EnglishLexiconMt', v(v('PSRule-AdjPFromAdj'), A)).
 2418'psRuleArity'('PSRule-AdvP-AdvPAdvP', 2, 'EnglishLexiconMt', v(v('PSRule-AdvP-AdvPAdvP'), A)).
 2419'psRuleCategory'('PSRule-V-VAdvP', 'Verb', 'EnglishLexiconMt', v(v('PSRule-V-VAdvP', 'Verb'), A)).
 2420'psRuleConstraint'('PSRule-AdjPFromAdj', 'ConstituentTypeConstraintFn'(1, 'Adjective'), 'EnglishLexiconMt', v(v('Adjective', 'ConstituentTypeConstraintFn', 'PSRule-AdjPFromAdj'), A)).
 2421'psRuleExample'('PSRule-VbarVComps', [likes, emus], 'EnglishLexiconMt', v(v('PSRule-VbarVComps', emus, likes), A)).
 2422'psRuleSemanticsFromDtr'('PSRule-DbarFromDet', 1, 'EnglishLexiconMt', v(v('PSRule-DbarFromDet'), A)).
 2423'psRuleSemanticsHandler'('PSRule-NP-DetNbar', 'PSP-SEMX-FOR-DET-NBAR', 'EnglishLexiconMt', v(v('PSRule-NP-DetNbar', 'PSP-SEMX-FOR-DET-NBAR'), A)).
 2424'psRuleSyntacticHeadDtr'('PSRule-AdjPFromAdj', 1, 'EnglishLexiconMt', v(v('PSRule-AdjPFromAdj'), A)).
 2425'psRuleTemplateBindings'('PSRule-V-VAdvP', 'PSBindingFn'(1, ':ACTION'), 'EnglishLexiconMt', v(v('PSBindingFn', 'PSRule-V-VAdvP', ':ACTION'), A)).
 2426'psRuleTemplateDtr'('PSRule-AdjPFromAdj', 1, 'EnglishLexiconMt', v(v('PSRule-AdjPFromAdj'), A)).
 2427
 2428*/
 2429/*===================================================================
 2430Convert S-Expression originating from user to a Prolog Clause representing the surface level
 2431
 2432Recursively creates a Prolog term based on the S-Expression to be done after compiler
 2433                                                 
 2434Examples:
 2435
 2436| ?- sterm_to_pterm([a,b],Pterm).
 2437Pterm = a(b)
 2438
 2439| ?- sterm_to_pterm([a,[b]],Pterm).    %Note:  This is a special Case
 2440Pterm = a(b)
 2441
 2442| ?- sterm_to_pterm([holds,X,Y,Z],Pterm).    %This allows Hilog terms to be Converted
 2443Pterm = _h76(_h90, _h104)                    
 2444
 2445| ?- sterm_to_pterm([X,Y,Z],Pterm).   %But still works in normal places
 2446Pterm = _h76(_h90, _h104)                    
 2447
 2448| ?- sterm_to_pterm(['AssignmentFn',X,[Y,Z]],Pterm).                                
 2449'Pterm = 'AssignmentFn'(_h84,[_h102, _h116])'
 2450
 2451*/
 2452
 2453sterm_to_pterm(VAR,VAR):-isSlot(VAR),!.
 2454sterm_to_pterm([VAR],VAR):-isSlot(VAR),!.
 2455sterm_to_pterm([X],Y):-!,nonvar(X),sterm_to_pterm(X,Y).
 2456
 2457sterm_to_pterm([S|TERM],PTERM):-isSlot(S),
 2458            sterm_to_pterm_list(TERM,PLIST),            
 2459            PTERM=..[holds,S|PLIST].
 2460
 2461sterm_to_pterm([S|TERM],PTERM):-number(S),!,
 2462            sterm_to_pterm_list([S|TERM],PTERM).            
 2463	    
 2464sterm_to_pterm([S|TERM],PTERM):-nonvar(S),atomic(S),!,
 2465            sterm_to_pterm_list(TERM,PLIST),            
 2466            PTERM=..[S|PLIST].
 2467
 2468sterm_to_pterm([S|TERM],PTERM):-!,  atomic(S),
 2469            sterm_to_pterm_list(TERM,PLIST),            
 2470            PTERM=..[holds,S|PLIST].
 2471
 2472sterm_to_pterm(VAR,VAR):-!.
 2473
 2474sterm_to_pterm_list(VAR,VAR):-isSlot(VAR),!.
 2475sterm_to_pterm_list([],[]):-!.
 2476sterm_to_pterm_list([S|STERM],[P|PTERM]):-!,
 2477              sterm_to_pterm(S,P),
 2478              sterm_to_pterm_list(STERM,PTERM).
 2479sterm_to_pterm_list(VAR,[VAR]).
 2480
 2481
 2482atom_junct(Atom,Words):-!,to_word_list(Atom,Words),!.
 2483
 2484atom_junct(Atom,Words):-
 2485   concat_atom(Words1,' ',Atom),
 2486   atom_junct2(Words1,Words),!.
 2487
 2488atom_junct2([],[]).
 2489atom_junct2([W|S],[A,Mark|Words]):- member(Mark,['.',',','?']),atom_concat(A,Mark,W),not(A=''),!,atom_junct2(S,Words).
 2490atom_junct2([W|S],[Mark,A|Words]):- member(Mark,['.',',','?']),atom_concat(Mark,A,W),not(A=''),!,atom_junct2(S,Words).
 2491atom_junct2([W|S],[W|Words]):-atom_junct2(S,Words).
 2492
 2493% :- include(logicmoo(vworld/moo_footer)).
 2494
 2495%:- module_predicates_are_exported(parser_e2c).
 2496%:- module_meta_predicates_are_transparent(parser_e2c).
 2497
 2498% :-module(parser_e2c).
 2499
 2500%:- debug, make:list_undefined. 
 2501 % speechPartPreds_transitive(X,Y).
 2502%:- parser_e2c:prolog.
 2503
 2504%:- user:prolog.
 2505
 2506%:- dm1.
 2507
 2508
 2509
 2510
 2511
 2512
 2513skip_ops:-  system:((
 2514 op(1199,fx,('==>')), 
 2515 op(1190,xfx,('::::')),
 2516 op(1180,xfx,('==>')),
 2517 op(1170,xfx,'<==>'),  
 2518 op(1160,xfx,('<-')),
 2519 op(1150,xfx,'=>'),
 2520 op(1140,xfx,'<='),
 2521 op(1130,xfx,'<=>'), 
 2522 op(600,yfx,'&'), 
 2523 op(600,yfx,'v'),
 2524 op(350,xfx,'xor'),
 2525 op(300,fx,'~'),
 2526 op(300,fx,'-'))).
 2527
 2528
 2529:- set_prolog_flag(do_renames,false). 2530
 2531hard_words(X):-member(X,[
 2532tricorder,
 2533teleport,
 2534recieved,
 2535picard,
 2536located,
 2537incurred,
 2538ensigns,
 2539dilithium,
 2540betazoid,
 2541alexander,
 2542'READY-',
 2543'INVIS',
 2544'Enterprise\'s',
 2545worf,
 2546wimpy,
 2547vulcan,
 2548turbolift,
 2549synthehol,
 2550starfleet,
 2551somwhere,
 2552rozhenko,
 2553romulan,
 2554riker,
 2555phasors,
 2556phasers,
 2557phaser,
 2558mudMaxHitPoints,
 2559mudLevelOf,
 2560mudBareHandDamage,
 2561marketpace,
 2562managed,
 2563holodeck,
 2564geordi,
 2565ferengi,
 2566embedded,
 2567easils,
 2568damageSizeDice,
 2569damageNumberDice,
 2570chargeRemaining,
 2571chargeCapacity,
 2572bustling,
 2573burgandy,
 2574\,
 2575+,
 2576***,
 2577********,
 2578********************,
 2579*********************,
 2580'|',
 2581'you\'ve',
 2582'worf\'s',
 2583'Worf',
 2584'WIMPY',
 2585'WeaponBlasting',
 2586'USS',
 2587'Turbolift',
 2588'Troi\'s',
 2589'Tricorder',
 2590'there\'s',
 2591'Synthehol',
 2592'Starfleet\'s',
 2593'ship\'s',
 2594'she\'s',
 2595'says:\n\n***************************************************\n',
 2596'riker\'s',
 2597'picard\'s',
 2598'Phaser',
 2599'people\'s',
 2600'NPC',
 2601'NOTRACK',
 2602'NOSUMMON',
 2603'NOSLEEP',
 2604'NOCHARM',
 2605'NOBLIND',
 2606'NOBASH',
 2607'NOBACKSTAB',
 2608'NCC',
 2609'Logged',
 2610'Lemonade\'Prune',
 2611'it\'s',
 2612'holodeck\'s',
 2613'Holodeck',
 2614'he\'s',
 2615'_______',
 2616'____/___',
 2617'___',
 2618'_/',
 2619'_',
 2620'\n***************************************************\n',
 2621'\n',
 2622'9d9',
 2623'8d8',
 2624'800',
 2625'5000',
 2626'4000',
 2627'3400',
 2628'2600',
 2629'20d20',
 2630'18d18',
 2631'1701',
 2632'1600',
 2633'1400',
 2634'12d12',
 2635'10d10',
 2636'-ENTER',
 2637'+mudToHitArmorClass0',
 2638'*\n**************************************************',
 2639'*\n***********************************************',
 2640'*\n',
 2641'***(_',
 2642'$PunchingSomething',
 2643'$LightingDevice',
 2644'"']).
 2645
 2646:-kb_shared(properNameStrings/2). 2647properNames(['Geordi',
 2648'Guinan',
 2649'LaForge',
 2650'Troi',
 2651'Picard',
 2652'Rozhenko',
 2653'Riker',
 2654'O\'Brien',
 2655'Crusher',
 2656'Data',
 2657'CycLBot',
 2658'CycBot1',
 2659'CycBot',
 2660'Romulan',
 2661'Starfleet',
 2662'Klingon',
 2663'Ferengi'])