1:-module(bot_neox, 
    2 [
    3  test_neox/0,
    4  test_neox/1,
    5  test_neox/2,
    6  test_neox_parse1/0,
    7  test_neox_parse2/0,  
    8  foc_neox_stream/2,
    9  text_to_neox_pos/2,
   10  text_to_neox_sents/2,
   11  text_to_neox_segs/2,
   12  neox_parse/2]).   13% test_neox('{"presence_penalty":1.4,"prompt":"How do you spell your name?"}',X).
   14% test_neox('{"presence_penalty":2.0,"prompt":"A florida man was ", "max_tokens":750}',X),print(X).
   15:- set_module(class(library)).   16:- set_module(base(system)).   17:- use_module(library(logicmoo_utils)).   18:- use_module(library(logicmoo_nlu/parser_penn_trees)).   19:- use_module(library(logicmoo_nlu/parser_tokenize)).   20
   21:- dynamic(lmconfig:bot_py_dir/1).   22:- ignore(( \+ lmconfig:bot_py_dir(Dir), prolog_load_context(directory,Dir), assert(lmconfig:bot_py_dir(Dir)))).   23
   24read_neox_lines(In, Result):- neox_to_dict(In, Result),!.
   25
   26neox_completion(Text,LExpr):-
   27  neox_parse(Text, String),
   28  nop(dmsg(neox_parse=String)),  
   29  neox_to_txt(String,LExpr),
   30  nop(print_tree_nl(neox=LExpr)),!.
   31
   32neox_to_w2(Text,Result):- neox_to_dict(Text,M),neox_dict_to_txt(M, Result).
   33%neox_to_w2((Word,POS),[POS,Word]).
   34%neox_to_w2(Text,Result):- neox_to_dict(Text,Result),!.
   35%neox_to_w2(Text,_ListO):- \+ compound(Text), nl,writeq(Text),nl,!,fail.
   36
   37neox_to_dict(Text,Result):- is_dict(Text),!,Result=Text.
   38neox_to_dict(In, Result):- is_stream(In),!,neox_stream_to_dict(In,_, Term),neox_to_dict(Term, Result).
   39neox_to_dict(neox(_In,Text),Result):- !, neox_to_dict(Text,Result).
   40neox_to_dict(Compound,Result):- \+ atomic(Compound),!, any_to_json_dict(Compound,Result),!.
   41neox_to_dict(Text,Result):- notrace(on_x_fail(atom_json_dict(Text,Term,[]))),!,neox_to_dict(Term,Result).
   42neox_to_dict(Text,Result):- notrace(on_x_fail(atom_json_term(Text,Term,[]))),!,neox_to_dict(Term,Result).
   43neox_to_dict(Text,Result):- notrace(on_x_fail(atom_to_term(Text,Term,_))),!,neox_to_dict(Term,Result).
   44
   45neox_dict_to_txt(Dict,Result):- neox_kv_name_value(Dict,choices,E),!,neox_to_txt(E,Result).
   46neox_dict_to_txt(Dict,Result):- neox_kv_name_value(Dict,text,Result).
   47
   48neox_to_txt(In, Result):-  is_stream(In),!,neox_stream_to_dict(In,_, Term),!,neox_to_txt(Term, Result).
   49neox_to_txt(E,V):- is_list(E),!,member(S,E),neox_to_txt(S,V).
   50neox_to_txt(Text,Result):- is_dict(Text),!,neox_dict_to_txt(Text,Result).
   51neox_to_txt(Text,Result):- compound(Text),!,neox_kv_name_value(Text,text,Result).
   52neox_to_txt(Text,Text):-!.
   53
   54neox_kv_name_value(E,_,_):- \+ compound(E),!,fail.
   55neox_kv_name_value(E,K,V):- is_list(E),!,member(S,E),neox_kv_name_value(S,K,V).
   56neox_kv_name_value(E,K,V):- compound_name_arity(E,_,2),E=..[_,N,V],atomic(N),\+ number(N),name(K,N),!.
   57neox_kv_name_value(E,K,V):- is_dict(E),get_dict(K,E,V),!.
   58neox_kv_name_value(E,K,V):- arg(_,E,S),compound(S),neox_kv_name_value(S,K,V).
   59
   60neox_lexical_segs(I,O):-
   61  old_into_lexical_segs(I,M),!,
   62  neox_parse_or_skip(I,S),!,
   63  merge_neox(S,M,O),!.
   64
   65%neox_parse_or_skip(I,O):- catch(neox_parse(I,O),_,fail),nonvar(O),!.
   66neox_parse_or_skip(_,[]).
   67
   68merge_neox([],O,O):-!.
   69merge_neox([H|T],I,O):- !, merge_neox(H,I,M), merge_neox(T,M,O).
   70merge_neox(w(W,L),O,O):- member(w(W,OL),O), \+ member(neox,OL),!,    
   71  ignore((member(spos(Pos),L),  downcase_atom(Pos,DPos), set_pos(2,DPos,OL))), 
   72  nb_set_add(OL,[neox|L]), !.
   73merge_neox(span(List),I,O):- member(span(_),List),!,
   74  merge_neox(List,I,O),!.
   75merge_neox(span(List),O,O):- 
   76  member(seg(S,E),List), member(span(Other),O), member(seg(S,E),Other),!,
   77  nb_set_add(Other,[neox|List]).
   78merge_neox(dep_tree(Type,R,Arg),O,O):- 
   79  member(w(_,Other),O),member(node(R),Other),
   80  nb_set_add(Other,dep_tree(Type,R,Arg)).
   81merge_neox(_,I,I):-!.
   82merge_neox(S,I,O):- append(I,[S],O).
   83
   84neox_stream_to_dict(In,_, Result):- peek_string(In,10,S),atom_contains(S,"neox("),!,read_term(In,Term,[]),neox_to_dict(Term, Result).
   85neox_stream_to_dict(In,S, Result):- atomic(S),atom_contains(S,"neox("),!,read_term_from_atom_rest(In,S,Term),neox_to_dict(Term, Result).
   86neox_stream_to_dict(In,S, Result):- atomic(S),at_end_of_stream(In),!,neox_to_dict(S, Result).
   87neox_stream_to_dict(In,_, Result):- repeat, read_pending_codes(In,Codes,[]),
   88 (Codes==[]->(sleep(0.1),fail);true),sformat(S,'~s',[Codes]),
   89 neox_stream_to_dict(In,S, Result).
   90
   91
   92:- dynamic(tmp:existing_neox_stream/4).   93:- volatile(tmp:existing_neox_stream/4).   94foc_neox_stream(Out,In):- thread_self(Self),tmp:existing_neox_stream(Self,_,Out,In),!,clear_neox_pending(In).
   95/*
   96foc_neox_stream(Out,In):- tmp:existing_neox_stream(OldThread,FFid,Out,In), \+ thread_property(OldThread,status(running)),!,
   97  retract(tmp:existing_neox_stream(OldThread,FFid,Out,In)),
   98  thread_self(Self),
   99  assert(tmp:existing_neox_stream(Self,FFid,Out,In)),!.
  100*/
  101foc_neox_stream(Out,In):- 
  102  user:network_service_info(neox,port,P4083),
  103  thread_self(Self),
  104  tcp_socket(Socket),
  105  catch((tcp_connect(Socket, 'logicmoo.org':P4083),
  106  tcp_open_socket(Socket, StreamPair)),_,fail),!,
  107  StreamPair = In, StreamPair = Out,
  108  set_stream(In,close_on_exec(false)),
  109  set_stream(In,close_on_abort(false)),
  110  set_stream(In,eof_action(eof_code)),
  111  assert(tmp:existing_neox_stream(Self,_,Out,In)),!.
  112
  113foc_neox_stream(Out,In):- current_prolog_flag(python_local,true),
  114  lmconfig:bot_py_dir(Dir),
  115  thread_self(Self),
  116  sformat(S,'python bot_neox.py -nc -cmdloop ',[]),
  117  nop(writeln(S)),
  118    process_create(path(bash), ['-c', S], [ cwd(Dir),  stdin(pipe(Out)),stdout(pipe(In)), stderr(null), process(FFid)]),!,
  119  set_stream(In,close_on_exec(false)),
  120  set_stream(Out,close_on_exec(false)),
  121  set_stream(In,close_on_abort(false)),
  122  set_stream(Out,close_on_abort(false)),
  123  set_stream(In,eof_action(eof_code)),
  124  set_stream(Out,eof_action(eof_code)),
  125  sleep(1.0),
  126  read_until_neox_notice(In,"cmdloop_Ready."),!,
  127  assert(tmp:existing_neox_stream(Self,FFid,Out,In)).
  128
  129read_until_neox_notice(In,Txt):- repeat,read_line_to_string(In,Str),(Str==end_of_file;atom_contains(Str,Txt)),!.
  130
  131current_neox_stream(In):- thread_self(Self),tmp:existing_neox_stream(Self,_FFid,_Out,In).
  132
  133clear_neox_pending:- current_neox_stream(In), clear_neox_pending0(In),!.
  134clear_neox_pending(In):- nop(clear_neox_pending0(In)).
  135
  136clear_neox_pending0(In):- at_end_of_stream(In),!,dmsg(clear_neox_pending=at_end_of_stream).
  137clear_neox_pending0(In):- read_pending_codes(In,Codes,[]),dmsg(clear_neox_pending=Codes).
  138
  139tokenize_neox_string([Str|Text],AtomO):- atomic(Str), is_list(Text), !, text_to_neox_string([Str|Text],AtomO).
  140tokenize_neox_string(Atom,AtomO):- atom(Atom),!,Atom=AtomO.
  141tokenize_neox_string(JSON,AtomO):- compound(JSON),!,any_to_json_dict(JSON,Dict),atom_json_dict(AtomO,Dict,[]).
  142tokenize_neox_string(Text,AtomO):- text_to_neox_string(Text,AtomO).
  143text_to_neox_string(Text,StrO):- any_to_string(Text,Str),  replace_in_string('\n',' ',Str,StrO).
  144/*
  145tokenize_neox_string(Text,StrO):- any_to_string(Text,Str), replace_in_string(['\\'='\\\\','\''='\\\''],Str,StrM),
  146  atomics_to_string(["'",StrM,"'"],StrO).
  147*/
  148
  149neox_parse(Text, Lines) :- 
  150  tokenize_neox_string(Text,Neox),
  151  neox_parse2(Neox, Lines).
  152
  153neox_parse2(String, Lines) :- 
  154  once(neox_parse3(String, Lines)
  155      ;neox_parse4(String, Lines)).
  156
  157try_neox_stream(Out,Write):- once(catch((format(Out,'~w',[Write])),_,
  158  (retract(tmp:existing_neox_stream(_,_,Out,_)),fail))).
  159
  160% Clears if there is a dead one
  161neox_parse3(_String, _Lines) :- fail,
  162  foc_neox_stream(Out,_In),
  163  try_neox_stream(Out,''),fail.
  164% Reuses or Creates
  165neox_parse3(String, Lines) :-
  166  foc_neox_stream(Out,In),
  167  try_neox_stream(Out,String),
  168  try_neox_stream(Out,'\n'),
  169  flush_output(Out),
  170  read_neox_lines(In, Lines).
  171
  172% Very slow version
  173neox_parse4(String, Lines) :- current_prolog_flag(python_local,true),
  174  lmconfig:bot_py_dir(Dir),
  175  sformat(S,'python bot_neox.py -nc ~q ',[String]),
  176  nop(writeln(S)),
  177    process_create(path(bash), ['-c', S], [ cwd(Dir), stdout(pipe(In))]),!,
  178  read_until_neox_notice(In,"cmdloop_Ready."),!,
  179  read_neox_lines(In, Lines).
  180
  181test_neox_parse1 :-
  182  String = "Can the can do the Can Can?",
  183  neox_parse3(String, Lines),
  184  pprint_ecp_cmt(yellow,test_neox_parse1=Lines).
  185
  186test_neox_parse2 :-
  187  Text = "Can the can do the Can Can?",
  188  neox_parse4(Text,Lines),
  189  pprint_ecp_cmt(yellow,test_neox_parse2=Lines).
  190
  191test_neox_parse3 :-
  192  Text = "Can the can do the Can Can?",
  193  neox_parse2(Text,Lines),
  194  pprint_ecp_cmt(yellow,test_neox_parse3=Lines).
  195
  196   
  197neox_pos_info(Text,PosW2s,Info,LExpr):-
  198  text_to_neox_sents(Text,LExpr),
  199  tree_to_lexical_segs(LExpr,SegsF),
  200  segs_retain_w2(SegsF,Info,PosW2s),!.
  201
  202text_to_neox_pos(Text,PosW2s):- neox_parse(Text,PosW2s),!.
  203text_to_neox_pos(Text,PosW2s):- neox_pos_info(Text,PosW2s0,_Info,_LExpr),guess_pretty(PosW2s0),!,PosW2s=PosW2s0.
  204  
  205text_to_neox_segs(Text,Segs):-
  206  neox_completion(Text,LExpr),
  207  tree_to_lexical_segs(LExpr,Segs).
  208
  209text_to_neox_sents(Text,Sent):-
  210  text_to_neox_segs(Text,Segs),!,
  211  neox_segs_to_sentences(Segs,Sent),!.
  212
  213neox_segs_to_sentences(Segs,sentence(0,W2,Info)):-
  214  segs_retain_w2(Segs,Info,W2).
  215
  216
  217:- if( \+ getenv('keep_going','-k')).  218:- use_module(library(editline)).  219:- add_history((call(make),call(test_neox1))).  220:- endif.  221
  222baseKB:regression_test:- test_neox(1,X),!,test_neox(X).
  223baseKB:sanity_test:- make, forall(test_neox(1,X),test_neox(X)).
  224baseKB:feature_test:- test_neox.
  225
  226test_neox0:- 
  227  Txt = "PERSON1 asks : Hey , what 's going on XVAR. < p >. PERSON2 said : Not a whole lot . . < p >. PERSON2 said : I 'm looking forward to the weekend , though . . < p >. PERSON1 asks : Do you have any big plans XVAR. < p >. PERSON2 said : Yes . . < p >. PERSON2 said : I 'm going to Wrigley Field on Saturday . . < p >. PERSON1 asks : Aren 't the Cubs out of town XVAR. < p >. PERSON2 said : Yes , but there 's a big concert at Wrigley this weekend . . < p >. PERSON1 said : Oh nice . . < p >. PERSON1 asks : Who 's playing XVAR. < p >. PERSON2 said : Pearl Jam is headlining the Saturday night show . . < p >. PERSON1 said : Wow , Pearl Jam . . < p >. PERSON1 said : I remeber when I got their first CD , Ten , at the record store at Harlem and Irving Plaza . . < p >. PERSON2 said : Oh right . . < p >. PERSON2 said : I remember that record store . . < p >. PERSON1 said : It was called Rolling Stone , and they went out of business many years ago . . < p >. PERSON2 said : Oh that 's too bad . . < p >. PERSON2 said : I really loved taking the bus to Harlem and Irving and visiting that store . . < p >. PERSON1 said : Me too . . < p >. PERSON1 said : We did n't have the internet back then and had to discover new music the hard way . . < p >. PERSON2 said : Haha yes . . < p >. PERSON2 said : I remember discovering ' ' Nirvana before they got famous . . < p >. PERSON1 said : Those were the good old days . . < p >. PERSON2 said : Yes they were . . < p >. PERSON2 said : I need to dig up my old Sony disc player and pop in an old CD . . < p >. PERSON1 asks : Where did the time go XVAR. < p >. PERSON1 said : Pearl Jam is 25 years old already . . < p >. PERSON2 said : It seems like only yesterday that the grunge music movement took over . . < p >. PERSON1 said : Right . . < p >. PERSON1 said : I bet everyone at the concert will be in their forty 's . . < p >. PERSON2 said : No doubt . . < p >. PERSON2 said : Well , I hope you have a great time at the concert . . < p > .",
  228  test_neox(Txt),
  229  ttyflush,writeln(('\n test_neox0.')),!.
  230
  231test_neox1:- 
  232  %Txt = "Rydell used his straw to stir the foam and ice remaining at the bottom of his tall plastic cup, as though he were hoping to find a secret prize.",
  233  Txt = "The Norwegian dude lives happily in the first house.",
  234  test_neox(Txt),
  235  ttyflush,writeln(('\n test_neox1.')),!.
  236test_neox2:- 
  237  Txt = "Rydell used his straw to stir the foam and ice remaining at the bottom of his tall plastic cup, as though he were hoping to find a secret prize.",
  238  %Txt = "The Norwegian dude lives happily in the first house.",
  239  test_neox(Txt),
  240  ttyflush,writeln(('\n test_neox2.')),!.
  241
  242test_neox:- 
  243  Txt = "Rydell was a big quiet Tennessean with a sad shy grin, cheap sunglasses, and a walkie-talkie screwed permanently into one ear.",
  244  test_neox(Txt),
  245  ttyflush,writeln(('\n test_neox.')),
  246  fail.
  247test_neox:- forall(test_neox(X),test_neox(X)).
  248
  249test_1neox(Text):- 
  250  format('~N?- ~p.~n',[test_neox(Text)]),
  251  neox_completion(Text,W),
  252  print_tree_nl(W),
  253  !.
  254test_1neox(Text):- wdmsg(failed(test_1neox(Text))).
  255
  256test_neox(N):- number(N),!, forall(test_neox(N,X),test_1neox(X)). 
  257test_neox(X):- test_neox(_,X),nop(lex_info(X)).
  258
  259test_neox(In,Out):- nonvar(In),\+ number(In),var(Out),!,neox_completion(In,Out).
  260test_neox(_,X):- nonvar(X), !, once(test_1neox(X)).
  261
  262test_neox(1,".\nThe Norwegian lives in the first house.\n.").
  263test_neox(1,"").
  264test_neox(1,".").
  265test_neox(1,"\n").
  266
  267test_neox(1,"Rydell used his straw to stir the foam and ice remaining at the bottom of his tall plastic cup, as though he were hoping to find a secret prize.").
  268
  269test_neox(2,Each):- test_neox(3,Atom),atomic_list_concat(List,'\n',Atom), member(Each,List).
  270
  271test_neox(3,
  272'There are 5 houses with five different owners.
  273 These five owners drink a certain type of beverage, smoke a certain brand of cigar and keep a certain pet.
  274 No owners have the same pet, smoke the same brand of cigar or drink the same beverage.
  275 The man who smokes Blends has a neighbor who drinks water.
  276 A red cat fastly jumped onto the table which is in the kitchen of the house.
  277 After Slitscan, Laney heard about another job from Rydell, the night security man at the Chateau.
  278 Rydell was a big quiet Tennessean with a sad shy grin, cheap sunglasses, and a walkie-talkie screwed permanently into one ear.
  279 Concrete beams overhead had been hand-painted to vaguely resemble blond oak.
  280 The chairs, like the rest of the furniture in the Chateau\'s lobby, were oversized to the extent that whoever sat in them seemed built to a smaller scale.
  281 Rydell used his straw to stir the foam and ice remaining at the bottom of his tall plastic cup, as though he were hoping to find a secret prize.
  282 A book called, "A little tribute to Gibson".
  283 "You look like the cat that swallowed the canary, " he said, giving her a puzzled look.').
  284
  285
  286test_neox(4,".
  287The Brit lives in the red house.
  288The Swede keeps dogs as pets.
  289The Dane drinks tea.
  290The green house is on the immediate left of the white house.
  291The green house's owner drinks coffee.
  292The owner who smokes Pall Mall rears birds.
  293The owner of the yellow house smokes Dunhill.
  294The owner living in the center house drinks milk.
  295The Norwegian lives in the first house.
  296The owner who smokes Blends lives next to the one who keeps cats.
  297The owner who keeps the horse lives next to the one who smokes Dunhills.
  298The owner who smokes Bluemasters drinks beer.
  299The German smokes Prince.
  300The Norwegian lives next to the blue house.
  301The owner who smokes Blends lives next to the one who drinks water.").
  302
  303:- add_history(test_neox).  304:- fixup_exports.