1% ===================================================================
    2% File 'parser_stanford.pl'
    3% Purpose: English to KIF conversions from SWI-Prolog  
    4% This implementation is incomplete
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: 'parser_stanford.pl' 1.0.0
    8% Revision:  $Revision: 1.3 $
    9% Revised At:   $Date: 2002/06/06 15:43:15 $
   10% ===================================================================
   11
   12:-module(parser_stanford,[
   13
   14         ]).   15
   16:-dynamic(tag_pos/2).   17:-dynamic(tag_pos/3).   18:-dynamic(get_pos_tagger/1).   19
   20% export all predicates in this file
   21export_preds_term_expansion(end_of_file):-!.
   22export_preds_term_expansion((MH:-_)):- !, export_preds_term_expansion((MH)).
   23export_preds_term_expansion((MH)):- strip_module(MH,M,H),
   24   functor(H,F,A),F\=(:-),M:export(F/A),!.
   25
   26parser_stanford:term_expansion(HB,_):- export_preds_term_expansion(HB),fail.
   27
   28atomic_subst(Before,Find,Replace,After):- atomic_list_concat(Atoms,Find,Before),atomic_list_concat(Atoms,Replace,After).
   29
   30%:- setenv('CLASSPATH','/devel/PrologMUD/runtime/stanford-corenlp/*:-devel/PrologMUD/runtime/stanford-corenlp/classes:.').
   31%:- setenv('CLASSPATH','/opt/PrologMUD/runtime/stanford-parser-full-2014-08-27:-opt/PrologMUD/pack/stanford-parser-full-2014-08-27/stanford-postagger.jar:-opt/PrologMUD/runtime/stanford-parser-full-2014-08-27/stanford-srpser-2014-08-28-models.jar:-opt/PrologMUD/runtime/stanford-parser-full-2014-08-27/stanford-parser-3.4.1-models.jar:-opt/PrologMUD/runtime/stanford-parser-full-2014-08-27/stanford-parser.jar').
   32
   33:- (prolog_load_context(directory,D),
   34 (getenv('CLASSPATH',PCP);PCP='.')->
   35  format(atom(Atom),'~w:~w:~w/stanford-corenlp3.5.2-ALL.jar',[PCP,D,D]), 
   36  show_call(setenv('CLASSPATH',Atom))).   37
   38:- reexport(library(jpl)).   39:- jpl_set_default_jvm_opts(['-Xmx5G']).   40
   41:-if(\+ current_predicate(must/1)).   42% must(G):- G *-> true; (trace,G).
   43:-endif.   44
   45:-dynamic(pos_tagger/1).   46
   47get_pos_tagger(I):- pos_tagger(I)->true;
   48   (jpl_new(class([],['POSTaggerParser']),[],I),
   49    jpl_call(I,'init',[],@(void)),asserta(pos_tagger(I))).
   50
   51call_pos_tagger(Call,Args,Out):- get_pos_tagger(I),jpl_call(I,Call,Args,Out).
   52
   53unwrap_functor([],O,O).
   54unwrap_functor([F/A-Arg|Rest],I,O):-unwrap_functor_0(F/A,Arg,I,M),unwrap_functor(Rest,M,O).
   55
   56unwrap_functor_0(F/A,Arg,I,M):-compound(I),functor(I,F,A),arg(Arg,I,M).
   57unwrap_functor_0(_,_,I,I).
   58
   59% pos_tagger_test(Out),arg(3,Out,A).
   60
   61s_to_sin(S,SIn):-
   62  string_to_atom(S,SIn),!.
   63
   64s_to_sin(S,SIn):-
   65  string_to_atom(S,In),
   66   atomic_subst(In,' here, ',' here and is ',SIn0),
   67   atomic_subst(SIn0,'\'re ',' are ',SIn1),
   68   atomic_subst(SIn1,'n\'t ',' not ',SIn2),
   69   atomic_subst(SIn2,', ',' and ',SIn),!.
   70
   71:-export(tag_pos/2).   72tag_pos(S,OO):-tag_pos(S,OO,_).
   73tag_pos(S,OO,OO2) :- 
   74  s_to_sin(S,SIn),
   75  call_pos_tagger(tagPOS, [SIn],O),
   76   j_get(O,[f(1),j_to_term],Out),once(unwrap_functor(['ROOT'/1-1,'S'/1-1],Out,OO)),
   77   j_get(O,[f(0),j_to_term],Out2),once(unwrap_functor(['ROOT'/1-1,'S'/1-1],Out2,OO2)).
   78
   79:-export(acetext_to_typedDependencies/2).   80acetext_to_typedDependencies(S,OO) :- 
   81  s_to_sin(S,SIn),
   82  call_pos_tagger(tagPOS, [SIn],O),
   83   j_get(O,[+j_to_term],Out),once(unwrap_functor(['ROOT'/1-1,'S'/1-1],Out,OO)).
   84
   85:-export(annotateSentence/2).   86annotateSentence(S,OO) :- 
   87  s_to_sin(S,SIn),
   88  call_pos_tagger(annotateSentence, [SIn],O),
   89   j_get(O,[j_to_term],Out),once(unwrap_functor(['ROOT'/1-1,'S'/1-1],Out,OO)).
   90
   91spall(S,a_t(A,B)) :- acetext_to_typedDependencies(S,B),annotateSentence(S,A),!.
   92spall(S):-spall(S,O),show_tree((S:-O)).
   93
   94
   95
   96jsv:- jpl_call(class([java,lang],['System']),getProperty,['java.specification.version'],O),dmsg(version(O)).
   97
   98:- must(jsv).   99
  100:-export(pos_tagger_test/1).  101pos_tagger_test(Out) :- tag_pos('Lieutenant Worf is here, looking pretty mean.',Out),writeq(Out).
  102% pos_tagger_test(Out) :- acetext_to_typedDependencies('Lieutenant Worf is here, looking pretty mean.',Out),writeq(Out).
  103pos_tagger_test(Out) :- spall('The strongest rain ever recorded in India shut down the financial hub of Mumbai, snapped communication lines, closed airports and forced thousands of people to sleep in their offices or walk home during the night, officials said today.',Out),
  104  portray_clause(c:-Out).
  105
  106% pos_tagger_test :- call_pos_tagger(tagPOS(class([java,lang],['String'])), ["The check is in your mouth. "],Out),writeq(Out).
  107
  108
  109
  110must_j_get(E,I,O):-(must_j_get(I,E,O)),!.
  111
  112j_is_term(I,T):- ground(T),!,must(jpl_type_to_class(T,SC)),jpl_call(SC,isInstance,[I],IS),IS='@'(true).
  113j_is_term(I,T):- jpl_call(I,getClass,[],C),j_subclasses(C,TT),jpl_class_to_type(TT,Type),T=Type,!.
  114
  115j_subclasses(C,C).
  116j_subclasses(C,TO):-jpl_call(C,getSuperclass,[],T),j_subclasses(T,TO).
  117j_subclasses(C,TE):-jpl_call(C,getInterfaces,[],T),jpl_array_to_list(T,L),member(E,L),j_subclasses(E,TE).
  118
  119
  120j_to_term_until_done(I,O):- j_to_term(I, M),(I\=@=M -> j_to_term_until_done(M, O) ; M=O).
  121
  122j_to_term(I, O):- var(I),!,must(I=O).
  123j_to_term(I, O):- is_list(I),!,(must_maplist(j_to_term,I,O)).
  124j_to_term(I, O):- jpl_is_object(I),!,must(jo_to_term(I, O)).
  125j_to_term(I, O):- compound(I),I=..[F|IA],!,must((maplist(j_to_term,IA,OA),O=..[F|OA])).
  126j_to_term(I, O):- must(I=O).
  127
  128
  129jo_to_term(I,OO):- jconvert(T,How),j_is_term(I,T),!,(must_j_get(I,How,O)),j_to_term(O,OO).
  130jo_to_term(I, O):- catch(jpl_enumeration_to_list(I,M),_,fail),!,j_to_term(M,O).
  131jo_to_term(I, O):- catch(jpl_array_to_list(I,M),_,fail),!,j_to_term(M,O).
  132jo_to_term(I, O):- catch(jpl_map_element(I,M),_,fail),!,j_to_term(M,O).
  133jo_to_term(I, O):- jpl_is_object(I),j_get(I,[getClass,isEnum],T),jpl_is_true(T),!,(must_j_get(I,[toString],O)).
  134jo_to_term(I, O):- jpl_is_object(I),j_get(I,pa(obj,[m(getClass,[]),jo_to_term],m(toString,[])),O).
  135jo_to_term(I, O):- jpl_is_object(I),(must_j_get(I,[toString],O)).
  136jo_to_term(IO,IO):-!.
  137
  138jconvert(class([edu, stanford, nlp, util], ['IntTuple']),pa('IntTuple',elems)).
  139jconvert(class([edu, stanford, nlp, trees], ['UniversalEnglishGrammaticalStructure']),term(ugs)).
  140jconvert(class([edu,stanford,nlp,semgraph],['SemanticGraph']),pa(sg,typedDependencies)).
  141jconvert(class([edu,stanford,nlp,dcoref],['CorefChain','CorefMention']),+ pa('CorefMention',-mentionSpan,-headIndex,-corefClusterID,-position, + animacy,+ gender,+ number,+ mentionType)).
  142jconvert(class([edu,stanford,nlp,dcoref],['CorefChain']),pa('CorefChain', - getRepresentativeMention,- getMentionsInTextualOrder)).
  143jconvert(class([java,lang],['String']),[toString,revcall(string_to_atom)]).
  144jconvert(class([edu,stanford,nlp,ling],['CoreLabel']),pa(twin,m(tag,[]),m(word,[]),m(index,[]),m(ner,[]))).
  145jconvert(class([edu,stanford,nlp,ling],['IndexedWord']),pa(wi,m(tag,[]),m(word,[]),m(index,[]))).
  146jconvert(class([edu,stanford,nlp,ling],['TaggedWord']),fa(m(tag,[]),m(word,[]))).
  147jconvert(array(class([java,lang],['Object'])),[call(jpl_array_to_list)]).
  148jconvert(class([edu,stanford,nlp,trees],['Tree']),pl([label,toString],[children,call(jpl_array_to_list)],[call(j_to_term)])).
  149jconvert(class([edu,stanford,nlp,trees],['TypedDependency']),fa([m(reln,[]),getShortName],m(gov,[]),m(dep,[]))).
  150jconvert(class([java,util],['Map']),[entrySet]).
  151jconvert(class([java,util],['Map','Entry']),[pa(kv,+getKey,+getValue)]).
  152jconvert(class([java,util],['List']),[toArray,+call(jpl_array_to_list)]).
  153jconvert(class([java,lang],['Class']),[call(jpl_class_to_type)]).
  154jconvert(class([java,lang],['Integer']),[m(intValue)]).
  155jconvert(class([java,util],['Collection']),[toArray,+call(jpl_array_to_list)]).
  156
  157
  158:- export(j_get/3).  159:- meta_predicate(j_get(?,?,?)).  160j_get(IO,[],IO):-!.
  161j_get(I,-(E),(E=O)):-!,must((j_get(I,E,M),j_to_term_until_done(M,O))).
  162j_get(I,+(E),O):-!,must((j_get(I,E,M),j_to_term_until_done(M,O))).
  163j_get(I,+,O):-!,must(j_to_term_until_done(I,O)).
  164j_get(I,[E|L],O):- !,(must_j_get(I,E,M)),!,(must_j_get(M,L,O)),!.
  165j_get(I,E,O):- compound(E),compound_name_arguments(E,fa,Args),!,must((maplist(j_get(I),Args,ArgsO),O=..ArgsO)).
  166j_get(I,E,O):- compound(E),compound_name_arguments(E,pa,[F|Args]),!,must((maplist(j_get(I),Args,ArgsO),O=..[F|ArgsO])).
  167j_get(I,pl(FunctorGet,ArgsGet,ArgFormat),O):- !, (must_j_get(I,FunctorGet,Atom)),(must_j_get(I,ArgsGet,List)),(must_maplist(must_j_get(ArgFormat),List,ListO)),O=..[Atom|ListO],!.
  168j_get(I,N,O):- number(N),is_list(I),nth0(N,I,O).
  169j_get(I,f(E),O):- jpl_get(I,E,O),!.
  170j_get(_,term(E),E):-!.
  171j_get(I,p2s,O):- pterm_to_sterm(I,O),!.
  172j_get(I,maplist(F),O):- must(is_list(I)),must_maplist(j_get(F),I,O),!.
  173j_get(I,maptree(F),O):- must(maptree(must_j_get(F),I,O)),!.
  174j_get(I,Compound,O):- compound(Compound),functor(Compound,lambda,_),call(Compound,I,O),!.
  175j_get(I,m(N),O):- jpl_call(I,N,[],O),!.
  176j_get(I,m(N,Args),O):- jpl_call(I,N,Args,O),!.
  177j_get(I,call(C),O):-!, must(call(C,I,O)),!.
  178j_get(I,show_call(C),O):-!, show_call(j_get(I,C,O)).
  179j_get(I,revcall(C),O):-!, must(call(C,O,I)),!.
  180j_get(I,E,O):- compound(E),compound_name_arguments(E,N,Args),catch(jpl_call(I,N,Args,O),_,fail),!.
  181j_get(I,j_to_term,O):- must(j_to_term(I,O)),!.
  182j_get(I,E,O):- catch(jpl_get(I,E,O),_,fail),!.
  183j_get(I,E,O):- catch(jpl_call(I,E,[],O),_,fail),!.
  184j_get(I,E,O):- catch(jpl_call(I,get,[E],O),_,fail),!.
  185j_get(I,E,O):- catch(jpl_call(I,getValue,[E],O),_,fail),!.
  186j_get(I,E,O):- catch(jpl_call(I,E,[I],O),_,fail),!.
  187j_get(I,E,O):- catch(call(E,I,O),_,fail),!.
  188
  189% j_get(O,[f(0),children,jpl_array_to_list,0,children,jpl_array_to_list],E).
  190
  191to_string(I):-jpl_get(class([java,lang],['System']),'out',Out),jpl_call(Out,println,[I],_).
  192% :- pos_tagger_test.
  193
  194:- op(400,xfy,((&))).  195:- op(400,xfy,((v))).  196
  197install_example(List):-is_list(List),!,maplist(install_example,List).
  198install_example(N=List):-is_list(List),!,maplist(add_example_value(N),List).
  199install_example(NList):-dmsg(warn(failed_install_example(NList))),!.
  200
  201:-dynamic(is_example_value/2).  202
  203:-export(add_example_value/2).  204add_example_value(N,V):- baseKB:assert_if_new(is_example_value(N,V)).
  205
  206:- op(900,xfx,(=>)).  207
  208:- install_example([
  209             sentences=[[^, 'All', persons, are, happy, '.']],
  210             sentencesToParse=[[^, 'All', persons, are, happy, '.']],
  211             syntaxTrees=[[specification, [s, [np, [det, all], [nbar, [n, persons]]], [vp, [], [aux, are, []], [ap_coord, [ap, [adj, happy]]], []]], '.']],
  212             drs0=[drs([], [ (drs([PERSON_OBJ], [object(PERSON_OBJ, person, countable, na, eq, 1)-1/2]) => drs([HAPPY_REL, A], [property(HAPPY_REL, happy, POS)-1/4, predicate(A, be, PERSON_OBJ, HAPPY_REL)-1/3]))]), drs([], [ (drs([PERSON_OBJ], [object(PERSON_OBJ, person, countable, na, eq, 1)-1/2])=>drs([HAPPY_REL, A], [property(HAPPY_REL, happy, POS)-1/4, predicate(A, be, PERSON_OBJ, HAPPY_REL)-1/3]))]), drs([], [ (drs([PERSON_OBJ], [object(PERSON_OBJ, person, countable, na, eq, 1)-1/2])=>drs([HAPPY_REL, A], [property(HAPPY_REL, happy, POS)-1/4, predicate(A, be, PERSON_OBJ, HAPPY_REL)-1/3]))])],
  213             tokens=[['All', persons, are, happy, '.']],
  214             paraphrase=[['If there is a person X1 then the person X1 is happy.']],
  215             drs=[drs([], [ (drs([PERSON_OBJ], [object(PERSON_OBJ, person, countable, na, eq, 1)-1/2])=>drs([HAPPY_REL, A], [property(HAPPY_REL, happy, POS)-1/4, predicate(A, be, PERSON_OBJ, HAPPY_REL)-1/3]))])],
  216             sdrs=[ ([object(PERSON_OBJ, person, countable, na, eq, 1)-1/2]=>[property(HAPPY_REL, happy, POS)-1/4, predicate(A, be, PERSON_OBJ, HAPPY_REL)-1/3])],
  217             fol=[forall(PERSON_OBJ, exists(HAPPY_PROP, exists(BE_EVENT, - (object(BE_FRAME, PERSON_OBJ, person, countable, na, eq, 1)-1/2)v (property(BE_FRAME, HAPPY_PROP, happy, POS)-1/4)& (predicate(BE_FRAME, BE_EVENT, be, PERSON_OBJ, HAPPY_PROP)-1/3)))), forall(PERSON_OBJ, exists(HAPPY_PROP, exists(BE_EVENT, - (object(BE_FRAME, PERSON_OBJ, person, countable, na, eq, 1)-1/2)v (property(BE_FRAME, HAPPY_PROP, happy, POS)-1/4)& (predicate(BE_FRAME, BE_EVENT, be, PERSON_OBJ, HAPPY_PROP)-1/3))))],
  218             pnf=[forall(PERSON_OBJ, (object(BE_FRAME, PERSON_OBJ, person, countable, na, eq, 1)-1/2=>exists(HAPPY_PROP, exists(BE_EVENT, (property(BE_FRAME, HAPPY_PROP, happy, POS)-1/4)& (predicate(BE_FRAME, BE_EVENT, be, PERSON_OBJ, HAPPY_PROP)-1/3))))), forall(PERSON_OBJ, (object(BE_FRAME, PERSON_OBJ, person, countable, na, eq, 1)-1/2=>exists(HAPPY_PROP, exists(BE_EVENT, (property(BE_FRAME, HAPPY_PROP, happy, POS)-1/4)& (predicate(BE_FRAME, BE_EVENT, be, PERSON_OBJ, HAPPY_PROP)-1/3)))))],
  219             kif(p)=[all(PERSON_OBJ, implies(tPerson(PERSON_OBJ), exists(HAPPY_PROP, exists(BE_EVENT, (vHappy(HAPPY_PROP), mudBe(PERSON_OBJ, HAPPY_PROP)))))), all(PERSON_OBJ, implies(tPerson(PERSON_OBJ), exists(HAPPY_PROP, exists(BE_EVENT, (vHappy(HAPPY_PROP), mudBe(PERSON_OBJ, HAPPY_PROP))))))],
  220             kif(f)=[all(PERSON_OBJ, exists(HAPPY_PROP, exists(BE_EVENT, (-tPerson(PERSON_OBJ);vHappy(HAPPY_PROP), mudBe(PERSON_OBJ, HAPPY_PROP))))), all(PERSON_OBJ, exists(HAPPY_PROP, exists(BE_EVENT, (-tPerson(PERSON_OBJ);vHappy(HAPPY_PROP), mudBe(PERSON_OBJ, HAPPY_PROP)))))],
  221             kif(d)=[implies(exists([PERSON_OBJ], tPerson(PERSON_OBJ)), exists([HAPPY_REL, A], (vHappy(HAPPY_REL), mudBe(PERSON_OBJ, HAPPY_REL)))), implies(exists([PERSON_OBJ], tPerson(PERSON_OBJ)), exists([HAPPY_REL, A], (vHappy(HAPPY_REL), mudBe(PERSON_OBJ, HAPPY_REL))))],
  222             kif(s)=[implies([tPerson(PERSON_OBJ)], [vHappy(HAPPY_REL), mudBe(PERSON_OBJ, HAPPY_REL)]), implies([tPerson(PERSON_OBJ)], [vHappy(HAPPY_REL), mudBe(PERSON_OBJ, HAPPY_REL)])]
  223           ]).  224
  225
  226:- add_example_value(stanfordTree,
  227  [ 'S',['NP', ['PRP', 'I-1']],[ 'VP',['VBD', 'had-2'],['ADVP', ['RB', 'never-3']],[ 'VP',['VBN', 'seen-4'],['NP', ['NN', 'something-5']],[ 'PP',['IN', 'like-6'],[ 'NP',['NP', ['DT', 'that-7']],['PP', ['IN', 'in-8'], ['NP', ['DT', 'any-9'], ['NN', 'language-10']]]]]]],['.', '.-11']]).  228
  229:- add_example_value(stanfordTree,
  230 [ 'FRAG', ['NP', ['NN', 'ok-1']],[',', ',-2'],[ 'SBAR',['IN', 'so-3'],[ 'S',['NP', ['PRP', 'you-4']],[ 'VP',['VBP', 'want-5'],[ 'NP',['NP', ['DT', 'a-6'], ['JJ', 'concrete-7'], ['NN', 'example-8']],[',', ',-9'],['RB', 'not-10'],['NP', ['DT', 'a-11'], ['JJ', 'general-12'], ['NN', 'rule-13']]]]]],['.', '?-14']]).  231
  232
  233% ===================================================================
  234
  235/*
  236TODO  FIX THE CONVERTERS!
  237:- install_converter(parser_stanford:acetext_to_typedDependencies(+acetext, -typedDependencies)).
  238:- install_converter(parser_stanford:typedDependencies_to_w2pos(+typedDependencies, -w2pos)).
  239:- install_converter(parser_stanford:acetext_to_w2pos(+acetext, -w2pos)).
  240:- install_converter(parser_stanford:w2pos_to_aacetext_w_pos(+w2pos, -acetext_w_pos)).
  241
  242:- install_converter(parser_stanford:acetext_to_stanfordTree(+acetext, -stanfordTree)).
  243:- install_converter(parser_stanford:typedDependencies_to_stanfordTree(+typedDependencies, -stanfordTree)).
  244*/
  245:- install_converter(parser_stanford:stanfordTree_to_simpleParseTree(+stanfordTree, -simpleParseTree)).  246
  247show_tree(H:-Tree):- !, nl,portray_clause((H:-Tree)),nl.
  248show_tree(Tree):-nl,portray_clause((t1:-Tree)),nl.
  249
  250tc0:- j_get('OK, so you want a concrete example, not a general rule?',
  251   [acetext_to_stanfordTree,stanfordTree_to_simpleParseTree],
  252   Tree),show_tree(Tree).
  253tc1:- acetext_to_stanfordTree('I had never seen something like that in any language.',Tree),show_tree(Tree).
  254tc2:- acetext_to_stanfordTree('Can the can do the Can Can dance?',Tree),show_tree(Tree).
  255
  256% ===================================================================
  257% 
  258
  259
  260:-export(acetext_to_w2pos/2).  261acetext_to_w2pos(I,O):-acetext_to_typedDependencies(I,M),typedDependencies_to_w2pos(M,O).
  262
  263% JJ = penn tag
  264% jj = brill tag
  265% 'Gradable-Adjective' -->  'JJR'
  266pos_penn_pos(POS,PennPOS):- flatten([POS],POSL),
  267  pos_penn_pos0(POSL,PennPOS),
  268  list_to_set([open, wordnum(-1)|POSL],[open, wordnum(-1)|SET]),
  269  pos_penn_pos0(SET,PennPOS).
  270
  271pos_penn_pos0([],open).
  272pos_penn_pos0(POSL,PennPOS):-
  273  must((member(PennPOS,POSL),
  274        atom(PennPOS),
  275        downcase_atom(PennPOS,UPOS), PennPOS=UPOS)),is_word_tag(PennPOS),
  276        must(is_penn(PennPOS)).
  277
  278% The/DT quick/JJ brown/JJ fox/NN jumped/VBD over/IN the/DT lazy/JJ dog/NN ./.
  279% w(pretty,['Adjective','Gradable-Adjective'])  -->  'pretty/JJR'
  280% w(pretty,['Adjective'])  -->  'pretty/JJ' 
  281
  282
  283% pennTagString,'EX-PennTag','EX', 
  284w2_to_pos_slash_word(Text,open,Text):-!.
  285w2_to_pos_slash_word(Text,POS,Atom):-
  286 must(get_word_from_hyphen(Text,W,_)),
  287 pos_penn_pos(POS,PennPOS),must(atom(PennPOS)),
  288 ( PennPOS==open -> Atom = W ; format(atom(Atom),'~w/~w',[W,PennPOS]) ).
  289
  290is_phrase_tag(PM):- ( \+ atom(PM) ),!,fail.
  291is_phrase_tag(PM):- arg(_,v('VP','S','NBAR','SBAR','NP','VP','ADJP'),PM),!.
  292is_phrase_tag(PM):- upcase_atom(PM,UC),!, \+ is_word_tag(UC).
  293
  294is_word_tag(WM):- atom(WM),bposToCPos(WM,DEF), is_variant_case(DEF),!.
  295%TODO is_word_tag(PM):- upcase_atom(PM,UC),!, \+ is_phrase_tag(UC).
  296
  297% jj = brill tag
  298is_brill_word_tag(WM):- atom(WM), downcase_atom(WM,UWM), WM==UWM, bposToCPos(WM,DEF), WM\=DEF, is_variant_case(DEF),!.
  299% JJ = penn tag
  300is_penn_word_tag(WM):- is_penn(WM),
  301    must((atom(WM),upcase_atom(WM,UWM), WM==UWM, bposToCPos(WM,DEF), WM\=DEF, is_variant_case(DEF))),!.
  302
  303
  304is_variant_case(DEF):- atom(DEF), (upcase_atom(DEF,OC);downcase_atom(DEF,OC)),DEF\=OC.
  305
  306w2pos_to_aacetext_w_pos(w(Text,POS),Atom):- w2_to_pos_slash_word(Text,POS,Atom).
  307w2pos_to_aacetext_w_pos([POS,Text],Atom):-  is_phrase_tag(POS),atom(Text), !, w2_to_pos_slash_word(Text,POS,Atom).
  308w2pos_to_aacetext_w_pos(W2List,Atom):-is_list(W2List),
  309    maplist(w2pos_to_aacetext_w_pos,W2List,AtomS),concat_atom(AtomS,' ',Atom).
  310w2pos_to_aacetext_w_pos(Atom,Atom).
  311
  312:-export(typedDependencies_to_w2pos/2).  313typedDependencies_to_w2pos(I,O):-  (must_j_get(I,[0,p2s,
  314  maplist(call(w_to_w2))],M)),!,
  315  (must_maplist(w2stanford_to_w2cyc,M,O)).
  316
  317:-export(typedDependencies_to_stanfordTree/2).  318typedDependencies_to_stanfordTree(I,O):- j_get(I,1,M),maptree(simplified_tree_element,M,O).  
  319
  320stanfordTree_to_simpleParseTree(I,O):- maptree(simplified_tree_element,I,O).
  321
  322
  323stanfordTree_to_syntaxTrees(I,O):- transform_language(lang_stanfordTree_to_syntaxTrees,I,O).
  324% :- add_example_value(stanfordTree , ['ROOT'('S'('NP'('DT'('All-1'),'NNS'('persons-2')),'VP'('VBP'('are-3'), 'ADJP'('JJ'('happy-4'))),'.'('.-5')))]).
  325% -> wordParseTree = 'S'('NP'('DT'('All-1'),'NNS'('persons-2')),'VP'('aux'('are-3'),           'ADJP'('JJ'('happy-4')))
  326% syntaxTrees=[[specification, [s, [np, [det, all], [nbar, [n, persons]]], [vp, [], [aux, are, []], [ap_coord, [ap, [adj, happy]]], []]], '.']],
  327% -> wordParseTree = [s, [np, [det, all], [nbar, [n, persons]]], [vp, [aux, are, []], [ap_coord, [ap,  [adj, happy]]], []]]
  328
  329
  330 is_penn('CC'). %  Coordinating conjunction 
  331 is_penn('CD'). %  Cardinal number 
  332 is_penn('DT'). %  Determiner 
  333 is_penn('EX'). %  Existential there 
  334 is_penn('FW'). %  Foreign word 
  335 is_penn('IN'). %  Preposition or subordinating conjunction 
  336 is_penn('JJ'). %  Adjective 
  337 is_penn('JJR'). %  Adjective, comparative 
  338 is_penn('JJS'). %  Adjective, superlative 
  339 is_penn('LS'). %  List item marker 
  340 is_penn('MD'). %  Modal 
  341 is_penn('NN'). %  Noun, singular or mass 
  342 is_penn('NNP'). %  Proper noun, singular 
  343 is_penn('NNPS'). %  Proper noun, plural 
  344 is_penn('NNS'). %  Noun, plural 
  345 is_penn('PDT'). %  Predeterminer 
  346 is_penn('POS'). %  Possessive ending 
  347 is_penn('PRP$'). %  Possessive pronoun 
  348 is_penn('PRP'). %  Personal pronoun 
  349 is_penn('RB'). %  Adverb 
  350 is_penn('RBR'). %  Adverb, comparative 
  351 is_penn('RBS'). %  Adverb, superlative 
  352 is_penn('RP'). %  Particle 
  353 is_penn('SYM'). %  Symbol 
  354 is_penn('TO'). %  to 
  355 is_penn('UH'). %  Interjection 
  356 is_penn('VB'). %  Verb, base form 
  357 is_penn('VBD'). %  Verb, past tense 
  358 is_penn('VBG'). %  Verb, gerund or present participle 
  359 is_penn('VBN'). %  Verb, past participle 
  360 is_penn('VBP'). %  Verb, non-3rd person singular present 
  361 is_penn('VBZ'). %  Verb, 3rd person singular present 
  362 is_penn('WDT'). %  Wh-determiner 
  363 is_penn('WP$'). %  Possessive wh-pronoun 
  364 is_penn('WP'). %  Wh-pronoun 
  365 is_penn('WRB'). %  Wh-adverb
  366
  367is_node_unwrappable('ROOT').
  368is_node_unwrappable('NBAR').
  369is_node_unwrappable('specification').
  370
  371is_node_unlistifiable('ROOT').
  372is_node_unlistifiable('nbar').
  373%is_node_unlistifiable('specification').
  374
  375rec_lambda5(I,O,Code,Start,End):- copy_term(v(I,Code,O),v(Start,Goal,End)),call(Goal),!.
  376:-maptree(rec_lambda5(I,O,(atom(I),upcase_atom(I,O))),a(b),X),assertion(X='A'('B')).  377
  378
  379simplified_tree_element(C,O):- compound(C),C=..[ROOT,LIST],simplified_tree_element0([ROOT,LIST],O),[ROOT,LIST]\=@=O,!.
  380simplified_tree_element([ROOT|LIST],O):- atom(ROOT),C=..[ROOT,LIST],simplified_tree_element0(C,O),[ROOT,LIST]\=@=O,!.
  381simplified_tree_element(C,O):-  simplified_tree_element0(C,O),!.
  382
  383simplified_tree_element_or_pass(I , O):-simplified_tree_element(I,O),!.
  384simplified_tree_element_or_pass(IO,IO).
  385
  386simplified_tree_element0(Var,Var):-var(Var),!.
  387simplified_tree_element0([ROOT,LIST],O):- is_node_unwrappable(ROOT), !,
  388  must(simplified_tree_element_or_pass(LIST,O)),!.
  389simplified_tree_element0([ROOT,LIST],O):- is_node_unlistifiable(ROOT), !,
  390  simplified_tree_element_or_pass(LIST,O),!.
  391
  392
  393simplified_tree_element0(wi(Text,POS,Index),w(Text,[penn(POS),index(Index)])).
  394simplified_tree_element0('VBP'('are-3'),w(are,[penn('VBP'),index(3)])):-!.
  395simplified_tree_element0(POSHWORD,w(TEXT,[penn(POS),index(INDEX)])):- compound(POSHWORD),POSHWORD=..[POS,HWORD],
  396    atom(HWORD),atomic_list_concat([TEXT,INDEX],'-',HWORD),!.
  397simplified_tree_element0('are/VBP',w(are,[penn('VBP')])):-!.
  398simplified_tree_element0(SWORD,w(TEXT,[index(INDEX)])):- 
  399    atom(SWORD),atomic_list_concat([TEXT,INDEX],'/',SWORD),!.
  400simplified_tree_element0('are-3',w(are,[index(3)])):-!.
  401simplified_tree_element0(w(Text,POS),O):- !,must(w2stanford_to_w2cyc(w(Text,POS),O)),!.
  402simplified_tree_element0(Var,O):-atom(Var),atomic_list_concat([_,_],'/',Var),!,get_word_from_slash(Var,Text,POS),
  403            simplified_tree_element0(w(Text,POS),O).
  404simplified_tree_element0([POS,Text],O):- is_word_tag(POS),!,simplified_tree_element0(w(Text,POS),O),!.
  405simplified_tree_element0([ROOT|LIST],valueWithComment(O,warn(ROOT))):- is_node_unwrappable(ROOT), !,
  406  simplified_tree_element_or_pass(LIST,O),!.
  407
  408
  409:-export(acetext_to_w2pos/2).  410acetext_to_stanfordTree(I,O):-acetext_to_typedDependencies(I,M),
  411  typedDependencies_to_stanfordTree(M,O).
  412
  413:-export(w2stanford_to_w2cyc/2).  414w2stanford_to_w2cyc(I,O):-  must(I = w(_,_)), copy_term(I,O),
  415  arg(1,I,WWP),
  416   must(get_word_from_hyphen(WWP,W,N)),
  417  arg(2,I,SPOS),
  418  findall(E,bposToCPos(SPOS,E),List),
  419  list_to_set([SPOS,wordnum(N)|List],Set),
  420  nb_setarg(1,O,W),
  421  nb_setarg(2,O,Set),!.
  422
  423
  424%'All-1' => 'All'
  425%'persons-2' => 'persons'
  426:-export(get_word_from_hyphen/3).  427get_word_from_hyphen(w(Text,POSL),Text,Index):- (member(index(Index),POSL);Index= -1),!.
  428get_word_from_hyphen(wi(Text,_,Index),Text,Index):-!.
  429get_word_from_hyphen(SP,_,_):- (\+ atomic(SP)),!,fail.
  430get_word_from_hyphen(SP,W,1):-atom_concat(W,'-1',SP),!.
  431get_word_from_hyphen(SP,W,2):-atom_concat(W,'-2',SP),!.
  432get_word_from_hyphen(SP,W,Num):-concat_atom([W,N],'-',SP),atom_number(N,Num),!.
  433get_word_from_hyphen(SP,W,Num):-concat_atom([W1,W2,N],'-',SP),atom_number(N,Num),!,concat_atom([W1,W2],'-',W).
  434get_word_from_hyphen(SP,W,Num):-concat_atom(List,'-',SP),reverse(List,[N|Rev]),atom_number(N,Num),!,
  435   reverse(Rev,UnRev),concat_atom(UnRev,'-',W).
  436get_word_from_hyphen(W,W,-1).
  437
  438
  439%'Pretty/JJ' => 'Pretty'/'JJ'
  440%'persons' => 'persons'/open
  441:-export(get_word_from_slash/3).  442get_word_from_slash(w(Text,POS),Text,POS):-!.
  443get_word_from_slash(wi(Text,POS,_Index),Text,POS):-!.
  444get_word_from_slash(SP,_,_):- (\+ atomic(SP)),!,fail.
  445get_word_from_slash(SP,W,POS):-concat_atom([W,N],'/',SP),=(N,POS),!.
  446get_word_from_slash(SP,W,POS):-concat_atom([W1,W2,N],'/',SP),=(N,POS),!,concat_atom([W1,W2],'/',W).
  447get_word_from_slash(SP,W,POS):-concat_atom(List,'/',SP),reverse(List,[N|Rev]),=(N,POS),!,
  448   reverse(Rev,UnRev),concat_atom(UnRev,'/',W).
  449get_word_from_slash(W,W,open).
  450
  451
  452% syntaxTrees=[[specification, [s, [np, [det, all], [nbar, [n, persons]]], [vp, [], [aux, are, []], [ap_coord, [ap, [adj, happy]]], []]], '.']],
  453
  454
  455:-if(\+ current_predicate(isSlot/1)).  456isSlot(Var):-var(Var),!.
  457isSlot('$VAR'(Var)):-number(Var).
  458:-endif.  459
  460:-if(\+ current_predicate(pterm_to_sterm/2)).  461pterm_to_sterm(VAR,VAR):-isNonCompound(VAR),!.
  462pterm_to_sterm([X|L],[Y|Ls]):-!,pterm_to_sterm(X,Y),pterm_to_sterm(L,Ls),!.
  463pterm_to_sterm(X,Y):-compound(X),X=..L,pterm_to_sterm(L,Y),!.
  464pterm_to_sterm(X,X).
  465
  466:-endif.