1/*
    2% NomicMUD: A MUD server written in Prolog
    3%
    4% Some parts used Inform7, Guncho, PrologMUD and Marty's Prolog Adventure Prototype
    5% 
    6% July 10, 1996 - John Eikenberry 
    7% Copyright (C) 2004 Marty White under the GNU GPL
    8% 
    9% Dec 13, 2035 - Douglas Miles
   10%
   11%
   12% Logicmoo Project changes:
   13%
   14% Main file.
   15%
   16*/
   17
   18/*
   19  
   20 ec_reader:   
   21    Converts Eric Muellers DEC Reasoner files  (IBM ".e" files)
   22    To a Prolog readable ".e.pl" which may be maintained by hand
   23    
   24
   25*/

   26:- module(ec_reader,[convert_e/1, set_ec_option/2, verbatum_functor/1, builtin_pred/1, e_to_pl/3, s_l/2,
   27   echo_format/1, echo_format/2]).
   28
   29
   30
   31:- use_module(library(logicmoo/portray_vars)).   32
   33
   34set_ec_option(N,V):- retractall(etmp:ec_option(N,_)),asserta(etmp:ec_option(N,V)).
   35
   36
   37% used by ec_reader
   38verbatum_functor(function).  verbatum_functor(event). 
   39verbatum_functor(predicate).  verbatum_functor(fluent).
   40verbatum_functor(next_axiom_uses).
   41
   42is_reified_sort(S):- S==belief.
   43
   44non_list_functor(ignore).
   45non_list_functor(manualrelease).
   46non_list_functor(sort).
   47non_list_functor(reified_sort).
   48non_list_functor(belief).
   49non_list_functor(reified).
   50non_list_functor(noninertial).
   51non_list_functor(mutex).
   52non_list_functor(completion).
   53non_list_functor(next_axiom_uses).
   54
   55is_non_sort(range).
   56is_non_sort(option).
   57is_non_sort(load).
   58is_non_sort(include).
   59is_non_sort(xor).
   60is_non_sort(P):- verbatum_functor(P).
   61is_non_sort(NoListF):- non_list_functor(NoListF).
   62
   63builtin_pred(initiates).
   64builtin_pred(terminates).
   65builtin_pred(releases).
   66builtin_pred(holds_at).
   67builtin_pred(happens).
   68builtin_pred(declipped).
   69builtin_pred(clipped).
   70builtin_pred(b).
   71builtin_pred(before).
   72builtin_pred(after).
   73builtin_pred(sort).
   74builtin_pred(initially).
   75
   76is_quantifier_type(thereExists,( & )):- use_some.
   77is_quantifier_type(forAll,all).
   78is_quantifier_type(thereExists,exists).
   79is_quantifier_type(X,Y):- atom(X), is_quantifier_type(_,X),Y=X.
   80
   81% used by ec_loader
   82
   83:- meta_predicate e_to_pl(1,+,+), e_to_pl(1,+,+).   84:- meta_predicate map_callables(2,*,*).   85:- meta_predicate in_space_cmt(0).   86:- meta_predicate process_e_stream(1,*).   87:- meta_predicate ec_on_read(1,*).   88:- meta_predicate e_io(1,*).   89:- meta_predicate upcased_functors(0).   90:- meta_predicate read_stream_until_true(*,*,1,*).   91:- meta_predicate process_e_stream_token(1,*,*).   92:- meta_predicate continue_process_e_stream_too(1,*,*,*).   93:- meta_predicate process_e_token_with_string(1,*,*).   94:- meta_predicate continue_process_e_stream(1,*,*,*).   95
   96:- thread_local(t_l:each_file_term/1).   97:- thread_local(t_l:block_comment_mode/1).   98:- thread_local(t_l:echo_mode/1).   99
  100%:- meta_predicate now_doing(1, ?).
  101%:- meta_predicate each_doing(1, ?).
  102%:- meta_predicate doing(1, *).
  103  
  104:- meta_predicate 
  105   with_e_sample_tests(1),
  106   raise_translation_event(1,*,*).  107
  108:- use_module(library(logicmoo_common)).
  109%:- use_module(library(logicmoo/filestreams)).
  110
  111:- export(e_reader_test/0).  112e_reader_test:- with_e_sample_tests(convert_e(user_output)).
  113:- export(e_reader_test/1).  114e_reader_test(Files):- with_abs_paths(convert_e(user_output),Files).
  115
  116:- export(e_reader_testf/0).  117e_reader_testf:- with_e_sample_tests(convert_e(outdir('.', pro))).
  118:- export(e_reader_testf/1).  119e_reader_testf(Files):- with_abs_paths(convert_e(outdir('.', pro)),Files).
  120
  121
  122
  123:- export(with_e_sample_tests/1).  124with_e_sample_tests(Out) :- 
  125  retractall(etmp:ec_option(load(_), _)),
  126%  call(Out, 'ectest/*.e'),  
  127%  call(Out, 'examples/AkmanEtAl2004/ZooWorld.e'),  
  128  %call(Out, 'ecnet/RTSpace.e'),
  129  %call(Out, 'ectest/ec_reader_test_ecnet.e'),
  130  %call(Out, 'ecnet/Kidnapping.e'),
  131  %call(Out, 'ecnet/SpeechAct.e'),
  132  % call(Out, 'ecnet/Diving.e'),
  133   %call(Out, 'examples/Mueller2006/Exercises/MixingPaints.e'),
  134   call(Out, ['*/*/*/*.e','*/*/*.e','*/*.e']),
  135  
  136%  call(Out, 'examples/Mueller2006/Chapter11/HungryCat.e'),
  137  !.
  138%:- initialization(e_reader_test, main).
  139
  140
  141% 
  142% :- meta_predicate ec_reader:must(0).
  143
  144raise_translation_event(Why,What,OutputName):- call(Why,translate(What,OutputName)).
  145
  146
  147dedupe_files(SL0,SL):- maplist(relative_file_name,SL0,SL1), list_to_set(SL1,SL2),maplist(absolute_file_name,SL2,SL),!.
  148  relative_file_name(A,S):-  prolog_canonical_source(A,L), file_name_on_path(L,S), atom(S), \+ name(S,[]), exists_file(S),!.
  149  relative_file_name(A,A).          
  150
  151exists_all_filenames(S0, SL, Options):- 
  152  findall(N, (relative_from(D), 
  153     absolute_file_name(S0, N, 
  154        [relative_to(D), file_type(txt), file_errors(fail), access(read), solutions(all)|Options])), SL0),
  155  dedupe_files(SL0,SL),!.
  156
  157:- export(resolve_local_files/2).  158resolve_local_files(S0,SL):- is_list(S0), !, maplist(resolve_local_files,S0,SS), append(SS,SL).
  159resolve_local_files(S0,SL):- atom(S0), exists_file(S0), !, SL = [S0].
  160resolve_local_files(S0,SL):- atom(S0), expand_file_name(S0,SL), SL = [E|_], exists_file(E), !.
  161resolve_local_files(S0,SL):- exists_all_filenames(S0,SL, [expand(false)]), SL \= [].
  162resolve_local_files(S0,SL):- exists_all_filenames(S0,SL, [expand(true)]), SL \= [].
  163resolve_local_files(S0,SS):- atom(S0), file_base_name(S0,S1), S0\==S1, resolve_local_files(S1,SS).
  164
  165relative_from(F):- nb_current('$ec_input_file', F).
  166relative_from(D):- working_directory(D,D).
  167relative_from(F):- stream_property(_,file_name(F)).
  168relative_from(D):- expand_file_search_path(library(ec_planner),D),exists_directory(D).
  169
  170/*
  171resolve_file(S0,SS):- atom(S0), exists_file(S0), !, SS=S0. 
  172resolve_file(S0,SS):- absolute_file_name(S0, SS, [expand(true), file_errors(fail), access(read)]), !.
  173resolve_file(S0,SS):- relative_from(F), absolute_file_name(S0, SS, [relative_to(F),file_errors(fail),access(read)]), !.
  174resolve_file(S0,SS):- atom(S0), file_base_name(S0,S1), S0\==S1, resolve_file(S1,SS).
  175*/
  176
  177:- export(needs_resolve_local_files/2).  178needs_resolve_local_files(F, L):- \+ is_stream(F), \+ is_filename(F),
  179  resolve_local_files(F, L), !,  L \= [], L \= [F].
  180
  181chop_e(InputNameE,InputName):- atom_concat(InputName,'.e',InputNameE),!.
  182chop_e(InputName,InputName).
  183
  184:- export(calc_where_to/3).  185calc_where_to(outdir(Dir, Ext), InputNameE, OutputFile):- 
  186    chop_e(InputNameE,InputName),
  187    atomic_list_concat([InputName, '.', Ext], OutputName),
  188    make_directory_path(Dir),
  189    absolute_file_name(OutputName, OutputFile, [relative_to(Dir)]).
  190
  191:- set_ec_option(overwrite_translated_files,false).  192
  193:- export(should_update/1).  194should_update(OutputName):- \+ exists_file(OutputName), !.
  195should_update(_):- etmp:ec_option(overwrite_translated_files,always),!.
  196
  197:- export(include_e/1).  198include_e(F):- e_to_pl(do_convert_e, current_output, F).
  199
  200
  201:- export(convert_e/1).
  202convert_e(F):- convert_e(outdir('.', pro), F).
  203:- export(convert_e/2).
  204convert_e(Out, F):- e_to_pl(do_convert_e, Out, F).
  205
  206:- export(is_filename/1).  207is_filename(F):- atom(F), \+ is_stream(F),
  208  (exists_file(F);is_absolute_file_name(F)).
  209
  210%e_to_pl(Why, Out, F):- dmsg(e_to_pl(Why, Out, F)), fail.
  211
  212e_to_pl(Why, Out, F):- compound(Out), Out=outdir(Dir), !, e_to_pl(Why, outdir(Dir, pro), F).
  213e_to_pl(Why, Out, F):- nonvar(F), \+ is_stream(F), \+ is_filename(F), needs_resolve_local_files(F, L), !, maplist(e_to_pl(Why, Out), L).  
  214
  215% wildcard input file  "./foo*.e"
  216e_to_pl(Why, Out, F):- atom(F), \+ is_stream(F), \+ is_filename(F), 
  217   expand_file_name(F, L), L\==[], [F]\==L, !, maplist(e_to_pl(Why, Out), L).
  218
  219% wildcard input file  logical(./foo*.e).
  220e_to_pl(Why, Out, F):-  \+ is_stream(F), \+ is_filename(F),
  221   findall(N, absolute_file_name(F, N, [file_type(txt), file_errors(fail), expand(false), solutions(all)]), L), 
  222   L\=[F], !, maplist(e_to_pl(Why, Out), L).
  223
  224% Out is a misdirected stream
  225e_to_pl(Why, Outs, Ins):- 
  226   atomic(Outs), is_stream(Outs),
  227   assertion(stream_property(Outs, output)), 
  228   \+ current_output(Outs), !,
  229   with_output_to(Outs, 
  230    e_to_pl(current_output, Why, Ins)),!.
  231
  232% Out is like a wildcard stream (but we have a real filename)
  233e_to_pl(Why, outdir(Dir, Ext), F):- is_filename(F), !, 
  234   calc_where_to(outdir(Dir, Ext), F, OutputName),
  235   e_to_pl(Why, OutputName, F).
  236
  237% Out is like a wildcard stream (calc a real filename)
  238e_to_pl(Why, outdir(Dir, Ext), Ins):- must(is_stream(Ins)), !, 
  239   must(stream_property(Ins, file(InputName))),
  240   calc_where_to(outdir(Dir, Ext), InputName, OutputName),
  241   e_to_pl(Why, OutputName, Ins).
  242
  243% Out is a filename not neding update
  244e_to_pl(Why, OutputName, _Ins):- is_filename(OutputName), 
  245   \+ should_update(OutputName),
  246   raise_translation_event(Why,skipped,OutputName),
  247   raise_translation_event(Why,ready,OutputName), !.
  248
  249e_to_pl(Why, Out, F):- is_filename(F), !, 
  250  absolute_file_name(F,AF),
  251    locally(b_setval('$ec_input_file',AF),
  252      setup_call_cleanup(
  253        open(F, read, Ins),    
  254         e_to_pl(Why, Out, Ins),
  255        close(Ins))),!.
  256
  257% Out is a filename not currently loadable 
  258e_to_pl(Why, OutputName, Ins):-  \+ is_stream(OutputName), !,
  259   assertion(is_stream(Ins)), assertion(stream_property(Ins, input)),
  260   must(should_update(OutputName)),
  261   raise_translation_event(Why,unskipped,OutputName),
  262   setup_call_cleanup(
  263     open(OutputName, write, Outs),
  264     with_output_to(Outs, 
  265       (raise_translation_event(Why,begining,OutputName),
  266         nb_setval('$ec_output_stream',Outs),
  267         format(Outs,'~N~q.~n',[:- expects_dialect(ecalc)]),
  268         e_to_pl(Why, current_output, Ins),
  269          raise_translation_event(Why,ending,OutputName))),
  270     (nb_setval('$ec_output_stream',[]),close(Outs))),
  271   raise_translation_event(Why,ready,OutputName).
  272
  273e_to_pl(Why, Out, Ins):- 
  274      assertion(current_output(Out)),       
  275      e_io(Why, Ins).
  276
  277:- nb_setval(ec_input_file,[]).  278        
  279%e_io(Why, Ins):- dmsg(e_io(Why, Ins)), fail.
  280e_io(Why, Ins):-  
  281  repeat, 
  282  locally(b_setval('$ec_input_stream',Ins),once(process_e_stream(Why, Ins))), 
  283  notrace(at_end_of_stream(Ins)), !.
  284  
  285
  286
  287removed_one_ws(S):-
  288  peek_code(S, W), char_type(W, white), get_code(S, W), echo_format('~s', [[W]]).
  289
  290removed_n_chars(_S, N):- N<1, !.
  291removed_n_chars(S, N):- get_code(S, _), Nm1 is N-1, removed_n_chars(S, Nm1).
  292
  293trim_off_whitepace(S):- repeat, \+ removed_one_ws(S).
  294
  295
  296
  297read_n_save_vars(Type, Codes):- read_some_vars(Codes, Vars),
  298  asserta(etmp:temp_varnames(Type, Vars)).
  299
  300read_some_vars(Codes, Vars):-
  301 maybe_o_s_l,
  302  must(e_read3(Codes, VarNames)), !, 
  303  varnames_as_list(VarNames, Vars).
  304
  305varnames_as_list({A},[A]):- atom(A),!.
  306varnames_as_list({A,B},Vars):- !,varnames_as_list({A},Vars1),varnames_as_list({B},Vars2),append(Vars1,Vars2,Vars).
  307varnames_as_list(VarNames,Vars):- assertion(is_list(VarNames)), !, VarNames=Vars.
  308
  309upcased_functors(G):- 
  310 notrace((allow_variable_name_as_functor = N, 
  311   current_prolog_flag(N, Was))), !, 
  312   setup_call_cleanup(notrace(set_prolog_flag(N, true)), 
  313      G, 
  314      notrace(set_prolog_flag(N, Was))).
 process_e_stream(Why, ?S) is det
