Skip to content

Commit

Permalink
fixed large file loading
Browse files Browse the repository at this point in the history
  • Loading branch information
TeamSPoon committed Feb 17, 2024
1 parent 46ced2c commit 3789079
Show file tree
Hide file tree
Showing 2 changed files with 204 additions and 48 deletions.
244 changes: 200 additions & 44 deletions metta_vspace/pyswip/metta_interp.pl
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@
atom_concat('--',What,FWhat),
(member(FWhat,ArgV)-> true ;
(atom_concat(FWhat,'=true',FWhatEqTrue),member(FWhatEqTrue,ArgV))).



is_compiling:- current_prolog_flag(os_argv,ArgV),member(E,ArgV), (E==qcompile_mettalog;E==qsave_program),!.
Expand Down Expand Up @@ -58,7 +58,7 @@
is_compatio0:- is_testing,!,fail.
%is_compatio0:- is_html,!,fail.
is_compatio0:- !.
is_compatio0:- is_metta_flag('compatio').
is_compatio0:- is_flag0('compatio').

keep_output:- is_mettalog.
keep_output:- is_testing.
Expand All @@ -78,6 +78,7 @@


nullify_output:- keep_output,!.
nullify_output:- nullify_output_really.
nullify_output_really:- current_output(MFS), null_user_output(OUT), MFS==OUT, !.
nullify_output_really:- null_user_output(MFS), set_prolog_IO(user_input,MFS,user_error).

Expand Down Expand Up @@ -535,6 +536,9 @@
cmdline_load_metta(Phase,Self,Rest).



%cmdline_load_file(Self,Filemask):- is_converting,!,

