Skip to content

Commit

Permalink
Merge pull request #101 from royward/main
Browse files Browse the repository at this point in the history
Fixes for non tty input
  • Loading branch information
TeamSPoon authored Aug 24, 2024
2 parents 0c9bb6f + fe96b80 commit 94bb95d
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 22 deletions.
8 changes: 0 additions & 8 deletions src/canary/metta_interp.pl
Original file line number Diff line number Diff line change
Expand Up @@ -55,8 +55,6 @@
:- set_prolog_flag(encoding, utf8).
:- nb_setval(cmt_override,lse('; ',' !(" ',' ") ')).
:- ensure_loaded(swi_support).
%:- set_prolog_flag(history, 10).
%:- set_prolog_flag(save_history, true).
:- set_prolog_flag(backtrace,true).
:- set_prolog_flag(backtrace_depth,100).
:- set_prolog_flag(backtrace_goal_dept,100).
Expand Down Expand Up @@ -279,9 +277,6 @@
:- nb_setval(repl_mode, '+').

%:- set_stream(user_input,tty(true)).
%:- if(exists_source(library(readline))).
%:- use_module(library(readline)).
%:- endif.
%:- use_module(library(editline)).
:- set_prolog_flag(encoding,iso_latin_1).
:- set_prolog_flag(encoding,utf8).
Expand Down Expand Up @@ -1680,8 +1675,6 @@
nts,
%install_ontology,
metta_final,
%nop(load_history),
%set_prolog_flag(history, 3),
% ensure_corelib_types,
set_output_stream,
if_t(is_compiled,update_changed_files),
Expand Down Expand Up @@ -1793,7 +1786,6 @@
:- ensure_loaded(library(flybase_main)).
:- ensure_loaded(metta_server).
:- initialization(update_changed_files,restore).
%:- set_prolog_flag(history, 3).

nts:- !.
nts:- redefine_system_predicate(system:notrace/1),
Expand Down
24 changes: 10 additions & 14 deletions src/canary/metta_repl.pl
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,8 @@
check_file_exists_for_append(HistoryFile) :- write("Error opening history file: "),writeln(HistoryFile),halt(1).

save_history :-
history_file_location(HistoryFile),
el_write_history(user_input,HistoryFile).
current_input(Input),
(((stream_property(Input, tty(true)))) -> ((history_file_location(HistoryFile),el_write_history(Input,HistoryFile))) ; true).

load_and_trim_history:-
notrace((
Expand Down Expand Up @@ -159,13 +159,12 @@
repl_read(O2):- clause(t_l:s_reader_info(O2),_,Ref),erase(Ref).
repl_read(Expr) :- repeat,
remove_pending_buffer_codes(_,Was),text_to_string(Was,Str),
%write_metta_prompt,
repl_read(Str, Expr),
% once(((symbol(Expr1),symbol_concat('@',_,Expr1), \+ atom_contains(Expr1,"="), repl_read(Expr2)) -> Expr=[Expr1,Expr2] ; Expr1 = Expr)),
% this cutrs the repeat/0
((peek_pending_codes(_,Peek),Peek==[])->!;true).

add_history_string(Str):- notrace(ignore(el_add_history(user_input,Str))),!.
add_history_string(Str):- current_input(Input),(((stream_property(Input, tty(true)))) -> ((notrace(ignore(el_add_history(Input,Str))))) ; true),!.

add_history_src(Exec):- notrace(ignore((Exec\=[],with_output_to(string(H),with_indents(false,write_src(Exec))),add_history_string(H)))).

Expand Down Expand Up @@ -199,8 +198,6 @@
is_interactive0(From):- From = true,!.


%:- set_prolog_flag(history, 3).

inside_assert(Var,Var):- \+ compound(Var),!.
inside_assert([H,IA,_],IA):- symbol(H),symbol_concat('assert',_,H),!.
inside_assert(Conz,Conz):- is_conz(Conz),!.
Expand Down Expand Up @@ -376,7 +373,7 @@


get_single_char_key(O):- get_single_char(C),get_single_char_key(C,O).
get_single_char_key(27,esc(A,[27|O])):- !,read_pending_codes(user_input,O,[]),name(A,O).
get_single_char_key(27,esc(A,[27|O])):- !,current_input(Input),read_pending_codes(Input,O,[]),name(A,O).
get_single_char_key(C,A):- name(A,[C]).

forall_interactive(file(_),false,Complete,Goal,After):- !, Goal, (Complete==true -> ( After,!) ; ( \+ After )).
Expand Down Expand Up @@ -540,23 +537,22 @@

install_readline(Input):- is_installed_readline_editline(Input),!.
%install_readline(_):- is_compatio,!.
install_readline(Input):-
install_readline(Input):- stream_property(Input,tty(true)),
assert(is_installed_readline_editline(Input)),
install_readline_editline1,
%use_module(library(readline)),
use_module(library(editline)),
%nop(catch(load_history,_,true)),
ignore(el_unwrap(user_input)), % unwrap the prolog wrapper so we can use our own.
ignore(el_unwrap(Input)), % unwrap the prolog wrapper so we can use our own.
ignore(el_wrap_metta(Input)),
history_file_location(HistoryFile),
check_file_exists_for_append(HistoryFile),
el_read_history(user_input,HistoryFile),
el_read_history(Input,HistoryFile),
%add_history_string("!(load-flybase-full)"),
%add_history_string("!(pfb3)"),
%add_history_string("!(obo-alt-id $X BS:00063)"),
%add_history_string("!(and (total-rows $T TR$) (unique-values $T2 $Col $TR))"),
!.

%add_history_string("!(and (total-rows $T TR$) (unique-values $T2 $Col $TR))"),!.
install_readline(_NoTTY). % For non-tty(true) clients over SWISH/Http/Rest server

:- dynamic setup_done/0.
:- volatile setup_done/0.
Expand All @@ -582,7 +578,7 @@
% %catch(setup_readline, E2, print_message(warning, E2)),
% %catch(setup_history, E3, print_message(warning, E3)),
% catch(setup_colors, E4, print_message(warning, E4))),
% install_readline(user_input).
% install_readline(Input).


% Command descriptions
Expand Down

0 comments on commit 94bb95d

Please sign in to comment.