Process file stream input
  321process_stream_comment(S) :- (peek_string(S, 3, W);peek_string(S, 2, W);peek_string(S, 1, W)), clause(process_stream_peeked213(S, W),Body),!,once(Body).
  322process_stream_peeked213(S, "#!"):- !, read_line_to_string_echo(S, _).
  323process_stream_peeked213(S, ";:-"):- !, 
  324   ( ( nb_current(last_e_string, axiom)) -> (echo_format('~N~n~n',[]), mention_s_l) ; true),
  325   get_char(S, ';'), read_term(S, Term, []),!, 
  326      portray_clause(Term),nl,
  327   nb_setval(last_e_string, axiom).
  328
  329process_stream_peeked213(S,  ";"):- !, 
  330   ( ( nb_current(last_e_string, axiom)) -> (echo_format('~N~n~n',[]), mention_s_l) ; true),
  331   echo_format('%'), read_line_to_string_echo(S, _),!, 
  332   nb_setval(last_e_string, cmt).
  333process_stream_peeked213(S, "["):- !, 
  334  locally(b_setval(e_echo, nil), read_stream_until(S, [], `]`, Codes)),
  335   ( (\+ nb_current(last_e_string, cmt), \+ nb_current(last_e_string, vars) ) -> (echo_format('~N~n~n',[]), mention_s_l) ; true),
  336   echo_format('% ~s~N',[Codes]),
  337   read_n_save_vars(universal, Codes),
  338   nb_setval(last_e_string, vars).
  339process_stream_peeked213(S, "{"):- mention_s_l, echo_format('% '), !, read_stream_until(S, [], `}`, Codes), read_n_save_vars(existential, Codes).
  340
  341
  342%process_e_stream(Why, S):- assertion(stream_property(S, input)).
  343process_e_stream(Why, S):- notrace(at_end_of_stream(S)), !, mention_s_l, call(Why, end_of_file).
  344process_e_stream(_, S) :- removed_one_ws(S), !.
  345process_e_stream(_, S):- process_stream_comment(S), !.
  346
  347process_e_stream(Why, S):-   
  348   OR = [to_lower('.'), to_lower('('), end_of_line, to_lower('='),to_lower('>'), space, to_lower(':')], 
  349   locally(b_setval(e_echo, nil),
  350         read_stream_until_true(S, [], char_type_inverse(Was, or(OR)), Text)), 
  351   unpad_codes(Text, Codes), 
  352   maybe_o_s_l,
  353   ttyflush, 
  354   must(continue_process_e_stream(Why, S, Codes, Was)), !.
  355process_e_stream(Why, S):- read_line_to_string(S, Comment), echo_format('~N%RROOR: ~w: ~s~n', [Why, Comment]), break.
  356
  357
  358% continue_process_e_stream(Why, _S, [], space):- !.
  359continue_process_e_stream(_Why, _S, [], _):- !.
  360continue_process_e_stream(_Why, _S, [], end_of_line):- !.
  361continue_process_e_stream(Why, S, NextCodes, CanBe ):- ttyflush,
  362  continue_process_e_stream_too(Why, S, NextCodes, CanBe ),!.
  363
  364continue_process_e_stream_too(Why, _S, Codes, to_lower(':')):- 
  365  append(Delta, [_], Codes), 
  366  text_to_string(Delta,DeltaS),
  367  normalize_space(atom(Term),DeltaS),
  368  nb_setval(last_e_string, delta),
  369  echo_format('~N~n'),maybe_mention_s_l(0), echo_format('% ~s ', [Codes]),
  370  ec_on_read(Why, directive(Term)),!.
  371continue_process_e_stream_too(Why, S, Codes, space):- last(Codes, Last), 
  372   once([Last]=`!`;char_type(Last, alpha)), !, 
  373   trim_off_whitepace(S), !, 
  374   atom_codes(Token, Codes),  
  375   nb_setval(last_e_string, kw),
  376   echo_format('~N~n'),maybe_mention_s_l(0), echo_format('% ~s ', [Codes]),
  377   process_e_stream_token(Why, Token, S), ttyflush, !.
  378continue_process_e_stream_too(Why, S, NextCodes, _CanBe ):-  !, 
  379  ( \+ nb_current(last_e_string, vars) -> (echo_format('~N~n~n',[]), mention_s_l) ; true),
  380   maybe_mention_s_l(2), echo_format('% ~s', [NextCodes]),
  381   last(NextCodes, Last), cont_one_e_compound(S, NextCodes, Last, Term), ec_on_read(Why, Term).
  382
  383unpad_codes(Text, Codes):- text_to_string(Text, String), 
  384   normalize_space(codes(Codes0), String),
  385   trim_eol_comment(Codes0,Codes).
  386
  387trim_eol_comment(Codes,Left):- append(Left,[59|_Cmt], Codes),!.
  388trim_eol_comment(Codes,Codes).
  389  
  390  
  391e_from_atom(String, Term):- e_read1(String, Term, _).   
  392
  393set_e_ops(M):- 
  394   op(1150, yfx, M:'->'),
  395   op(1150, xfx, M:'->'),
  396   op(1150, xfy, M:'->'),
  397   % op(1125, xfy, M:'thereExists'), 
  398   op(1100, xfy, M:'<->'),
  399   op(1075, xfx, M:'thereExists'),
  400   op(1050, xfy, M:'|'),
  401   op(950, xfy, M:'&'),
  402   op(900, fx, M:'!'),
  403   op(400, yfx, M:'%'),
  404   op(1,fx,(M:($))).
  405
  406e_read3(String, Term):- 
  407   M = ecread,
  408   forall(current_op(_,fx,OP),
  409    op(0,fx,(M:OP))),    
  410    set_e_ops(M),
  411       upcased_functors(notrace(((catch(
  412        (read_term_from_atom(String, Term, 
  413            [var_prefix(true),variable_names(Vars), module(M)])), _, fail))))), !, 
  414  maplist(ignore, Vars).
  415
  416:- dynamic(etmp:temp_varnames/2).
  417:- dynamic(etmp:ec_option/2).  418
  419
  420insert_vars(Term, [], Term, []).
  421insert_vars(Term0, [V|LL], Term, [V=VV|Has]):-
  422  insert1_var(Term0, V, VV, Term1), 
  423  insert_vars(Term1, LL, Term, Has).
  424
  425
  426insert1_var(Term0, V, VV, Term1):- 
  427  debug_var(V, VV), 
  428  subst(Term0, V, VV, Term1).
  429
  430
  431map_callables(_, Term0, Term):- \+ callable(Term0), !, Term0=Term.
  432map_callables(_, Term0, Term):- []== Term0, !, Term =[].
  433map_callables(Call, Term0, Term):- atom(Term0), !, call(Call, Term0, Term).
  434map_callables(_Call, Term0, Term):- \+ compound(Term0), !, Term0=Term.
  435map_callables(Call, Compound=Value, Term):- fail, compound(Compound), 
  436  append_term(Compound, Value, Term0), map_callables(Call, Term0, Term).
  437map_callables(_, '$VAR'(HT), '$VAR'(HT)):-!.
  438map_callables(Call, [H|T], [HTerm|TTerm]):- !, map_callables(Call, H, HTerm), map_callables(Call, T, TTerm), !.
  439map_callables(Call, '$'(F, A), '$'(FF, AA)):- A==[], [] = AA, !, call(Call, F, FF).
  440%map_callables(Call, '$'(F, [A]), '$'(F, [AA])):- \+ special_directive(F), !, map_callables(Call, A, AA).
  441map_callables(Call, '$'(F, A), '$'(FF, AA)) :- call(Call, F, FF), maplist(map_callables(Call), A, AA), !.
  442map_callables(Call, HT, HTTerm):- !, 
  443 compound_name_arguments(HT, F, L), 
  444 map_callables(Call, '$'(F, L), '$'(FF, LL)), 
  445 compound_name_arguments(HTTerm, FF, LL).
  446
  447
  448:- export(fix_predname/2).  449
  450fix_predname('!', 'not').
  451fix_predname('~', 'not').
  452
  453fix_predname(';', ';').
  454fix_predname('\\/', ';').
  455fix_predname('v', ';').
  456fix_predname('or', ';').
  457fix_predname('|', ';').
  458fix_predname('xor', 'xor').
  459
  460fix_predname(',', ',').
  461fix_predname('^', ',').
  462fix_predname('and', ',').
  463fix_predname('&', ',').
  464fix_predname('/\\', ',').
  465
  466fix_predname('equiv','<->').
  467fix_predname('iff', '<->').
  468fix_predname('<->', '<->').
  469fix_predname('<=>', '<->').
  470
  471fix_predname('->', '->').
  472fix_predname('implies', '->').
  473fix_predname('=>', '->').
  474fix_predname('if', '->').
  475
  476fix_predname(holds_at, holds_at).
  477fix_predname(holdsat, holds_at).
  478
  479fix_predname(Happens, Happens):- builtin_pred(Happens).
  480
  481fix_predname(F, New):- downcase_atom(F, DC), F\==DC, !, fix_predname(DC, New).
  482
  483
  484
  485

  486my_unCamelcase(X, Y):- atom(X), fix_predname(X, Y), !.
  487my_unCamelcase(X, Y):- atom(X), upcase_atom(X, X), !, downcase_atom(X, Y).
  488my_unCamelcase(X, Y):- unCamelcase(X, Y), !.
  489
  490:- export(e_to_ec/2).  491e_to_ec(C, C):- \+ callable(C), !.
  492e_to_ec('$VAR'(HT), '$VAR'(HT)):-!.
  493e_to_ec(X, Y):- \+ compound(X), !, must(my_unCamelcase(X, Y)).
  494e_to_ec(X, Y):- compound_name_arity(X, F, 0), !, my_unCamelcase(F, FF), compound_name_arity(Y, FF, 0).
  495e_to_ec(not(Term),not(O)):- !, e_to_ec(Term, O).
  496e_to_ec(Prop,O):- 
  497  Prop =.. [ThereExists,NotVars,Term0],
  498  is_quantifier_type(ThereExists,_Exists),
  499  conjuncts_to_list(NotVars,NotVarsL), select(NotVs,NotVarsL,Rest),compound(NotVs),not(Vars)=NotVs,
  500  is_list(Vars),%forall(member(E,Vars),ground(E)),!,
  501  (Rest==[]->Term1= Term0 ; list_to_conjuncts(Rest,NotVarsRest),conjoin(NotVarsRest,Term0,Term1)), 
  502  QProp =.. [ThereExists,Vars,Term1], 
  503  e_to_ec(not(QProp),O).
  504e_to_ec(Prop,O):- 
  505  Prop =.. [ThereExists,Vars,Term0], 
  506  is_quantifier_type(ThereExists,Exists),
  507  is_list(Vars), forall(member(E,Vars),ground(E)),
  508  QProp =.. [Exists,Vars,Term0],
  509  insert_vars(QProp, Vars, Term, _Has),
  510  e_to_ec(Term,O),!.
  511
  512%e_to_ec(X, Y):- e_to_ax(X, Y),X\=@=Y,!,e_to_ec(X, Y).
  513%e_to_ec(neg(C),O):-e_to_ec(holds_at(neg(N),V),O):- compound(C),holds_at(N,V)=C,
  514%e_to_ec(neg(holds_at(N,V)),O):-e_to_ec((holds_at(neg(N),V)),O).
  515e_to_ec(t(X, [Y]), O):- nonvar(Y), !, e_to_ec(t(X, Y), O).
  516e_to_ec(load(X), load(X)):-!.
  517e_to_ec(include(X), include(X)):-!.
  518e_to_ec(option([N, V]), O):- !, e_to_ec(option(N, V), O).
  519e_to_ec(range([N, V, H]), O):- !, e_to_ec(range(N, V, H), O).
  520
  521e_to_ec(t(X, Y), O):- atom(X), is_non_sort(X), !, SS=..[X, Y], e_to_ec(SS, O).
  522e_to_ec(t(X, Y), O):- atom(X), is_list(Y), is_non_sort(X), SS=..[X|Y], e_to_ec(SS, O).
  523e_to_ec(t(X, Y), O):- atom(X), is_list(Y), SS=..[X, Y], e_to_ec(SS, O).
  524e_to_ec(sort(col([S1, S2])), O):- !, e_to_ec(subsort(S1, S2), O).
  525e_to_ec(function(F, [M]), O):- e_to_ec(function(F, M), O).
  526%e_to_ec(Compound=Value, equals(Compound,Value)).
  527/*
  528e_to_ec(Term1, Term):- 
  529%  map_callables(my_unCamelcase, Term1, HTTermO),
  530%  Term1\=@=HTTermO,!,
  531%  e_to_ec(HTTermO, Term). 
  532*/

  533e_to_ec(HT, HTTermO):- !, 
  534 compound_name_arguments(HT, F, L), 
  535 maplist(e_to_ec,L,LL),
  536 compound_name_arguments(HTTerm, F, LL),
  537 map_callables(my_unCamelcase, HTTerm, HTTermO).
  538
  539
  540vars_verbatum(Term):- \+ compound_gt(Term, 0), !.
  541vars_verbatum(Term):- compound_name_arity(Term, F, A), (verbatum_functor(F);verbatum_functor(F/A)), !.
  542
  543add_ec_vars(Term0, Term, Vs):- vars_verbatum(Term0), !, Term0=Term, Vs=[].
  544add_ec_vars(Term0, Term, Vs):- 
       
  545  get_vars(universal, UniVars),
  546  get_vars(existential,ExtVars),
  547  insert_vars(Term0, UniVars, Term1, VsA),!,  
  548  add_ext_vars(VsA, ExtVars, Term1, Term, Vs), !.
  549
  550add_ext_vars(Vs, [], Term, Term, Vs):- !.
  551add_ext_vars(VsA, LLS, Term0, Term, Vs):-  use_some,
  552  insert_vars((some(LLS), Term0), LLS, Term, VsB), !,
  553  append(VsA,VsB,Vs),!.
  554add_ext_vars(VsA, LLS, Term0, Term, Vs):-  
  555  insert_vars(exists(LLS, Term0), LLS, Term, VsB), !,
  556  append(VsA,VsB,Vs),!.
  557
  558use_some :- fail.
  559
  560get_vars(Type,LLS):- findall(E, (etmp:temp_varnames(Type,L), member(E, L)), LL), sort(LL, LLS),!.
  561
  562
  563e_read1(String, Term, Vs):- 
  564   e_read2(String, Term0), !, 
  565   add_ec_vars(Term0, Term1, Vs), !,
  566   retractall(etmp:temp_varnames(_,_)),
  567   e_to_ec(Term1, Term), !.
  568
  569if_string_replace(T, B, A, NewT):-   
  570   atomics_to_string(List, B, T), List=[_,_|_], !,
  571   atomics_to_string(List, A, NewT). 
  572
  573
  574e_read2(Txt, Term):- \+ string(Txt), text_to_string(Txt, T),!, e_read2(T, Term).
  575e_read2(T, Term):- if_string_replace(T, '!=', (\=), NewT), !, e_read2(NewT, Term).
  576e_read2(T, Term):- if_string_replace(T, '%', (/), NewT), !, e_read2(NewT, Term).
  577e_read2(T, Term):- use_some,
  578  if_string_replace(T,  '{', ' some( ', T1), 
  579  if_string_replace(T1, '}', ' ) & ', NewT), 
  580  e_read2(NewT, Term).
  581e_read2(T, Term):- 
  582  if_string_replace(T, '{', ' [ ', T1), 
  583  if_string_replace(T1, '}', ' ] thereExists ', NewT),    
  584  e_read2(NewT, Term).
  585%e_read2(T, Term):- if_string_replace(T, '[', ' forAll( ', NewT), !, e_read2(NewT, Term).
  586%e_read2(T, Term):- if_string_replace(T, ']', ') quantz ', NewT), !, e_read2(NewT, Term).
  587e_read2(T, Term):- e_read3(T, Term), !.
  588e_read2(T, Term):- 
  589   must(e_read3(T, Term)), !.
  590   
  591   
  592
  593cleanout(Orig, B, E, MidChunk, RealRemainder):-
  594 text_to_string(Orig, Str), 
  595 AfterFirstB=[_|_],
  596 atomic_list_concat([BeforeB|AfterFirstB], B, Str), 
  597         atomics_to_string(  AfterFirstB, B, AfterB),
  598 Remainder=[_|_],
  599 atomic_list_concat([Mid|Remainder], E, AfterB),
  600 atomics_to_string( Remainder, E, AfterE),
  601 atomics_to_string( [BeforeB,' ', AfterE], RealRemainder),
  602 atomics_to_string( [B, Mid, E], MidChunk).
  603
  604
  605read_one_e_compound(S, Term):- 
  606   read_stream_until_true(S, [], char_type_inverse(_Was, or([to_lower('.'), end_of_line])), Text), 
  607   unpad_codes(Text, Codes), last(Codes, Last), 
  608   cont_one_e_compound(S, Codes, Last, Term).
  609
  610cont_one_e_compound(_S, Text, Last, Term):- char_type(Last, to_lower('.')),
  611   unpad_codes(Text, Codes), e_from_atom(Codes, Term), nb_setval(last_e_string, axiom).
  612
  613cont_one_e_compound(_S, Text, Last, Term):- char_type(Last, to_lower(')')),
  614   \+ (member(T, `>&|`), member(T, Text)),
  615   unpad_codes(Text, Codes), e_from_atom(Codes, Term), nb_setval(last_e_string, axiom).
  616
  617cont_one_e_compound(S, InCodes, WasLast, Term):- process_stream_comment(S), !, cont_one_e_compound(S, InCodes, WasLast, Term).
  618cont_one_e_compound(S, InCodes, WasLast, Term):- 
  619   (WasLast\==40-> echo_format('% ') ; true), 
  620   read_stream_until_true(S, InCodes, char_type_inverse(_Was, or([to_lower('.'), end_of_line])), Text), 
  621   unpad_codes(Text, Codes), last(Codes, Last), 
  622   cont_one_e_compound(S, Codes, Last, Term).
  623
  624
  625%ec_on_read(S):- ec_on_read(on_load_ele, S).
  626
  627:- meta_predicate ec_on_each_read(1,*,*).  628
  629ec_on_read(Why, EOF):- EOF == end_of_file, !,  must(call(Why, EOF)).
  630ec_on_read(Why, SL):- e_to_ec(SL, SO) -> SL\=@=SO, !, ec_on_read(Why, SO).
  631ec_on_read(Why, Cmp):- compound_gt(Cmp, 0), 
  632  Cmp =.. [NonlistF, List], is_list(List), non_list_functor(NonlistF),!, 
  633  maplist(ec_on_each_read(Why,NonlistF), List).
  634ec_on_read(Why, S):- must(glean_data(Why, S)), must(call(Why, S)).
  635
  636
  637:- use_module(library(logicmoo/misc_terms)).  638
  639ec_on_each_read(Why, NonlistF, E):- univ_safe(Cmp , [NonlistF, E]), ec_on_read(Why, Cmp).
  640
  641%must(G):- tracing, !, notrace(G).
  642%must(G):- call(G)->true;(trace,ignore(rtrace(G)),break).
  643
  644on_convert_ele(translate(Event, Outfile)):- !, must((mention_s_l, echo_format('~N% translate: ~w  File: ~w ~n',[Event, Outfile]))).
  645on_convert_ele(include(S0)):- resolve_local_files(S0,SS), !, maplist(include_e, SS), !.
  646%on_convert_ele(load(S0)):- resolve_local_files(S0,SS), !, maplist(load_e, SS), !.  
  647on_convert_ele(end_of_file).
  648on_convert_ele(SS):- must(echo_format('~N')), must(pprint_ecp(e,SS)).
  649
  650
  651do_convert_e(SS):- on_convert_ele(SS).
  652
  653
  654glean_data(Why, SL):- \+ compound(SL), !, dmsg(warn(glean_data(Why, SL))).
  655glean_data(Why, subsort(S1, S2)):- !, glean_data(Why, sort(S1)), glean_data(Why, sort(S2)), assert_gleaned(Why, subsort(S1, S2)).
  656glean_data(Why, sort(S)):- !, assert_gleaned(Why, sort(S)).
  657glean_data(Why, isa(E, S)):- !, assert_gleaned(Why, isa(E, S)).
  658glean_data(Why, SL):- SL=..[S, L], 
  659  \+ is_non_sort(S), is_list(L), !, 
  660  glean_data(Why, sort(S)), 
  661  maplist(glean_data(Why, hasInstance(S)), L).
  662glean_data(_, _).
  663
  664%assert_gleaned(Why, sort(S)):-  !, call(Why, gleaned(sort(S))).
  665assert_gleaned(_Why, SS):-  asserta_if_new(gleaned(SS)).
  666%assert_gleaned(Why, SS):-  call(Why, gleaned(SS)).
  667
  668glean_data(Why, hasInstance(S), E):- !, glean_data(Why, isa(E, S)).
  669
  670
  671
  672process_e_stream_token(Why, Atom, S):- atom_concat(New, '!', Atom), !, process_e_stream_token(Why, New, S).
  673process_e_stream_token(Why, Type, S):- normalize_space(atom(A), Type), A\==Type, !, process_e_stream_token(Why, A, S).
  674process_e_stream_token(Why, Text, S):- \+ atom(Text), !, text_to_string(Text, String), atom_string(Atom,String), process_e_stream_token(Why, Atom, S).
  675process_e_stream_token(Why, function, S):- !, read_stream_until(S, [], `:`, Text), read_line_to_string_echo(S, String), 
  676  append(TextL, [_], Text), 
  677  e_read1(TextL, Value, _), 
  678  token_stringsss(String, Type), 
  679   ec_on_read(Why, (function(Value, Type))).
  680
  681process_e_stream_token(Why, Type, S):- downcase_atom(Type, Event), (memberchk(Event, [fluent, predicate, event]);is_reified_sort(Event)), !, 
  682   read_one_e_compound(S, Value), ec_on_read(Why, t(Event, Value)).
  683
  684process_e_stream_token(Why, reified, S):- !, read_stream_until(S, [], ` `, Text), 
  685   text_to_string(Text, St), atom_concat('reified_', St, Type), !, process_e_stream_token(Why, Type, S).
  686
  687process_e_stream_token(Why, Type, S):- read_line_to_string_echo(S, String), process_e_token_with_string(Why, Type, String).
  688
  689process_e_token_with_string(Why, Type, String):- \+ is_non_sort(Type), 
  690 % \+ atom_contains(String,"("),
  691  atomics_to_string(VList, ',', String), VList \= [_], !, 
  692  maplist(process_e_token_with_string(Why, Type), VList).
  693process_e_token_with_string(_, _, ""):-!.
  694process_e_token_with_string(Why, Type, String):- token_stringsss(String, Out), ec_on_read(Why, t(Type, Out)).
  695
  696token_stringsss("", []):-!.
  697token_stringsss(T, Out) :- if_string_replace(T, '  ', ' ', NewT), !, token_stringsss(NewT, Out).
  698token_stringsss(T, Out) :- if_string_replace(T, ': ', ':', NewT), !, token_stringsss(NewT, Out).
  699token_stringsss(T, Out) :- if_string_replace(T, ' :', ':', NewT), !, token_stringsss(NewT, Out).
  700token_stringsss(String, Out):- normalize_space(string(S), String), S\==String, !, token_stringsss(S, Out).
  701token_stringsss(String, VVList):- atomics_to_string(VList, ',', String), VList \= [_], remove_blanks_col(VList, VVList), !.
  702token_stringsss(String, col(VVList)):- atomics_to_string(VList, ':', String), VList \= [_], remove_blanks(VList, VVList), !.
  703token_stringsss(String, VVList):- atomics_to_string(VList, ' ', String), remove_blanks(VList, VVList), !.
  704
  705remove_blanks_col(I, O):- remove_blanks(I, M),maplist(token_cols, M, O).
  706
  707token_cols(String, col(VVList)):- atomics_to_string(VList, ':', String), VList \= [_], remove_blanks(VList, VVList), !.
  708token_cols(String,String).
  709
  710remove_blanks([], []).
  711remove_blanks([''|I], O):- !, remove_blanks(I, O).
  712remove_blanks([E|I], O):- string(E), normalize_space(string(EE), E), E\==EE, !, remove_blanks([EE|I], O).
  713remove_blanks([E|I], O):- atom(E), normalize_space(atom(EE), E), E\==EE, !, remove_blanks([EE|I], O).
  714remove_blanks([E|I], O):- to_atomic_value(E, EE), E\==EE, !, remove_blanks([EE|I], O).
  715remove_blanks([E|I], [E|O]):- remove_blanks(I, O).
  716
  717
  718to_atomic_value(A, N):- number(A), !, N=A.
  719to_atomic_value(A, N):- normalize_space(atom(S), A), S\==A, !, to_atomic_value(S, N).
  720to_atomic_value(A, N):- atom_number(A, N).
  721to_atomic_value(A, A).
  722
  723:- meta_predicate(read_stream_until(+,+,*,-)).  724read_stream_until(S, Buffer, [Until], Codes):- !, name(N, [Until]), char_code(N, UntilCode), !, 
  725 read_stream_until_true(S, Buffer, ==(UntilCode), Codes).
  726read_stream_until(S, Buffer, UntilCode, Codes):- integer(UntilCode), !, 
  727 read_stream_until_true(S, Buffer, ==(UntilCode), Codes).
  728read_stream_until(S, Buffer, Until, Codes):- atom(Until), atom_length(Until, 1), char_code(Until, UntilCode), !, 
  729 read_stream_until_true(S, Buffer, ==(UntilCode), Codes).
  730read_stream_until(S, Buffer, Until, Codes):- read_stream_until_true(S, Buffer, Until, Codes).
  731
  732char_type_inverse(Type, or(TypeList), Code):- !, member(E, TypeList), char_type_inverse(Type, E, Code).
  733char_type_inverse(Type, [Spec], Code):- !, char_type_inverse(Type, Spec, Code).
  734char_type_inverse(Type, [Spec|List], Code):- !, char_type_inverse(_, Spec, Code), char_type_inverse(Type, List, Code).
  735char_type_inverse(Type, Spec, Code):- char_type(Code, Spec), Type=Spec.
  736
  737read_stream_until_true(S, Buffer, Pred, Buffer):- at_end_of_stream(S), !, ignore(call(Pred, 10)).
  738read_stream_until_true(S, Buffer, Pred, Codes):- get_code(S, Char), 
  739  (nb_current(e_echo,nil) -> true; put_out(Char)),
  740  (call(Pred, Char) -> notrace(append(Buffer, [Char], Codes)) ; 
  741  (notrace(append(Buffer, [Char], NextBuffer)), read_stream_until_true(S, NextBuffer, Pred, Codes))).
  742
  743
  744/*
  745process_e_stream(Why, S):- must((read_term(S, T, [variable_names(Vs)]), put_variable_names( Vs))), 
  746  call(b_setval, '$variable_names', Vs), b_setval('$term', T), 
  747  (t_l:echo_mode(skip(items)) -> true ; write_stream_item(user_error, T)), !, 
  748  ttyflush(user_error), 
  749  must(visit_script_term(T)), !, 
  750  echo_format('~N', []), !.
  751
  752write_stream_item(Out, T):- 
  753  ttyflush, 
  754  format(Out, '~N~n', []), 
  755  must(with_output_to(Out, portray_clause_w_vars(T))), 
  756  format(Out, '~N~n', []), !, ttyflush(Out).
  757
  758
  759*/
  760   
  761
  762
  763till_eof(In) :-
  764        repeat, 
  765            (   at_end_of_stream(In)
  766            ->  !
  767            ;   (read_pending_codes(In, Chars, []), 
  768                (t_l:echo_mode(echo_file) ->
  769                  echo_format('~s', [Chars]);
  770                  true), 
  771                fail)
  772            ).
  773
  774
  775:- fixup_exports.