cmdline_load_file(Self,Filemask):-
Src=user:load_metta_file(Self,Filemask),
catch_abort(Src,
Expand Down Expand Up @@ -614,54 +618,202 @@
include_metta(Self,Filename):-
(\+ atom(Filename); \+ exists_file(Filename)),!,
must_det_ll(with_wild_path(include_metta(Self),Filename)),!.

include_metta(Self,RelFilename):-
must_det_ll((
atom(RelFilename),
exists_file(RelFilename),!,
absolute_file_name(RelFilename,Filename),
must_det_ll((setup_call_cleanup(open(Filename,read,In, [encoding(utf8)]),
((directory_file_path(Directory, _, Filename),
assert(metta_file(Self,Filename,Directory)),
with_cwd(Directory,
must_det_ll( load_metta_file_stream(Filename,Self,In))))),close(In)))))).

load_metta_file_stream(Filename,Self,In):-
once((is_file_stream_and_size(In, Size) , Size>102400) -> P2 = read_sform2 ; P2 = read_metta2),
with_option(loading_file,Filename,
%current_exec_file(Filename),
((must_det_ll((
set_exec_num(Filename,1),
load_answer_file(Filename),
set_exec_num(Filename,0))),
load_metta_file_stream_fast(Size,P2,Filename,Self,In)))).


must_det_ll((
atom(RelFilename),
exists_file(RelFilename),!,
absolute_file_name(RelFilename,Filename),
directory_file_path(Directory, _, Filename),
assert(metta_file(Self,Filename,Directory)),
include_metta_directory_file(Self,Directory, Filename))).


% count_lines_up_to_200(Filename, Count).
count_lines_up_to_200(Filename, Count) :-
open(Filename, read, Stream),
count_lines_in_stream(Stream, 0, Count),
close(Stream).

% count_lines_in_stream(Stream, CurrentCount, FinalCount).
count_lines_in_stream(Stream, CurrentCount, FinalCount) :-
( CurrentCount >= 2000
-> FinalCount = 2000
; read_line_to_codes(Stream, Codes),
( Codes == end_of_file
-> FinalCount = CurrentCount
; NewCount is CurrentCount + 1,
count_lines_in_stream(Stream, NewCount, FinalCount)
)
).


include_metta_directory_file_prebuilt(_Self,_Directory, Filename):-
atom_concat(_,'.metta',Filename),
atom_concat(Filename,'.qlf',QLFFilename),
exists_file(QLFFilename),
ensure_loaded(QLFFilename),!.
include_metta_directory_file_prebuilt(_Self,_Directory, Filename):- just_load_datalog,
atom_concat(_,'.metta',Filename),
atom_concat(Filename,'.datalog',QLFFilename),
exists_file(QLFFilename),
ensure_loaded(QLFFilename),!.

include_metta_directory_file(Self,Directory, Filename):-
include_metta_directory_file_prebuilt(Self,Directory, Filename),!.
include_metta_directory_file(Self,Directory, Filename):-
count_lines_up_to_200(Filename, Count), Count > 1980,
convert_metta_to_qlf(Filename,Load),
(exists_file(Load)-> ensure_loaded(Load);
include_metta_directory_file_prebuilt(Self,Directory, Filename)),!.
include_metta_directory_file(Self,Directory, Filename):-
setup_call_cleanup(open(Filename,read,In, [encoding(utf8)]),
with_cwd(Directory, must_det_ll( load_metta_file_stream(Filename,Self,In))),
close(In)).

convert_metta_to_datalog(Filename,DatalogFile):-
atom_concat(Filename,'.datalog',DatalogFile),
setup_call_cleanup(open(Filename,read,Input,[]),
setup_call_cleanup(open(DatalogFile, write, Output,[]),
translate_metta_file_to_datalog_io(Filename,Input,Output),
close(Output)),
close(Input)),!.


translate_metta_file_to_datalog_io(Filename,Input,Output):-
must_det_ll((
%write header
write(Output,'/* '),write(Output,Filename),writeln(Output,' */'),
% write the translation time and date
get_time(Time),stamp_date_time(Time,Date,'UTC'),
format_time(string(DateStr),'%FT%T%z',Date),
write(Output,'/* '),write(Output,DateStr),writeln(Output,' */'),
% make the predicate dynamic/multifile
writeln(Output,':- dynamic(asserted_metta/4).'),
writeln(Output,':- multifile(asserted_metta/4).'),
flag(translated_forms,_,0),
% translate the file
once(call((
repeat,
(at_end_of_stream(Input)->!;
( must_det_ll((
line_count(Input,Lineno),
read_line_to_string(Input,Line),
read_sform(Line,Term))),
(Term==end_of_file->!;
(once(((if_t((1 is (Lineno mod 3000)),writeln(Term:Lineno)),
flag(translated_forms,X,X+1),
write_metta_datalog_term(Output,Term,Filename,Lineno)))),fail))))))),
flush_output(Output),
% teell the user we are done
flag(translated_forms,TF,TF),
writeln('/* Done translating */':TF))).


% write comments
write_metta_datalog_term(Output,'$COMMENT'(Term,_,_),_File,_Lineno):-
format(Output,"/* ~w */~n",[Term]).
% write executed terms
write_metta_datalog_term(Output,exec(Term),File,Lineno):-
format(Output,":-eval_H('&self',~q,~q,~q).~n",[Term,File,Lineno]).
% write asserted terms
write_metta_datalog_term(Output,Term,File,Lineno):-
format(Output,"asserted_metta('&self',~q,~q,~q).~n",[Term,File,Lineno]).

translate_metta_datalog(Input,Output):- translate_metta_datalog('',Input,Output),!.

translate_metta_datalog(_,Input,_):- at_end_of_stream(Input),!.
translate_metta_datalog(Ch,Input,Output):- peek_char(Input,Char),
translate_metta_datalog(Ch,Input,Output,Char).

translate_metta_datalog(_,Input,Output,')'):- !, get_char(Input,_),
writeq(Output,']'),translate_metta_datalog(',',Input,Output).
translate_metta_datalog(Ch,Input,Output,'('):- !,get_char(Input,_),
write(Output,Ch),writeq(Output,'['),translate_metta_datalog('',Input,Output).
translate_metta_datalog(Ch,Input,Output,Space):-char_type(Space,space),!,
get_char(Input,Char), write(Output,Char),translate_metta_datalog(Ch,Input,Output).
translate_metta_datalog(Ch,Input,Output,';'):-!,read_line_to_string(Input, Comment),
'format'(Output, '/* ~w */',[Comment]),translate_metta_datalog(Ch,Input,Output).
translate_metta_datalog(Ch,Input,Output,'"'):-!,read_term(Input,Term,[]),
write(Output,Ch),writeq(Output,Term),translate_metta_datalog(',',Input,Output).
translate_metta_datalog(Ch,Input,Output,'`'):-!,read_term(Input,Term,[]),
write(Output,Ch),writeq(Output,Term),translate_metta_datalog(',',Input,Output).
translate_metta_datalog(Ch,Input,Output,'\''):-!,read_term(Input,Term,[]),
write(Output,Ch),writeq(Output,Term),translate_metta_datalog(',',Input,Output).
translate_metta_datalog(Ch,Input,Output,'$'):-!,
read_chars_until([type(space),')'],Input,Codes),name(Term,Codes),
write(Output,Ch),writeq(Output,Term),translate_metta_datalog(',',Input,Output).
translate_metta_datalog(Ch,Input,Output,Peek):-!,
read_chars_until([type(space),')'],Peek,Input,Codes),name(Term,Codes),
write(Output,Ch),writeq(Output,Term),translate_metta_datalog(',',Input,Output).

read_chars_until(_StopsBefore,Input,[]):- at_end_of_stream(Input),!.
read_chars_until(StopsBefore,Input,Codes):- peek_char(Input,Char),
read_chars_until(StopsBefore, Char, Input, Codes).

stops_before([type(Type)|StopsBefore],Char):- char_type(Char,Type); stops_before(StopsBefore,Char).
stops_before([Ch|StopsBefore],Char):- Ch==Char; stops_before(StopsBefore,Char).

read_chars_until(StopsBefore,Char,_, []):- stops_before(StopsBefore,Char),!.
read_chars_until(StopsBefore, '\\', Input, [Code|Codes]):- get_char(Input,Code),
read_chars_until(StopsBefore, Input, Codes).
read_chars_until(StopsBefore, Char, Input, [Char|Codes]):- get_char(Input,_),
read_chars_until(StopsBefore, Input, Codes).

just_load_datalog:-!, fail.
convert_datalog_to_qlf(DatalogFile,DatalogFile):-just_load_datalog,!.
convert_datalog_to_qlf(DatalogFile,QlfFile):-
sformat(S,'swipl -g "qcompile(~q)" -t halt',[DatalogFile]),
shell(S,_),
file_name_extension(Base, _, DatalogFile),
file_name_extension(Base,'qlf',QlfFile).

convert_metta_to_qlf(Filename,QlfFile):-
must_det_ll((
convert_metta_to_datalog(Filename,DatalogFile),
convert_datalog_to_qlf(DatalogFile,QlfFile))),!.

convert_metta_to_qlf(Filename,_):-
metta_dir(Dir),
sformat(S,'~w/cheap_convert.sh --verbose=1 ~w',[Dir,Filename]),
shell(S,Ret),!,Ret==0.

accept_line(_Self,end_of_file):-!.
accept_line(Self,I):- normalize_space(string(Str),I),!,accept_line2(Self,Str),!.

accept_line2(_Self,S):- string_concat(";",_,S),!,writeln(S).
accept_line2(Self,S):- string_concat('(',RS,S),string_concat(M,')',RS),!,
atomic_list_concat([F|LL],' ',M),PL =..[F,Self|LL],assert(PL),!,flag(next_assert,X,X+1),
if_t((0 is X mod 10_000_000),(writeln(X=PL),statistics)).
atomic_list_concat([F|LL],' ',M),PL =..[F,Self|LL],assert(PL),!,flag(next_assert,X,X+1),
if_t((0 is X mod 10_000_000),(writeln(X=PL),statistics)).
accept_line2(Self,S):- fbug(accept_line2(Self,S)),!.


load_metta_file_stream(Filename,Self,In):-
once((is_file_stream_and_size(In, Size) , Size>102400) -> P2 = read_sform2 ; P2 = read_metta2),
with_option(loading_file,Filename,
%current_exec_file(Filename),
((must_det_ll((
set_exec_num(Filename,1),
load_answer_file(Filename),
set_exec_num(Filename,0))),
load_metta_file_stream_fast(Size,P2,Filename,Self,In)))).


load_metta_file_stream_fast(_Size,_P2,Filename,Self,S):- atomic_list_concat([_,_,_|_],'.',Filename),
\+ option_value(html,true),
atomic(S),is_stream(S),stream_property(S,input),!,
repeat,
read_line_to_string(S,I),
accept_line(Self,I),
I==end_of_file,!.
\+ option_value(html,true),
atomic(S),is_stream(S),stream_property(S,input),!,
repeat,
read_line_to_string(S,I),
accept_line(Self,I),
I==end_of_file,!.


load_metta_file_stream_fast(_Size,P2,Filename,Self,In):-
repeat,
repeat,
current_read_mode(file,Mode),
call(P2, In,Expr), %write_src(read_metta=Expr),nl,
once((((do_metta(file(Filename),Mode,Self,Expr,_O)))->true; pp_m(unknown_do_metta(file(Filename),Mode,Self,Expr)))),
flush_output,
at_end_of_stream(In),!.
flush_output,
at_end_of_stream(In),!.

clear_spaces:- clear_space(_).
clear_space(S):-
Expand Down Expand Up @@ -893,8 +1045,8 @@

read_sform3(_AoS,_AltEnd,'"',S,Text):- !,must_det_ll(atom_until(S,[],'"',Text)).
read_sform3(_AoS,_AltEnd,'`',S,Text):- !,atom_until(S,[],'`',Text).
read_sform3(_AoS,_AltEnd,'\'',S,Text):- !,atom_until(S,[],'\'',Text).
read_sform3(_AoS,_AltEnd,',',_,','):- !.
read_sform3(_AoS,_AltEnd,'\'',S,Text):- fail, !,atom_until(S,[],'\'',Text).
read_sform3(_AoS,_AltEnd,',',_,','):- fail, !.
read_sform3( s , AltEnd,C,S,F):- read_sform4( AltEnd,C,S,F),!.
read_sform3(_AoS, AltEnd,P,S,Sym):- peek_char(S,Peek),!,read_symbol_or_number( AltEnd,Peek,S,[P],Expr),into_symbol_or_number(Expr,Sym).

Expand All @@ -910,19 +1062,22 @@
read_sform5(AoS,'[',S,List,']'):- !,collect_list_until(AoS,S,']',List),!.


read_symbol_or_number(_AltEnd,Peek,_S,SoFar,Expr):- char_type(Peek,space),!,must_det_ll(( atomic_list_concat(SoFar,Expr))).
read_symbol_or_number(AltEnd,B,S,SoFar,Expr):- read_sform5(AltEnd,B,S,List,E),flatten([List,E],F), append(SoFar,F,NSoFar),
peek_char(S,NPeek), read_symbol_or_number(AltEnd,NPeek,S,NSoFar,Expr).
read_symbol_or_number( AltEnd,Peek,_S,SoFar,Expr):- member(Peek,AltEnd),!,must_det_ll(( do_atomic_list_concat(Peek,SoFar,Expr))).
read_symbol_or_number( AltEnd,_Peek,S,SoFar,Expr):- get_char(S,C),append(SoFar,[C],NSoFar),
read_symbol_or_number(_AltEnd,Peek,_S,SoFar,Expr):- char_type(Peek,space),!,
must_det_ll(( atomic_list_concat(SoFar,Expr))).
read_symbol_or_number( AltEnd,Peek,_S,SoFar,Expr):- member(Peek,AltEnd),!,
must_det_ll(( do_atomic_list_concat(Peek,SoFar,Expr))).
read_symbol_or_number(AltEnd,B,S,SoFar,Expr):- fail,read_sform5(AltEnd,B,S,List,E),
flatten([List,E],F), append(SoFar,F,NSoFar),!,
peek_char(S,NPeek), read_symbol_or_number(AltEnd,NPeek,S,NSoFar,Expr).
read_symbol_or_number( AltEnd,_Peek,S,SoFar,Expr):- get_char(S,C),append(SoFar,[C],NSoFar),
peek_char(S,NPeek), read_symbol_or_number(AltEnd,NPeek,S,NSoFar,Expr).

atom_until(S,SoFar,End,Text):- get_char(S,C),atom_until(S,SoFar,C,End,Text).
atom_until(_,SoFar,C,End,Expr):- C ==End,!,must_det_ll((do_atomic_list_concat(End,SoFar,Expr))).
atom_until(S,SoFar,'\\',End,Expr):-get_char(S,C),!,atom_until2(S,SoFar,C,End,Expr).
atom_until(S,SoFar,C,End,Expr):- atom_until2(S,SoFar,C,End,Expr).
atom_until2(S,SoFar,C,End,Expr):- append(SoFar,[C],NSoFar),get_char(S,NC),
atom_until(S,NSoFar,NC,End,Expr).
atom_until(S,NSoFar,NC,End,Expr).

do_atomic_list_concat('"',SoFar,Expr):- \+ string_to_syms,!, atomics_to_string(SoFar,Expr),!.
do_atomic_list_concat(_End,SoFar,Expr):- atomic_list_concat(SoFar,Expr).
Expand Down Expand Up @@ -2442,7 +2597,8 @@
ensure_mettalog_system,
option_value(exeout,Named),
catch_err(qsave_program(Named,
[class(development),autoload(true),goal(loon(goal)), toplevel(loon(toplevel)), stand_alone(true)]),E,writeln(E)),
[class(development),autoload(true),goal(loon(goal)),
toplevel(loon(toplevel)), stand_alone(true)]),E,writeln(E)),
halt(0).
qsave_program:- ensure_mettalog_system, next_save_name(Name),
catch_err(qsave_program(Name,
Expand Down
8 changes: 4 additions & 4 deletions mettalog
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,7 @@ if [ ! -f /.dockerenv ]; then
if command -v docker &> /dev/null; then
# Check if the Docker image exists
if docker image inspect "$IMAGE_NAME" &> /dev/null; then
echo "Updating the Docker image: $IMAGE_NAME"
DEBUG "Updating the Docker image: $IMAGE_NAME"

# Create a temporary file to capture the build output
temp_file=$(mktemp)
Expand All @@ -163,7 +163,7 @@ if [ ! -f /.dockerenv ]; then
else
# If build succeeds, remove the temporary file
rm "$temp_file"
echo "Image $IMAGE_NAME successfully updated."
DEBUG "Image $IMAGE_NAME successfully updated."
fi

# Setup additional environment variables or paths
Expand All @@ -179,10 +179,10 @@ if [ ! -f /.dockerenv ]; then
/home/user/vspace-metta/mettalog "$@"

else
echo "Image $IMAGE_NAME is not installed. Continuing with script..."
DEBUG "Image $IMAGE_NAME is not installed. Continuing with script..."
fi
else
echo "Docker is not installed. Continuing with script..."
DEBUG "Docker is not installed. Continuing with script..."
fi
fi

Expand Down

0 comments on commit 3789079

Please sign in to comment.