1:- module(file,
    2	  [file/3, combine_file/2, cat_text/2, clean_io/3, posix_file_path/2,
    3	   symbolic_link/2,
    4	   tmp_file_name/1,
    5	   cat_files_to_codes/3,
    6	   cat_files/2,
    7	   pipe_line/2,
    8	   dict_of_files/1,
    9	   read_lines_as_atoms/2, read_lines/2,
   10	   fold_text_lines/2, fold_text_lines/3
   11	   ]).   12
   13%
   14
   15:- use_module(pac(basic)).   16:- use_module(util(misc)).   17
   18:- meta_predicate file(+, ?, 0).   19:- meta_predicate file(+, ?, 0, ?).   20:- meta_predicate snap(1, ?).   21
   22		/**************
   23		*     file    *
   24		**************/
   25
   26%%% standard I/O (read/write/append) files
   27
   28file(F, M, A):- file(F, M, A, [encoding(utf8)]).
   29%
   30file(F, M, A, Ops):-
   31        (	expand_file_search_path(F, F0)  -> true
   32		;	absolute_file_name(F, F0)
   33        ),
   34        setup_call_cleanup(
   35			open(F0, M, S, Ops),
   36	        clean_io(S, M, A),
   37		    close(S)).
   38%
   39clean_io(S, read, A) :- !,
   40		current_input(Old),
   41		set_input(S),
   42        once(A),
   43		set_input(Old).
   44clean_io(S, _, A) :-
   45		current_output(Old),
   46		set_output(S),
   47        once(A),
   48		set_output(Old).
   49
   50% ?- fold_text_lines("~/.skk-jisyo", misc:edit_skk_line).
   51:- meta_predicate fold_text_lines(?, 3).   52fold_text_lines(F, Pred):-
   53		expand_file_name(F, [F0|_]),
   54		read_file_to_codes(F0, Codes, [encoding(utf8)]),
   55		split(Codes, Lines),
   56		foldl(Pred, Lines, EditedLines, []),
   57	    tmp_file_stream(utf8, Filetmp, Sout),
   58		put_lines(EditedLines, Sout),
   59		close(Sout),
   60		rename_file(Filetmp, F0).
   61
   62% ?- fold_text_lines("~/.skk-jisyo", misc:edit_skk_line, "~/Desktop/deldel").
   63:- meta_predicate fold_text_lines(?, 3, ?).   64fold_text_lines(F, Pred, G):-
   65		expand_file_name(F, [F0|_]),
   66		read_file_to_codes(F0, Codes, [encoding(utf8)]),
   67		split(Codes, Lines),
   68		foldl(Pred, Lines, EditedLines, []),
   69		expand_file_name(G, [G0|_]),
   70	    open(G0, write, Sout, [encoding(utf8)]),
   71		put_lines(EditedLines, Sout),
   72		close(Sout).
   73
   74%
   75put_lines([], _).
   76put_lines([L|Ls], S):- maplist(put_code(S), L),
   77	put_code(S, `\n`),
   78	put_lines(Ls, S).
 pipe_line(+X, -Y) is det
execute shell X via pipe and recieve the result as string Y.
   84% ?-pipe_line('echo $HOME', S).
   85% ?-pipe_line(date, S).
   86
   87pipe_line(Shell, String):-
   88	open(pipe(Shell), read, Stream, [encoding(utf8)]),
   89	read_string(Stream, "\n", "\r\t ", _, String),
   90	close(Stream).
   91
   92%
   93combine_file(Ls, F) :-
   94	maplist(through_list_or_string, Ls, CombinedCodes),
   95	file(F, write, basic:smash(CombinedCodes)).
   96
   97
   98% ?- cat_text([abc, def], deldel).
   99% ?- cat_text(['\\a\nbc', '\n', 2, '\n', 3, '\n', def, '\n', file(deldel)], deldeldel).
  100% ?- shell('cat deldeldel').
  101
  102cat_text(Segments, F):- file(F, write, cat_text(Segments)).
  103%
  104cat_text([]):-!.
  105cat_text([X|Y]):-!, cat_text(X), cat_text(Y).
  106cat_text(codes(X)):-!, smash(X).
  107cat_text(file(F)):-!,
  108	file(F, read, read_current_text(X)),
  109	write(X).
  110cat_text(X):- atomic(X), write(X).
  111%
  112read_current_text(X):- current_input(S),
  113	read_string(S, "\n", "\r\t ", -1, X).
  114
  115% ?- posix_file_path('~', X).
  116% ?- posix_file_path('~/*', X). % fail.
  117posix_file_path(X, Y):- expand_file_name(X, L), !, L = [Y].
  118
  119%
  120cat_files(G, F):- atomic(G), !,
  121	cat_files([G], F).
  122cat_files(Fs, F):-
  123	tmp_file_stream(text, TMPfile, Stream),
  124    close(Stream),
  125	maplist(expand_file_name, Fs, Gs),
  126	cat_files_rec(Gs, TMPfile),
  127	expand_file_name(F, [F0|_]),
  128	rename_file(TMPfile, F0).
  129
  130cat_files_rec([], _).
  131cat_files_rec([X|Xs], T):- atomic(X), !,
  132	pshell(cat(X) >> T),
  133	cat_files_rec(Xs, T).
  134cat_files_rec([X|Xs], T):-
  135	cat_files_rec(X, T),
  136	cat_files_rec(Xs, T).
  137
  138%
  139cat_files_to_codes([], C, C).
  140cat_files_to_codes([P|Q], C, C0):-
  141    	read_file_to_codes(P, C, [tail(C1), encoding(utf8)]),
  142	cat_files_to_codes(Q, C1, C0).
  143
  144%
  145through_list_or_string(X, X):- (listp(X); string(X)), !.
  146through_list_or_string(X, Y):- call(X, Y).
 symbolic_link(+Target:string, +Link:string) is det
