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	   ]).   11
   12%
   13
   14:- use_module(pac(basic)).   15
   16:- meta_predicate file(+, ?, 0).   17:- meta_predicate file(+, ?, 0, ?).   18:- meta_predicate snap(1, ?).   19
   20		/**************
   21		*     file    *
   22		**************/
   23
   24%%% standard I/O (read/write/append) files
   25
   26file(F, M, A):- file(F, M, A, [encoding(utf8)]).
   27%
   28file(F, M, A, Ops):-
   29        (	expand_file_search_path(F, F0)  -> true
   30		;	absolute_file_name(F, F0)
   31        ),
   32        setup_call_cleanup(
   33			open(F0, M, S, Ops),
   34	        clean_io(S, M, A),
   35		    close(S)).
   36%
   37clean_io(S, read, A) :- !,
   38		current_input(Old),
   39		set_input(S),
   40        once(A),
   41		set_input(Old).
   42clean_io(S, _, A) :-
   43		current_output(Old),
   44		set_output(S),
   45        once(A),
   46		set_output(Old).
 pipe_line(+X, -Y) is det
execute shell X via pipe and recieve the result as string Y.
   52% ?-pipe_line('echo $HOME', S).
   53% ?-pipe_line(date, S).
   54
   55pipe_line(Shell, String):-
   56	open(pipe(Shell), read, Stream, [encoding(utf8)]),
   57	read_string(Stream, "\n", "\r\t ", _, String),
   58	close(Stream).
   59
   60%
   61combine_file(Ls, F) :-
   62	maplist(through_list_or_string, Ls, CombinedCodes),
   63	file(F, write, basic:smash(CombinedCodes)).
   64
   65
   66% ?- cat_text([abc, def], deldel).
   67% ?- cat_text(['\\a\nbc', '\n', 2, '\n', 3, '\n', def, '\n', file(deldel)], deldeldel).
   68% ?- shell('cat deldeldel').
   69
   70cat_text(Segments, F):- file(F, write, cat_text(Segments)).
   71%
   72cat_text([]):-!.
   73cat_text([X|Y]):-!, cat_text(X), cat_text(Y).
   74cat_text(codes(X)):-!, smash(X).
   75cat_text(file(F)):-!,
   76	file(F, read, read_current_text(X)),
   77	write(X).
   78cat_text(X):- atomic(X), write(X).
   79%
   80read_current_text(X):- current_input(S),
   81	read_string(S, "\n", "\r\t ", -1, X).
   82
   83% ?- posix_file_path('~', X).
   84% ?- posix_file_path('~/*', X). % fail.
   85posix_file_path(X, Y):- expand_file_name(X, L), !, L = [Y].
   86
   87%
   88cat_files(G, F):- atomic(G), !,
   89	cat_files([G], F).
   90cat_files(Fs, F):-
   91	tmp_file_stream(text, TMPfile, Stream),
   92    close(Stream),
   93	maplist(expand_file_name, Fs, Gs),
   94	cat_files_rec(Gs, TMPfile),
   95	expand_file_name(F, [F0|_]),
   96	rename_file(TMPfile, F0).
   97
   98cat_files_rec([], _).
   99cat_files_rec([X|Xs], T):- atomic(X), !,
  100	pshell(cat(X) >> T),
  101	cat_files_rec(Xs, T).
  102cat_files_rec([X|Xs], T):-
  103	cat_files_rec(X, T),
  104	cat_files_rec(Xs, T).
  105
  106%
  107cat_files_to_codes([], C, C).
  108cat_files_to_codes([P|Q], C, C0):-
  109    	read_file_to_codes(P, C, [tail(C1), encoding(utf8)]),
  110	cat_files_to_codes(Q, C1, C0).
  111
  112%
  113through_list_or_string(X, X):- (listp(X); string(X)), !.
  114through_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.
  118symbolic_link(Target, Link) :- 	expand_file_name(Link, [Link0]),
  119	(	read_link(Link0,_,_)
  120	 ->	true
  121 	 ;	expand_file_name(Target, [Target0]),
  122		eh:sh(ln(-s, Target0, Link0))
  123	),
  124	!.
  125
  126% tmp_file_name(File):- tmp_file_stream(text, File, Stream), close(Stream).
  127tmp_file_name(File):- tmp_file_stream(utf8, File, Stream), close(Stream).
  128
  129push_to_file(M, F):- expand_file_name(F, [F1]),
  130	(	exists_file(F1)
  131	-> 	tmp_file_name(T1),
  132		file(T1, write, M),
  133		tmp_file_name(T2),
  134		pshell(cat(T1, F) + ' > ' +  T2),
  135		rename_file(T2, F1),
  136		delete_file(T1)
  137	;	file(F1, write, M)
  138	).
  139
  140% ?- open_url('http://web.sfc.keio.ac.jp/~mukai/paccgi7/index.html', IN).
  141% sample coding
  142open_url(URL, In, Option) :-
  143        tmp_file_stream(text, File, Stream),
  144        close(Stream),
  145        process_create('/usr/bin/curl', ['-o', File, URL], []),
  146        open(File, read, In, Option),
  147        delete_file(File).  % Unix-only
  148%
  149open_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).

  158ignore_special((.)).
  159ignore_special((..)).
  160ignore_special(('.DS_Store')).
  161ignore_special(('.git')).
  162
  163%
  164dict_of_files(X):- directory_files((.), Files),
  165		directory_files(Files, X, []).
  166%
  167directory_files([], X, X).
  168directory_files([F|R], X, Y):- ignore_special(F), !,
  169	   directory_files(R, X, Y).
  170directory_files([D|R], [D-Z|X], Y):- exists_directory(D), !,
  171		directory_files(D, Files),
  172		working_directory(_, D),
  173		directory_files(Files, Z, []),
  174		working_directory(_, (..)),
  175		directory_files(R, X, Y).
  176directory_files([F|R], [F|X], Y):- directory_files(R, X, Y).
  177
  178		/**************
  179		*     snap    *
  180		**************/
  181
  182user:snap(C)  :- getenv(snapshot, File),
  183	do_snap(File, basic:smash, [C,"\n"]).
  184%
  185user:snap(M, C):- user:snap(M >> C).
  186%
  187user:snap(M, X, X):- basic:smash(X, X0), user:snap(["\n", M, "\n", X0]).
  188%
  189user:dsnap(X, X):- user:snap(X).
  190
  191%
  192do_snap(File, M, X):-
  193	current_output(Old),
  194	open(File, append, New, [encoding(utf8)]),
  195	set_output(New),
  196	call(M, X),
  197	set_output(Old),
  198	close(New).
  199
  200% Prevents "stream... does not exist (already closed)" error
  201close_stream(Stream) :-
  202    (   is_stream(Stream)
  203    ->  close(Stream)
  204    ;   true
  205    ).
  206
  207read_stream_to_codes(Stream, Codes) :-
  208    fill_buffer(Stream),
  209    read_pending_codes(Stream, Codes, Tail),
  210    (   Tail == []
  211    ->  true
  212    ;   read_stream_to_codes(Stream, Tail)
  213    ).
  214
  215% Recommended by Jan.
  216
  217read_lines_as_atoms(Stream, Lines) :-
  218    read_string(Stream, "\n", "", Sep, String),
  219    (   Sep == -1
  220    ->  Lines = []
  221    ;   atom_string(Line, String),
  222        Lines = [Line|Rest],
  223        read_lines_as_atoms(Stream, Rest)
  224    ).
  225%
  226read_lines(Out, Lines) :-
  227    read_line_to_codes(Out, Line1),
  228    read_lines(Line1, Out, Lines).
  229
  230% read_lines(end_of_file, _, []) :- !.
  231read_lines(Codes, Out, [Line|Lines]) :-
  232    atom_codes(Line, Codes),
  233    read_line_to_codes(Out, Line2),
  234    read_lines(Line2, Out, Lines)