:- use_module(library(dcg/basics)). :- encoding(utf8). %----- :- dynamic eval_tag/6. :- dynamic eval_tag_secondary/2. :- dynamic eval_tag_found/6. :- dynamic found_search_result/6. today_key(Dk):- get_time(Stamp), stamp_day_atom(Stamp, Dk),!. %number_zero2(Y, Y2):- atom_number(Ya, Y), atom_length(Ya, Le), Le == 1,!, atom_concat(0, Ya, Y2). %number_zero2(Y, Ya):- atom_number(Ya, Y),!. number_zero2(Y, Y2):- atom_length(Y, Le), Le == 1,!, atom_concat(0, Y, Y2). number_zero2(Y, Y):- !. %number_zero2(Y, 11):- number(Y),!. %number_zero2(Y, 12):- atom(Y),!. stamp_day_atom(Stamp, Dat):- stamp_date_time(Stamp, D, 0), date_time_value(date, D, Dx), Dx = date(Y,M,Dag), number_zero2(M, M2), number_zero2(Dag, Dag2), atomic_list_concat([Y,M2,Dag2], Dat),!. stamp_day_atom(_, 00):- !. % atom_number(Sta2, Sta), add_file_to_zip(Sta, Gma, El):- atom_concat('totgs_',Sta, Xu), atom_concat(Xu,'.zip', Cx), atomic_list_concat(['zip ',Cx,' /var/www/html/',Gma,El], Bg), atom_string(Bg, Str), shell(Str). % DUS AANROEP MET bvb do(20190519). % today_key(Dk):- do(Sta):- retractall(file(_,_,_)), Dir = '/var/www/html/', gmap(Gma), atom_concat(Dir, Gma, Fdir), directory_files(Fdir, Lis), member(El, Lis), El \= '..', El \= '.', atom_concat(Fdir, El, Cx), time_file(Cx, Stamp), stamp_day_atom(Stamp, Dat), atom_number(Dat, Datnum), Datnum > Sta, assert(file(Gma, El, Dat)), fail. % stamp_date_time(Stamp, D, 0), % date_time_value(date, D, Date), do(_Sta):- today_key(Dk), file(Gma, El, Dat), format(Gma), format(El), format(Dat), nl, add_file_to_zip(Dk, Gma, El), fail. do(_):- !. % zip -r compressed_filename.zip foldername % directory_member(Dx, Item, [ recursive(true)]), %-------- :- dynamic dir_level/10. :- discontiguous dir_level/10. :- dynamic file_level/11. :- discontiguous file_level/11. % htdoc_m_app % 1 is alleen met de apps , 0 is alleen gym files %-- special_directory_files('../canary/', [ 'metta_eval.pl' , 'metta_interp.pl' , 'metta_ontology.pfc.pl', 'stdlib_mettalog.metta' ]):- !. % experime %special_directory_files('../../../hyperon-experimental/lib/src/metta/runner/', [ 'stdlib_minimal.rs' , 'stdlib.rs' ]):- !. special_directory_files('../../../hyperon-experimental/lib/src/metta/runner/', [ 'stdlib_minimal.rs' , 'stdlib.rs' ]):- !. % special_directory_files(Dx, Lis):- !, directory_files(Dx, Lis). %---- get_all_singularity_files( Tp, _, Dx):- retractall(dir_level(_, _, _,_, _,_,_,_,_,_)), retractall(file_level(_, _, _, _,_, _,_,_,_,_,_)), directory_files(Dx, Lis), member(El, Lis), El \= '..', El \= '.', allow_dir(Tp, Dx, El), atom_concat(Dx, El, Cx), exists_directory(Cx), assert( dir_level(1, El, '', '', '','','','','','') ), fail, !. get_all_singularity_files( Tp, _, Dx):- dir_level( 1, Item, _, _, _, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/' ], Cy ), directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', allow_dir(Tp, Cy, El), atom_concat( Cy, El, Cxy ), exists_directory( Cxy ), assert( dir_level( 2, Item, El, '', '', '', '', '', '', '' ) ), fail, !. % dir_level(2,'PR_12_NvoDesign',tools,'','','','','','',''). get_all_singularity_files( Tp, _, Dx ):- dir_level( 2, Item, Item2, _, _, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/' , Item2 , '/' ], Cy ), directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', allow_dir(Tp, Cy, El), atom_concat( Cy, El, Cxy ), exists_directory( Cxy ), assert( dir_level( 3, Item, Item2, El, '', '', '', '', '', '' ) ), fail, !. get_all_singularity_files( Tp, _, Dx):- dir_level( 3, Item, Item2, Item3, _, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/' , Item2 , '/', Item3, '/' ], Cy ), directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', allow_dir(Tp, Cy, El), atom_concat( Cy, El, Cxy ), exists_directory( Cxy ), assert( dir_level( 4, Item, Item2, Item3, El, '', '', '', '', '' ) ), fail, !. get_all_singularity_files( Tp, _, Dx):- dir_level( 4, Item, Item2, Item3, Item4, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/' , Item2 , '/', Item3, '/', Item4, '/' ], Cy ), directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', allow_dir(Tp, Cy, El), atom_concat( Cy, El, Cxy ), exists_directory( Cxy ), assert( dir_level( 5, Item, Item2, Item3, Item4, El, '', '', '', '' ) ), fail, !. get_all_singularity_files( Tp, _, Dx):- dir_level( 5, Item, Item2, Item3, Item4, Item5, _, _, _, _), atomic_list_concat([ Dx, Item, '/' , Item2 , '/', Item3, '/', Item4, '/', Item5, '/' ], Cy ), directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', allow_dir(Tp, Cy, El), atom_concat( Cy, El, Cxy ), exists_directory( Cxy ), assert( dir_level( 6, Item, Item2, Item3, Item4, Item5, El, '', '', '' ) ), fail, !. % canary get_all_singularity_files(_, Is_mdf_day_after, Dx):- % dir_level(1, Item, _,_, _,_,_,_,_,_), atomic_list_concat([ Dx, Item, '/'], Cy), special_directory_files(Dx, Lis), % 'H:/metta-wam-main/src/canary/' member(El, Lis), El \= '..', El \= '.', % write( El ), nl, is_prolog_atom_file( El, Dx ), atom_concat(Dx, El, Cx), time_file(Cx, Stamp), stamp_day_atom(Stamp, Dat), match_date_atom(Dat, Is_mdf_day_after), assert( file_level(0, Dx, '', '','','','','','', El, Dat) ), fail,!. % assert( file_level(0, Item, '', '','','','','','', El, Dat) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(1, Item, _,_, _,_,_,_,_,_), atomic_list_concat([ Dx, Item, '/'], Cy), special_directory_files(Cy, Lis), member(El, Lis), El \= '..', El \= '.', is_prolog_atom_file( El, Item ), atom_concat(Cy, El, Cx), time_file(Cx, Stamp), stamp_day_atom(Stamp, Dat), match_date_atom(Dat, Is_mdf_day_after), assert( file_level(1, Item, '', '','','','','','', El, Dat) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(2, Item, Sub, _, _, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/', Sub, '/' ], Cy ), special_directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', is_prolog_atom_file( El, Sub ), atom_concat(Cy, El, Cx), time_file( Cx, Stamp ), stamp_day_atom( Stamp, Dat ), match_date_atom( Dat, Is_mdf_day_after ), assert( file_level( 2, Item, Sub, '', '', '', '', '', '', El, Dat ) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(3, Item, Item2, Sub, _, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/', Item2, '/', Sub, '/' ], Cy ), special_directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', is_prolog_atom_file( El, Sub ), atom_concat(Cy, El, Cx), time_file( Cx, Stamp ), stamp_day_atom( Stamp, Dat ), match_date_atom( Dat, Is_mdf_day_after ), assert( file_level( 3, Item, Item2, Sub, '', '', '', '', '', El, Dat ) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(4, Item, Item2, Item3, Sub, _, _, _, _, _), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Sub, '/' ], Cy ), special_directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', is_prolog_atom_file( El, Sub ), atom_concat(Cy, El, Cx), time_file( Cx, Stamp ), stamp_day_atom( Stamp, Dat ), match_date_atom( Dat, Is_mdf_day_after ), assert( file_level( 4, Item, Item2, Item3, Sub, '', '', '', '', El, Dat ) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(5, Item, Item2, Item3, Item4, Sub, _, _, _, _), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Item4, '/', Sub, '/' ], Cy ), special_directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', is_prolog_atom_file( El, Sub ), atom_concat(Cy, El, Cx), time_file( Cx, Stamp ), stamp_day_atom( Stamp, Dat ), match_date_atom( Dat, Is_mdf_day_after ), assert( file_level( 5, Item, Item2, Item3, Item4, Sub, '', '', '', El, Dat ) ), fail,!. get_all_singularity_files(_, Is_mdf_day_after, Dx):- dir_level(6, Item, Item2, Item3, Item4, Item5, Sub, _, _, _), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Item4, '/', Item5, '/', Sub, '/' ], Cy ), special_directory_files( Cy, Lis ), member( El, Lis ), El \= '..', El \= '.', is_prolog_atom_file( El, Sub ), atom_concat(Cy, El, Cx), time_file( Cx, Stamp ), stamp_day_atom( Stamp, Dat ), match_date_atom( Dat, Is_mdf_day_after ), assert( file_level( 6, Item, Item2, Item3, Item4, Item5, Sub, '', '', El, Dat ) ), fail,!. get_all_singularity_files(_, _, _):- write("start writing to data/htm_file_list.pl\n"), tell('data/htm_file_list.pl'), write(":- dynamic dir_level/10."), nl, write(":- discontiguous dir_level/10."), nl, write(":- dynamic file_level/11."), nl, write(":- discontiguous file_level/11."), nl, fail. get_all_singularity_files(_, _, _):- dir_level(1, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(1, Item, Sub, X, A,B,C,D,E,F),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- dir_level(2, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(2, Item, Sub, X, A,B,C,D,E,F ),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- dir_level(3, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(3, Item, Sub, X, A,B,C,D,E,F ),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- dir_level(4, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(4, Item, Sub, X, A,B,C,D,E,F ),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- dir_level(5, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(5, Item, Sub, X, A,B,C,D,E,F ),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- dir_level(6, Item, Sub, X, A,B,C,D,E,F), write_term(dir_level(6, Item, Sub, X, A,B,C,D,E,F ),[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- retract( file_level(0, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(0, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- retract( file_level(1, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(1, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- retract( file_level(2, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(2, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_, _):- retract( file_level(3, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(3, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_,_):- retract( file_level(4, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(4, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_,_):- retract( file_level(5, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(5, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files(_,_,_):- retract( file_level(6, Item, Sub, El, Q, A,B,C,D,E,F) ), write_term( file_level(6, Item, Sub, El, Q, A,B,C,D,E,F) ,[ quoted(true) ]), write("."), nl, fail, !. get_all_singularity_files( _, _, _ ):- told(), write( "finished writing to data/htm_file_list.pl\n" ), !. % hier dus Als het JS is opschoon comment er uit % ALS het htm is ?versie= % % % copyr(), % 1 is htm 2 is js wr_newlin( 0 ):- ! . wr_newlin( _ ):- ! , nl . % write(From), nl, write(To), nl, % :- dynamic found_base_teur/4. %read_has_search_strings( _, From, Zk, Level, Is_include , Isleading):- % sub_atom( From, _, _, _, '.metta' ), size_file( From , Size ), Size < 700, read_file_to_string(From, Bstr, [] ), !, % if_extra_string_demand_search( Bstr ), search_o_y_and_assert( Is_include, Bstr, Zk, From, Level, 0 , Isleading). %read_has_search_strings( _, From, Zk, Level, Is_include , Isleading):- % sub_atom( From, _, _, _, '.py' ), size_file( From , Size ), Size < 700, read_file_to_string(From, Bstr, [] ), !, % if_extra_string_demand_search( Bstr ), search_o_y_and_assert( Is_include, Bstr, Zk, From, Level, 0 , Isleading). %read_has_search_strings( _, From, Zk, Level, Is_include , Isleading):- % sub_atom( From, _, _, _, '.rs' ), size_file( From , Size ), Size < 700, read_file_to_string(From, Bstr, [] ), !, % if_extra_string_demand_search( Bstr ), search_o_y_and_assert( Is_include, Bstr, Zk, From, Level, 0 , Isleading). read_has_search_strings( is_octet , From, Zk, Level, Is_include , Isleading):- retractall( comment_started() ), write( "check must read : " ), write( From ), nl , not_exclude_metta_file( From ), max_file_size( From , Max), size_file( From, Size ), Size < Max, write( "Start read : " ), write( From ), nl , open( From, read, Sea , [ encoding(octet) ] ), read_has_search_stream( Sea, Zk, From, Level, 1, 1, Is_include , Isleading ), close( Sea ). % % mogelijke waarden octet, ascii, iso_latin_1 , text, utf8 , unicode_be, unicode_le read_has_search_strings( is_utf8 , From, Zk, Level, Is_include , Isleading):- retractall( comment_started() ), write( "check must read : " ), write( From ), nl , not_exclude_metta_file( From ), max_file_size( From , Max ), size_file( From, Size ), Size < Max, write( "Start read : " ), write( From ), nl , open( From, read, Sea , [ encoding(utf8) ] ), read_has_search_stream( Sea, Zk, From, Level, 1, 1, Is_include , Isleading), close( Sea ). read_has_search_strings( _, _, _, _, _ , _ ):- !. %--- %read_all_singularity_files(_Tp, _, _Isalways_copy, _Is_update, _, _):- % Xfi = 'data/htm_file_list.pl', % retractall( dir_level( _, _, _, _, _, _, _, _, _, _) ), % retractall( file_level(_, _, _, _, _, _, _, _, _, _, _) ), % consult( Xfi ), % write("Consulted\n"), write(Xfi), % fail. % separate_prolog_code( Zk, Dirx_walk ), read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, _Dx, Is_include , Isleading):- file_level(0, Item, _, _, _, _, _, _, _, Xf, _ ), atomic_list_concat([ Item, Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type, From, Zk, 0, Is_include, Isleading ), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(1, Item, _, _, _, _, _, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings(Is_file_type, From, Zk, 1, Is_include , Isleading), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(2, Item, Sub, _, _, _, _, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Sub, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type,From, Zk, 2, Is_include , Isleading), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(3, Item, Item2, Sub, _, _, _, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Item2, '/', Sub, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type,From, Zk, 3, Is_include , Isleading), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(4, Item, Item2, Item3, Sub, _, _, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Sub, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type,From, Zk, 4, Is_include , Isleading), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(5, Item, Item2, Item3, Item4, Sub, _, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Item4, '/', Sub, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type,From, Zk, 5, Is_include , Isleading), fail. read_all_singularity_files(Is_file_type,_Tp, Zk, _Isalways_copy, _Is_update, Dx, Is_include, Isleading):- file_level(6, Item, Item2, Item3, Item4, Item5, Sub, _, _, Xf, _ ), atomic_list_concat([ Dx, Item, '/', Item2, '/', Item3, '/', Item4, '/', Item5, '/', Sub, '/', Xf ], From ), is_relevant_file(Is_include, From ), read_has_search_strings( Is_file_type,From, Zk, 6, Is_include , Isleading), fail. % HIER NOG LEVEL 4 5 6 7 % assert( file_level( 2, Item, Sub, El, Dat, '', '', '', '', '', '' ) ), fail,!. read_all_singularity_files( _, _, _, _, _, _, _ , _):- !. match_date_atom( _ , _ ):- !. % MATCH ALL Prolog JDKlog match_date_atom( _Dat, '' ):- !. match_date_atom( Dat, Is_mdf_day_after ):- atom_number( Dat, Nu1 ), atom_number( Is_mdf_day_after, Nu2 ), Nu1 >= Nu2,!. :- dynamic comment_started/0. not_is_comment( Lx ):- sub_string( Lx, Sta, _, _, "%"), Sta < 5,!, fail. not_is_comment( _ ):- !. % gaat fout bij genest zet_comment_started(Lx):- sub_string( Lx, _, _, _, "/*"),!, assert( comment_started() ). zet_comment_started(_):-!. zet_comment_ended(Lx):- sub_string( Lx, _, _, _, "*/"), retractall( comment_started() ), !. zet_comment_ended(_):- !. is_not_inside_comment():- comment_started(),!, fail. is_not_inside_comment():- !. search_and( _, [] ):- !. search_and( Lx, [ H | Lis_and ] ):- sub_string( Lx, _, _, _, H ),!, search_and( Lx, Lis_and ). search_or(Lx, [ H | _Lis_or]):- split_string(H, "&", "", Lis_and), search_and( Lx, Lis_and ),!. % sub_string( Lx, _, _, _, H ),!. search_or(Lx, [ _H | Lis_or]):- !, search_or(Lx, Lis_or ). search_o_y(Lx, Zk):- !, string_lower( Lx, Lx2 ), split_string(Zk, ",", "", Lis_or), search_or(Lx2, Lis_or). :- dynamic found_include_file/11. str_part_after_tag(Str, Tag, AfterStr):- string_length(Str, Sle), string_length(Tag, Tagl), sub_string(Str, Beg, _ , _, Tag), Beg2 is Beg + Tagl, Lx is Sle - Beg2, sub_string(Str, Beg2 , Lx, _, AfterStr),!. str_part_before_tag(At, Tag, Pa_before):- atom_length(Tag, TagLe), TagLe > 0, sub_atom(At, Bg, _, _, Tag), sub_atom(At, 0, Bg, _, Pa_before),!. %str_replace_tag(At, Repwhat, RepWith, Resu):- str_part_before_tag(At, Repwhat, Pa_before), str_part_after_tag(At, Repwhat, Pa_aft),!, % string_concat(Pa_before,RepWith, C1), string_concat(C1,Pa_aft, Resu). %str_replace_tag(At, _,_, At):- !. str_replace_tag(At, Repwhat, RepWith, Resu):- str_part_before_tag(At, Repwhat, Pa_before), str_part_after_tag(At, Repwhat, Pa_aft),!, string_concat(Pa_before,RepWith, C1), string_concat(C1,Pa_aft, Resu). str_replace_tag(At, _,_, At):- !. lis_code_remove([], _, [], [] ):-!. lis_code_remove([H|Codes1], Cde, [Cde |Codes2], Lisnot ):- H = Cde, !, lis_code_remove(Codes1, Cde, Codes2, Lisnot). lis_code_remove([H|Codes1], Cde, Codes2 , [ H |Lisnot]):- !, lis_code_remove(Codes1, Cde, Codes2, Lisnot). %--- lis_code_count( [], _, Res, Res ):- !. lis_code_count( [ H | Codes1 ], Cde, Count, Res ):- H = Cde, !, Count2 is Count + 1, lis_code_count( Codes1, Cde, Count2, Res ). lis_code_count( [ _ | Codes1 ], Cde, Count , Res ):- !, lis_code_count( Codes1, Cde , Count , Res ). %--- str_code_remove( Str, Cde, Str2 ):- string_codes( Str, Codes1 ), lis_code_remove( Codes1, Cde, _, Codes2 ),!, string_codes( Str2, Codes2 ). str_code_occurence_count( Str, Cde, Count ):- string_codes( Str, Codes1 ), lis_code_count( Codes1, Cde, 0, Count ), !. %---- % , read_extra_lines_max_until_full_metta_claus( reject_zero, Count_is_open, Count, _Max, _Sea , StrBuf, StrBuf, Count ):- Count_is_open == 0, !. read_extra_lines_max_until_full_metta_claus( Rej_zero, Count_is_open, Count, Max, Sea , StrBuf, Xtra_lines, ResultCount ):- Count < Max, read_line_to_string( Sea, Lx ), Lx \= end_of_file, !, parenthesis_count( Lx, Count_open ), NewCount is Count_is_open + Count_open, string_concat( StrBuf, "\n", C2 ), string_concat( C2, Lx, StrBuf2 ), Count2 is Count + 1, read_extra_lines_max_until_full_metta_claus( Rej_zero, NewCount, Count2, Max, Sea , StrBuf2, Xtra_lines, ResultCount ). read_extra_lines_max_until_full_metta_claus( _, _Count_is_open, Count, _Max, _Sea , StrBuf, StrBuf, Count ):- !. %-- %write_line_with_tag_colors( Ext, Txt ):- !, % string_codes( Txt, Codes ), % write_codes_with_tag_colors( Ext, Codes ). %--- write_metta_clause_htm( Lx ):- % str_replace_tag(At, Repwhat, RepWith, Resu) string_codes( Lx, Codes ), % write_codes_with_tag_colors( Ext, Codes ). Parenthesis_level is 0, write_codes_metta_clause_htm( Codes , Parenthesis_level ). %-- write_big_tag( Tag ):- write( "\n
" ), write( Tag ), write( "
self.assertEqualMettaRunnerResults(metta.run('!(get-st (name id-001))'), % [[S('Fritz')]])% !(assertEqualToResult (change-state! aq au ) ( result_with_type )) % str_replace_tag(At, Repwhat, RepWith, Resu):- % sub_str_between( Lx, Second_tag_begin, Second_tag_end, Subz2 ), concat_slist( [], Resu, Resu ):- !. concat_slist( [ H | Rs ], Hs, Resu ):- !, string_concat( Hs, H, C1 ), concat_slist( Rs , C1, Resu ). %---- concat_slist_with_delim( [], Resu, _, Resu ):- !. concat_slist_with_delim( [ H ], Hs, _Delim, Resu ):- !, string_concat( Hs, H, Resu ), !. %-- % to implement , clean this kind of constructs clean_python_string_constructs( Subz3, Subz3 ):- !. %--- % eval_tag(python_src_metta_test,38, % "assertequalmettarunnerresults(", % '../../../hyperon-experimental/python/tests/test_pln_tv.py', % orginal string % " self.assertEqualMettaRunnerResults(\n metta.run('!(pln (And (P A) (P $x)))'),\n % [metta.parse_all('''\n ((And (P A) (P A)) (stv 0.5 0.8))\n ((And (P A) (P B)) (stv 0.3 0.8))\n ''')])",0) try_read_python_second_arg_asserteq( AfterStr, Subz30 ):- sub_string( AfterStr, _,_,_, "metta.parse_all" ), sub_str_between( AfterStr, "'''", "'''", Subz30 ), !. try_read_python_second_arg_asserteq( AfterStr, Subz30 ):- sub_string( AfterStr, _,_,_, "metta.parse_all" ), sub_str_between( AfterStr, "[", "]", Subz30 ), !. try_read_python_second_arg_asserteq( AfterStr, Subz30 ):- sub_str_between( AfterStr, ",", ")", Subz30 ), !. % eval_tag(python_src_metta_test,22, % "assertequalmettarunnerresults(", % 1. '../../../hyperon-experimental/python/tests/test_run_metta.py', % " self.assertEqualMettaRunnerResults(metta.run(program),\n [metta.parse_all('red green blue'), % metta.parse_all('5')])",0) % 2. ---self.assertEqualMettaRunnerResults(metta.run(program), % [metta.parse_all('red green blue'), metta.parse_all('5')]) try_clean_python_to_metta( Lx0, Lx2 ):- sub_string( Lx0, _,_,_, "self.assertEqualMettaRunnerResults" ), str_code_replace( Lx0, 10, 32, Lx ), sub_str_between( Lx, "metta.run('!", "'", Subz2 ), str_part_after_tag( Lx, "self.assertEqualMettaRunnerResults", AfterStr ), try_read_python_second_arg_asserteq( AfterStr, Subz30 ), clean_python_string_constructs( Subz30, Subz3 ), ! , today_key( Dk ), incr2( N2 ), number_string( N2, N2_s ), concat_slist( [ "; ", N2_s, ". ", Dk, " R.v.Vessum converted python source to metta \n!(assertEqualToResult ", Subz2, " ", Subz3, "     ) " ], "", Lx2 ). try_clean_python_to_metta( Lx, Lx3 ):- sub_string( Lx, _,_,_, "self.assertEqualMettaRunnerResults" ), sub_str_between( Lx, "metta.run(pro", ")", _Subz2 ), % str_part_after_tag( Lx, "self.assertEqualMettaRunnerResults", AfterStr ), str_part_after_tag( Lx, "metta.parse_all('", _AfterStr2 ), !, % clean_python_string_constructs( Subz30, Subz3 ), ! , today_key( Dk ), incr2( N2 ), number_string( N2, N2_s ), concat_slist( [ "\n;
\n", "\n;\n" ), fail, ! . make_python_src_to_metta_table():- write( " " ), !. make_rust_prolog_table():- show_read_files_dir(), write( "