Make a symbolic link Link to Target via a shell call.
  150symbolic_link(Target, Link) :- 	expand_file_name(Link, [Link0]),
  151	(	read_link(Link0,_,_)
  152	 ->	true
  153 	 ;	expand_file_name(Target, [Target0]),
  154		eh:sh(ln(-s, Target0, Link0))
  155	),
  156	!.
  157
  158% tmp_file_name(File):- tmp_file_stream(text, File, Stream), close(Stream).
  159tmp_file_name(File):- tmp_file_stream(utf8, File, Stream), close(Stream).
  160
  161push_to_file(M, F):- expand_file_name(F, [F1]),
  162	(	exists_file(F1)
  163	-> 	tmp_file_name(T1),
  164		file(T1, write, M),
  165		tmp_file_name(T2),
  166		pshell(cat(T1, F) + ' > ' +  T2),
  167		rename_file(T2, F1),
  168		delete_file(T1)
  169	;	file(F1, write, M)
  170	).
  171
  172% ?- open_url('http://web.sfc.keio.ac.jp/~mukai/paccgi7/index.html', IN).
  173% sample coding
  174open_url(URL, In, Option) :-
  175        tmp_file_stream(text, File, Stream),
  176        close(Stream),
  177        process_create('/usr/bin/curl', ['-o', File, URL], []),
  178        open(File, read, In, Option),
  179        delete_file(File).  % Unix-only
  180%
  181open_url(URL, In) :- open_url(URL, In, []).
List files recursively under the working directory, and unify D with the result in the form of a dict with <directory name> - <dict> for subdirectories.

?- file:dict_of_files(D).

  190ignore_special((.)).
  191ignore_special((..)).
  192ignore_special(('.DS_Store')).
  193ignore_special(('.git')).
  194
  195%
  196dict_of_files(X):- directory_files_((.), Files),
  197		directory_files_(Files, X, []).
  198%
  199directory_files_([], X, X).
  200directory_files_([F|R], X, Y):- ignore_special(F), !,
  201	   directory_files_(R, X, Y).
  202directory_files_([D|R], [D-Z|X], Y):- exists_directory(D), !,
  203		directory_files_(D, Files),
  204		working_directory(_, D),
  205		directory_files_(Files, Z, []),
  206		working_directory(_, (..)),
  207		directory_files_(R, X, Y).
  208directory_files_([F|R], [F|X], Y):- directory_files_(R, X, Y).
  209
  210		/**************
  211		*     snap    *
  212		**************/
  213
  214user:snap(C)  :- getenv(snapshot, File),
  215	do_snap(File, basic:smash, [C,"\n"]).
  216%
  217user:snap(M, C):- user:snap(M >> C).
  218%
  219user:snap(M, X, X):- basic:smash(X, X0), user:snap(["\n", M, "\n", X0]).
  220%
  221user:dsnap(X, X):- user:snap(X).
  222
  223%
  224do_snap(File, M, X):-
  225	current_output(Old),
  226	open(File, append, New, [encoding(utf8)]),
  227	set_output(New),
  228	call(M, X),
  229	set_output(Old),
  230	close(New).
  231
  232% Prevents "stream... does not exist (already closed)" error
  233close_stream(Stream) :-
  234    (   is_stream(Stream)
  235    ->  close(Stream)
  236    ;   true
  237    ).
  238
  239read_stream_to_codes(Stream, Codes) :-
  240    fill_buffer(Stream),
  241    read_pending_codes(Stream, Codes, Tail),
  242    (   Tail == []
  243    ->  true
  244    ;   read_stream_to_codes(Stream, Tail)
  245    ).
  246
  247% Recommended by Jan.
  248
  249read_lines_as_atoms(Stream, Lines) :-
  250    read_string(Stream, "\n", "", Sep, String),
  251    (   Sep == -1
  252    ->  Lines = []
  253    ;   atom_string(Line, String),
  254        Lines = [Line|Rest],
  255        read_lines_as_atoms(Stream, Rest)
  256    ).
  257%
  258read_lines(Out, Lines) :-
  259    read_line_to_codes(Out, Line1),
  260    read_lines(Line1, Out, Lines).
  261
  262% read_lines(end_of_file, _, []) :- !.
  263read_lines(Codes, Out, [Line|Lines]) :-
  264    atom_codes(Line, Codes),
  265    read_line_to_codes(Out, Line2),
  266    read_lines(Line2, Out, Lines)