1:- module(file,
    2	  [file/3, combine_file/2, clean_io/3, posix_file_path/2,
    3%	   dsnap/3,
    4	   symbolic_link/2,
    5	   tmp_file_name/1,
    6	   cat_files_to_codes/3,
    7	   cat_files/2,
    8	   dict_of_files/1,
    9	   read_lines_as_atoms/2, read_lines/2
   10	   ]).   11
   12%;; (setq module-query  "qcompile(util(file)), module(file).")
   13% ?- qcompile(util(file)), module(file).
   14
   15:- use_module(pac(basic)).   16
   17:- meta_predicate file(+, ?, 0).   18:- meta_predicate file(+, ?, 0, ?).   19:- meta_predicate snap(1, ?).   20
   21		/**************
   22		*     file    *
   23		**************/
   24
   25%%% standard I/O (read/write/append) files
   26
   27file(X, Y, Z):- file(X,Y,Z,[encoding(utf8)]).
   28
   29file(X, Y, Z, Ops):- once(file_(X,Y,Z,Ops)).
   30
   31file_(F, M, A, Ops):-
   32        (	F = pipe(_) -> F0 = F
   33        ;	expand_file_search_path(F, F0)  -> true
   34		;	F0 = F
   35        ),
   36        open(F0, M, S, Ops),
   37        clean_io(S, M, A),
   38        close(S).
   39%
   40clean_io(F, read, A) :- !,
   41		current_input(Old),
   42		set_input(F),
   43        once(A),
   44		set_input(Old).
   45clean_io(F, _, A) :-
   46		current_output(Old),
   47		set_output(F),
   48        once(A),
   49		set_output(Old).
   50
   51f_pipe(Data, Pipe) :-
   52		file(	pipe(Pipe),
   53				write,
   54                basic:smash(Data),
   55                [encoding(octet)]). % was utf8
   56
   57combine_file(Ls, F) :-
   58	maplist(through_list_or_string, Ls, CombinedCodes),
   59	file(F, write, basic:smash(CombinedCodes)).
   60
   61% ?- posix_file_path('~', X).
   62% ?- posix_file_path('~/*', X). % fail.
   63posix_file_path(X, Y):- expand_file_name(X, L), L = [Y].
   64
   65%
   66cat_files(G, F):- atomic(G), !,
   67	cat_files([G], F).
   68cat_files(Fs, F):-
   69	tmp_file_stream(text, TMPfile, Stream),
   70    close(Stream),
   71	maplist(expand_file_name, Fs, Gs),
   72	cat_files_rec(Gs, TMPfile),
   73	expand_file_name(F, [F0|_]),
   74	rename_file(TMPfile, F0).
   75
   76cat_files_rec([], _).
   77cat_files_rec([X|Xs], T):- atomic(X), !,
   78	pshell(cat(X) >> T),
   79	cat_files_rec(Xs, T).
   80cat_files_rec([X|Xs], T):-
   81	cat_files_rec(X, T),
   82	cat_files_rec(Xs, T).
   83
   84%
   85cat_files_to_codes([], C, C).
   86cat_files_to_codes([P|Q], C, C0):-
   87    	read_file_to_codes(P, C, [tail(C1), encoding(utf8)]),
   88	cat_files_to_codes(Q, C1, C0).
   89
   90%
   91through_list_or_string(X, X):- (listp(X); string(X)), !.
   92through_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.
   96symbolic_link(Target, Link) :- 	expand_file_name(Link, [Link0]),
   97	(	read_link(Link0,_,_)
   98	 ->	true
   99 	 ;	expand_file_name(Target, [Target0]),
  100		eh:sh(ln(-s, Target0, Link0))
  101	),
  102	!.
  103
  104% tmp_file_name(File):- tmp_file_stream(text, File, Stream), close(Stream).
  105tmp_file_name(File):- tmp_file_stream(utf8, File, Stream), close(Stream).
  106
  107push_to_file(M, F):- expand_file_name(F, [F1]),
  108	(	exists_file(F1)
  109	-> 	tmp_file_name(T1),
  110		file(T1, write, M),
  111		tmp_file_name(T2),
  112		pshell(cat(T1, F) + ' > ' +  T2),
  113		rename_file(T2, F1),
  114		delete_file(T1)
  115	;	file(F1, write, M)
  116	).
  117
  118% ?- open_url('http://web.sfc.keio.ac.jp/~mukai/paccgi7/index.html', IN).
  119% sample coding
  120open_url(URL, In, Option) :-
  121        tmp_file_stream(text, File, Stream),
  122        close(Stream),
  123        process_create('/usr/bin/curl', ['-o', File, URL], []),
  124        open(File, read, In, Option),
  125        delete_file(File).  % Unix-only
  126%
  127open_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).

  136ignore_special((.)).
  137ignore_special((..)).
  138ignore_special(('.DS_Store')).
  139ignore_special(('.git')).
  140
  141%
  142dict_of_files(X):- directory_files((.), Files),
  143		directory_files(Files, X, []).
  144%
  145directory_files([], X, X).
  146directory_files([F|R], X, Y):- ignore_special(F), !,
  147	   directory_files(R, X, Y).
  148directory_files([D|R], [D-Z|X], Y):- exists_directory(D), !,
  149		directory_files(D, Files),
  150		working_directory(_, D),
  151		directory_files(Files, Z, []),
  152		working_directory(_, (..)),
  153		directory_files(R, X, Y).
  154directory_files([F|R], [F|X], Y):- directory_files(R, X, Y).
  155
  156		/**************
  157		*     snap    *
  158		**************/
  159
  160user:snap(C)  :- getenv(snapshot, File),
  161	do_snap(File, basic:smash, [C,"\n"]).
  162%
  163user:snap(M, C):- user:snap(M >> C).
  164%
  165user:snap(M, X, X):- basic:smash(X, X0), user:snap(["\n", M, "\n", X0]).
  166%
  167user:dsnap(X, X):- user:snap(X).
  168
  169%
  170do_snap(File, M, X):-
  171	current_output(Old),
  172	open(File, append, New, [encoding(utf8)]),
  173	set_output(New),
  174	call(M, X),
  175	set_output(Old),
  176	close(New).
  177
  178% Prevents "stream... does not exist (already closed)" error
  179close_stream(Stream) :-
  180    (   is_stream(Stream)
  181    ->  close(Stream)
  182    ;   true
  183    ).
  184
  185read_stream_to_codes(Stream, Codes) :-
  186    fill_buffer(Stream),
  187    read_pending_codes(Stream, Codes, Tail),
  188    (   Tail == []
  189    ->  true
  190    ;   read_stream_to_codes(Stream, Tail)
  191    ).
  192
  193% Recommended by Jan.
  194
  195read_lines_as_atoms(Stream, Lines) :-
  196    read_string(Stream, "\n", "", Sep, String),
  197    (   Sep == -1
  198    ->  Lines = []
  199    ;   atom_string(Line, String),
  200        Lines = [Line|Rest],
  201        read_lines_as_atoms(Stream, Rest)
  202    ).
  203%
  204read_lines(Out, Lines) :-
  205    read_line_to_codes(Out, Line1),
  206    read_lines(Line1, Out, Lines).
  207
  208read_lines(end_of_file, _, []) :- !.
  209read_lines(Codes, Out, [Line|Lines]) :-
  210    atom_codes(Line, Codes),
  211    read_line_to_codes(Out, Line2),
  212    read_lines(Line2, Out, Lines)