1:- module(eh, [
    2	       new_file/2,  new_base_name/2, counter/3,
    3	       assemble/2, expand_cgi_path/2,
    4	       boomerang/2,  getstring/1, include_text/2,
    5	       file_string/3,
    6	       getinfo_codes/2, getinfo_string/2, getinfo/2,
    7	       sh/1, pshell/1, qshell/1,
    8		   vector_term/3,
    9	       perform/4,
   10	       apply3/3,
   11	       choose_files/1, choose_folder/1,
   12		   run_shell/2, run_shell/3, dir/1, dired/2
   13			  ]).   14
   15% ?- misc:sh(open("/Users/cantor/Documents/Mac\\ Fan_OCR.pdf")).
   16% ?- A='/Users/cantor/Documents/Mac Fan_OCR.pdf', term_string(A, B), misc:sh(open(B)).
   17:- use_module(pac(basic)).   18:- use_module(util(obj)).   19:- use_module(pac(reduce)).   20:- use_module(util(file)).   21:- use_module(util('prolog-elisp')).   22:- use_module(util('emacs-jockey')).   23:- use_module(util('emacs-jockey2')).   24% :- expects_dialect(pac).
   25term_expansion --> pac:expand_pac.
   26:- use_module(pac(op)).   27%
   28:- set_prolog_flag(allow_variable_name_as_functor, true).
is True if R is unified with a standard output codes of a shell command S.
   34% ?- eh:getinfo('echo Hello', X).
   35% ?- eh:getinfo("echo Hello", X).
   36% ?- eh:getinfo_codes('echo Hello', X).
   37% ?- eh:getinfo("osascript -e 'return  POSIX path of (choose folder)'", X).
   38% ?- eh:getinfo("date +%Y-%m-%d", X).
   39% ?- eh:getinfo_codes("date +%Y-%m-%d", X), smash(X).
   40
   41% ?- run_command_to_codes([choosefolder], X, _, _),
   42%	atom_codes(A, X).
   43%@ X = [47, 85, 115, 101, 114, 115, 47, 99, 97|...],
   44%@ A = '/Users/cantor/Documents/texnotes/\n'.
   45
   46
   47% ?- run_command_to_codes([choosefolder], X, _, _).
   48%@ X = [47, 85, 115, 101, 114, 115, 47, 99, 97|...].
   49% ?- run_command_to_codes([echo, hello], X, _, _).
   50% ?- run_command_to_codes([osascript, " -e 'return  POSIX path of (choose folder)'"], X, _, _).
   51
   52%@ X = [].
   53
   54% ?- run_command_to_codes([doscript, echo,  hello], X, _, _).
   55
   56getinfo_codes(P, X):- file(pipe(P), read, getstring(X0)),
   57	( X0 == [] -> X = X0; append(X, [_], X0) ).
 getinfo_string(+S:atom/string, -R:string) is det
R is unified with a string for the standard output codes of a shell command S.
   63getinfo_string(P, X):- getinfo_codes(P, Codes),
   64					   string_codes(X, Codes).
is True if% R is unified with an atom/string as standard output of the shell command S.
   70%;; (setq module-query  "qcompile(util('emacs-hanlder')), module(eh).").
   71% ?- expand_file_name("~", [X]).
   72
   73getinfo(P, X):- getinfo_codes(P, X0),
   74		atom_codes(X, X0).
   75
   76%
   77done(_, _).
is True if X is unified with a folder name which you choose from a Finder window.
   83% ?- choose_folder(X).
   84% by Jan.
   85choose_folder(X) :- expand_file_name('~/local/bin/choose-folder.scpt', SCPT),
   86                setup_call_cleanup(
   87                    process_create(path(osascript), [SCPT],
   88                                   [ stdout(pipe(Out)), stderr(null)
   89                                   ]),
   90                    read_lines_as_atoms(Out, X),
   91                    close(Out)).
Strings is unified with a list of atoms which is the standard output of the unix command Com.
   98% ?- run_shell(echo, ["hello world\n"], Out).
   99% ?- run_shell(echo, ["hello\n", "world\n"], Out).
  100% ?- run_shell(echo, ["hello", "world\n"], Out).
  101run_shell(Com, Args, Strings) :-
  102	            setup_call_cleanup(
  103                    process_create(path(Com), Args,
  104                                   [ stdout(pipe(PipeOut)), stderr(null)
  105                                   ]),
  106                    read_lines_as_atoms(PipeOut, Strings),
  107                    close(PipeOut)).
run unix command Com with arguments Args.
  112% ?- run_shell(echo, ["hello world\n"]).
  113% ?- run_shell(rmdir, ['/Users/cantor/Desktop/deldel']).
  114% ?- run_shell(mkdir, ["$HOME/Desktop/deldel"]).
  115run_shell(Com, Args) :-
  116           process_create(path(Com), Args,
  117                          [stdout(null), stderr(null)]).
is True if X is unified with a file name which you choose from a Finder window.
  124% ?- choose_files(X), maplist(writeln, X).
  125choose_files(X) :-
  126				expand_file_name('~/local/bin/choose-files.scpt', SCPT),
  127				run_shell(osascript, [SCPT], X).
Repeats cycles of read / act / write on stadanrd I/O.
  132scriptstart :-
  133 	prompt(_, ''),
  134 	current_input(In),
  135 	set_stream(In, encoding(utf8)),
  136 	current_output(Out),
  137 	set_stream(Out, encoding(utf8)),
  138    process_loop.
  139
  140process_loop :- catch(process_step, E, handle_exception(E)),
  141  	process_loop.
  142
  143%
  144process_step :-	once(read_term_from_lisp(C)),
  145	(	phrase(C, _, R)
  146	->	insert_buffer(R)
  147	;	insert_buffer("fail")
  148	).
  149
  150%
  151handle_exception(E) :- smash(["exception: ",  E], M),
  152			message(M),
  153			lisp('start-emacshandler'()).
is True if Y is unified with the value of F(X) when A(X) is true; otherwise with X.
  159% ?-  eh:maplist(filter(atom, atom_codes), [a,f(b), c], X).
  160%@ X = [[97], f(b), [99]].
  161filter(F, A, X, Y):- call(F, X) -> call(A, X, Y); Y=X.
  162
  163term(F, X, Y, Z):- Z=..[F, X, Y].
  164
  165
  166% ?- qcompile(util('emacs-handler')).
  167% ?- module(eh).
is True if Y is unified with the argument list of X folded by F with initial value I.
  173% ?- eh:termrec(plus, 0, f(1,2,3,5,6,7), SumOfArgs).
  174:- meta_predicate termrec(3, ?, ?, ?).  175termrec(F, I, X, Y) :- functor(X,_,N),
  176	termrec(F, 0, N, X, I, Y).
  177
  178termrec(_, N, N, _, V, V) :-!.
  179termrec(F, J, N, X, V, Y) :- J1 is J + 1,
  180	arg(J1, X, A),
  181	call(F, A, V, V1),
  182	termrec(F, J1, N, X, V1,Y).
is True if T1 is unified with the argument list of T, and N1 with N, folded together by A.
  189% ?-  eh:termrec(pred([I, J, X, a(X)]:- J is I + X), f(1,2,3,5,6,7), H, 0, S).
  190:- meta_predicate termrec(4, ?, ?, ?,?).  191termrec(A, T, T1, N, N1):- functor(T, Fun, Ar),
  192	functor(T1, Fun, Ar),
  193	termrec(A, 0, Ar, T, T1, N, N1).
  194
  195%
  196termrec(_, M, M, _, _, N, N) :- !.
  197termrec(A, J, M, T, T1, N, N1) :- J1 is J + 1,
  198    arg(J1, T, B),
  199    arg(J1, T1, C),
  200    call(A, N, N2, B, C),
  201    termrec(A, J1, M, T, T1, N2, N1).
  202%
  203power(P) --> maplist(phrase(P)).
is True if Y is unified with the value of applying F as an extended phrase to X.
  209phrase_on_car(X, [Y0|Z], [Y|Z]) :- once(perform([], X, Y0, Y)).
  210
  211% ?- eh:perform([], (=, =, =), a, X).
  212% ?- perform([], seqcal: (p2q,raster,rasterx), p(right(+),[]>>[a+ (!a)],[p(right(!),[]>>[a,!a],[p(axiom,[a]>>[a])])]), X), smash(X).
  213% :- meta_predicate perform(?,:,?,?).
  214perform(_, eval, X, Y):- eval(X, Y).
  215perform(_, true, X, X).
  216perform(Ms, M:A, X, Y):-	perform([M|Ms], A, X, Y).
  217perform(M, (A; _), X, Y):-	perform(M, A, X, Y).
  218perform(M, (_; A), X, Y):-	perform(M, A, X, Y).
  219perform(M, (A, B), X, Y):-	perform(M, A, X, Z), perform(M, B, Z, Y).
  220perform([], A, X, Y):-		call(A, X, Y).
  221perform([M|_], A, X, Y):-	call(M:A, X, Y).
  222
  223% % Prolog on emacs buffer
  224% /** ::prolog
  225%  append(X, Y,[a,b,c]), X=[_,_]
  226% **/
  227
  228% module_prefix_for_expand(eh).
  229module_prefix_for_expand(user).
  230
  231prolog --> solve_bind.
  232
  233solve_bind_once --> solve_bind, !.
  234
  235solve_bind -->  herbrand(Bind),
  236	current(X),
  237	{	module_prefix_for_expand(Mod),
  238		once(pac:expand_goal(X, Mod, Y, P, [])),
  239		maplist(assert, P),
  240		solve(Y)
  241	},
  242	peek(Bind),
  243	term_codes.
  244
  245%
  246solve((X,Y)):- solve(X), solve(Y).
  247solve(X):- call(X).
  248
  249%
  250phrase(C, G, X, Y) :- call(C, call(G, X, Y)).
  251
  252% %
  253% once(G)--> phrase(once, G).
  254
  255% once(G, U, L0, L) :- once(call(G, U, L0, L)).
  256
  257% % once(G, X, X0) --> phrase(once, call(G, X, X0)).
  258% once(G, X, X0, L0, L) :- once(call(G, X, X0, L0, L)).
  259
  260
  261% a la cd command
  262% ?- eh:walk_on_tree(up, [a,b,c], X).
  263% ?- eh:walk_on_tree(up_down([x,y]), [a,b,c], X).
  264
  265walk_on_tree(up, X, Y):- !,  (append(Y, [_], X) -> true; Y=X).
  266walk_on_tree(down(A), X, Y):- !,  append(X, A, Y).
  267walk_on_tree(up_down(A), X, Y):-  walk_on_tree(up, X, X0),
  268	walk_on_tree(down(A), X0,  Y).
  269
  270%
  271% ?- eh:change_unix_path(up, "/a", X).
  272%@ X = "".
  273
  274% ?- eh:change_unix_path(up, "/ab/cd/ef", X).
  275% ?- eh:change_unix_path(down("x/y"), "/ab/cd/ef", X).
  276%@ X = "/ab/cd/ef/x/y/".
  277% ?- eh:change_unix_path(up_down("x/y"), "/ab/cd/ef", X).
  278%@ X = "/ab/cd/x/y/".
  279
  280change_unix_path(up, P, Q):-  !, path_to_list(P, X),
  281	walk_on_tree(up, X, Y),
  282	path_to_list(Q, Y).
  283change_unix_path(down(A), P, Q):-  !,
  284	path_to_list(A, Z),
  285	path_to_list(P, X),
  286	walk_on_tree(down(Z), X, Y),
  287	path_to_list(Q, Y).
  288change_unix_path(up_down(A), P, Q):-
  289	path_to_list(A, Z),
  290	path_to_list(P, X),
  291	walk_on_tree(up_down(Z), X, Y),
  292	path_to_list(Q, Y).
  293
  294% ?- eh:path_to_list("/", X).
  295% ?- eh:path_to_list(A, []).
  296% ?- eh:path_to_list(A, [a]).
  297% ?- eh:path_to_list(A, [a,b]).
  298
  299path_to_list(A, X):- nonvar(A), !,
  300	atomics_to_string(Y, (/), A),
  301	remove_null(Y, X).
  302path_to_list(A, X):- remove_null(X, X0),
  303	list_to_unix_path(X0, A).
  304
  305%
  306list_to_unix_path([], "/"):- !.
  307list_to_unix_path(X,  A):-  append([[""],X,[""]], X0),
  308	atomics_to_string(X0, "/",  A).
  309
  310%
  311remove_null([''|A], B):-!, remove_null(A, B).
  312remove_null([""|A], B):-!, remove_null(A, B).
  313remove_null([X|A], [X|B]):- remove_null(A, B).
  314remove_null([], []).
  315
  316
  317% [2015/12/28]
  318file_string(File, Length, String):-  open(File, read, Stream, [encoding(utf8)]),
  319			     read_string(Stream, Length, String),
  320			     close(Stream).
  321%
  322file_string(File, String):- file_string(File, _, String).
  323
  324%
  325getstring(X) :- get_code(C),
  326	(C == -1 -> X=[] ; X=[C|Y], eh:getstring(Y)).
  327
  328putstring(X) :- maplist(put_code, X).
  329
  330getline(X) :- get_code(C),
  331	((C == -1; C==0'\n) -> X=[] ; X=[C|Y], getline(Y)).
  332
  333putline(X) :- smash(X), put_code(0'\n).
 assemble(L:list, F:stream) is det
True when all elements of L have been written to F. text(T) -- T as text. file(G) -- the contents of G region -- the current buffer region buffer -- the current whole buffer
  344assemble(Fs, F) :- expand_file_search_path(F, F1),
  345        open(F1, write, FX, [encoding(utf8)]),
  346        maplist(assemble_basic(FX), Fs),
  347        close(FX).
  348
  349assemble_basic(FX, text(F)) :- !, clean_io(FX, write, basic:smash(F)).
  350assemble_basic(FX, file(F)) :- !, expand_file_search_path(F, F1),
  351        open(F1, read, FY, [encoding(utf8)]),
  352        clean_io(FY, read, eh:getstring(D)),
  353        maplist(put_code(FX), D).
  354assemble_basic(FX, codes(Codes)) :-!, maplist(put_code(FX), Codes).
  355assemble_basic(FX, region(Codes)):-!, maplist(put_code(FX), Codes).
  356assemble_basic(FX, buffer) :-
  357	call_lisp(list('point-min'(), 'point-max'()), string(L)),
  358	list_number_list(L, [Min, Max]),
  359	get_buffer_region(Min, Max, R),
  360	maplist(put_code(FX), R).
  363mac_open(F):-  pshell(open(F)).
  364
  365mac_open(F, F):- mac_open(F).
  366
  367mac_open(P, F, F):- mac_open_prefix(P, F).
  368
  369mac_open_prefix(_, F):- prefix_chk(`/`, F ), !, mac_open(F).
  370mac_open_prefix(_, F):- prefix_chk(`~`, F), !,	mac_open(F).
  371mac_open_prefix(Prefix, F):- mac_open(Prefix+ '/'+ F).
  372
  373prefix_chk(Prefix, String):- append(Prefix, _, String).
  374
  375:- meta_predicate wild_map(1,?).  376wild_map(M, W):- expand_file_name(W, L0), maplist(M, L0).
  377
  378:- meta_predicate wild_map(2,?,?).  379wild_map(M, W, L):- expand_file_name(W, L0), maplist(M, L0, L).
  380
  381wild_open(Wildcard):- wild_map(pred([X] :- pshell(open(X))), Wildcard).
  382
  383		/******************************
  384		*     counter file handler    *
  385		******************************/
 counter_general(+P:pred, +X:obj, -Y:obj) is det
Manage a counter file depending on P new -- new counter check -- check existence. update -- increment the content by 1.
  393:- meta_predicate counter_general(1, ?, ?).  394
  395counter_general(FileProp)	-->  obj:obj_get([counter_name(C), directory(D)]),
  396{
  397	pshell(mkdir(-p, D)), !,
  398	setup_call_cleanup(	working_directory(Old, D),
  399				call(FileProp, C),
  400				working_directory(_, Old))
  401}.
 counter(+P, +X, -Y) is det
Perform action P on a file X to unify Y with the result.
  406counter(new)	-->
  407	counter_general(pred([C] :- file(C, write, format("~w.~n", [0])))),
  408	obj_put([count(0)]).
  409counter(update) --> counter_general(exists_file), !,
  410	 obj:obj_get([counter_name(C), directory(D)]),
  411	{	working_directory(Old, D),
  412		file(C, read, read(V1)),
  413		V is (V1 + 1) mod 100,
  414		file(C, write, format("~w.~n",[V])),
  415		working_directory(_, Old)
  416	},
  417	obj_put([count(V)]).
  418counter(update) --> counter(new).
 new_file(+X, -Y) is det
Create a new file according to X, and unify Y with the result.
  423new_file --> obj:obj_get([ stem(R), directory(D) ] ),
  424        counter(update),
  425        obj:obj_get([count(N)]),
  426        {	atomic_list_concat([R,  N], B),
  427		atomic_list_concat([D,  / , B], F)
  428        },
  429        obj_put([base(B), file(F)]).
 new_file_here(+X, -Y) is det
Create a new file at the current directory.
  434new_file_here	--> obj_get([stem(R), count(N)]),
  435        { atomic_list_concat([R,  N], B) },
  436        obj_put([base(B)]).
 new_base_name(+X, -Y) is det
Create a new file according to X, and unify Y with the result.
  441new_base_name -->
  442        counter(update),
  443        obj_get([count(N), stem(R), directory(D)]),
  444        {	atomic_list_concat([R,  N], B),
  445		atomic_list_concat([D,  / , B], F)
  446        },
  447        obj_put([base(B), file(F)]).
 dir_open(+X, -Y) is det
Open the file X, and unify Y with X.
  452dir_open	--> obj_get([directory(D)]),
  453	{	pshell(open(D))	}.
 dir_open(+D) is det
Open the directory D.
  458dir_open(D):-	dir_open([directory(D)], _).
 expand_cgi_path(+X, -Y) is det
Expand a CGI path in X, and unify Y with X.
  463expand_cgi_path(X, Y):-
  464	getenv(http_cgi_bin, CB),
  465    expand_path(CB, X, Y).
 expand_cgi_path(+P, +X, -Y) is det
Expand a CGI path under the current home directory in X, and unify Y with X.
  471expand_path(P, X, Y):-  getenv(user, Name),
  472        smash([`/~`, Name, `/`,  P, `/`, X], Y).
 include_text(+X, -Y) is det
Read as string from a file X into Y.
  477include_text(X,Y) :- once(filepath(X,P)), file(P, read, getstring(Y)).
 include_text(+L, -Y) is det
Read as strings from all files in X into Y.
  482include_text(A)--> {listp(A) -> L = A; L = [A]}, peek(L),
  483		   maplist(include_text).
 filepath(+X, -Y) is det
Expand a file path X into Y.
  488filepath(X,X) :- atomic(X), !.
  489filepath(A,X) :- A=..[P|A1],
  490     ( P= (/) ->  Q = [ /|A1] ; dir(P, D), Q = [D, /|A1] ),
  491     atomic_list_concat(Q, X).
  492filepath(A,X) :- expand_file_search_path(A, X).
  493
  494% some handy
  495singleton(X,[X]).
  496comma((X, Y), X, Y).
  497args(X, A, B):- arg(1, X, A), arg(2, X, B).
  498image(R, S) :- maplist(snd, R, S).
  499%
  500vector_term(_, [X], X).
  501vector_term(F, [X, Y|Z], U):- vector_term(F,[Y|Z], X0), U=..[F, X, X0].
  502
  503%
  504wrap(X, Y, A, [X,A,Y] ).
Goto Dir, do ShellCom, then go back to the original directory.
  509boomerang(Dir, ShellCom):- sh(cd(Dir); ShellCom).
  510
  511same_atom(X, Y, "yes"):- atom_codes(X, Y).
  512same_atom(_, _, "no").
  513
  514backquote_string(X) :- string_codes(X, [96]).
  515
  516
  517sh(X) :- pshell(X, [path, c, q]).
  518
  519% ?- pshell(ls, [c, q, path]).
  520% ?- pshell(ls, [path]).
  521% ?- pshell(echo("$PATH") > "~/Desktop/PATH").
  522% ?- pshell("update-all").
  523% ?- pshell("update-swipl").
  524
  525pshell(X, Opts):-
  526	(	memberchk(path(V), Opts)
  527	->	T0 = shell( "PATH=" + V ; X)
  528	;	T0 = shell(X)
  529	),
  530	(	memberchk(q, Opts)
  531	->  T1 = T0 + " >> /dev/null 2>&1"
  532	;	T1 = T0
  533	),
  534	misc:shell_string(T1, T2),
  535	(	memberchk(c, Opts)
  536	->	term_string(T2, T3),
  537		T4 = "/bin/sh -c " + T3
  538	;   T4 = T2
  539	),
  540	misc:shell_string(T4, S),
  541	shell(S).
  542
  543% ?- pshell(ls).
  544% ?- pshell(pwd).
  545% pshell(T):- misc:shell_string(T, S), shell(S).
  546pshell(T):- pshell(T, []).
  547
  548% pshell in quiet mode.
  549% ?- qshell(ls).
  550% ?- qshell(pwd).
  551qshell(X):- pshell(X,  [q]).
  552
  553:-meta_predicate(directory(?, 0)).  % <= neccessary dcl.
  554directory(D, A):-
  555	working_directory(Old, D),
  556	call(A),
  557	working_directory(_, Old).
  558%  ?- ls_pdf_files(L).
  559%  ?- ls_pdf_files(_, L), smash(L).
  560%  ?- ls_files_suffix(['.pdf'], L).
True when L is unified with a list of pdf files in the current folder.
  564ls_pdf_files(_, L)	:- ls_pdf_files(L0), insert("\n", L0, L).
 ls_pdf_files(L:list) is det
True when L is unified with a list of pdf files in the current folder.
  568ls_pdf_files(L)		:- ls_files(suffix([".pdf"]), L).
 ls_files_suffix(S, L:list) is det
True when L is unified with a list of files in the current directory wich a suffix S.
  572ls_files_suffix(S, L)	:- ls_files(suffix(S), L).
 suffix(+S:string, X:string) is det
True if S is a suffix of L.
  576suffix(S, X):- sub_string(X, _, _, 0, S).
is True if L is unified with the list of files filtered by F.
  582% ?- eh:directory_filter(pred(([X]:- sub_string(X, _, 3, 0, ".pl"))), PDFs).
  583:- meta_predicate directory_filter(1, ?).  584directory_filter(Filter, Fs):- ls_objects(FS0), collect(Filter, FS0, Fs).
 ls_files(Filter:pred/1, L:list) is det
True when L is unfified with names of files in the current folder that satisfies Filter.
  589ls_files(Filter, L):- directory_filter(exists_file, L0),
  590	collect(Filter, L0, L).
 ls_files(L:list) is det
True when L is unfified with names of files in the current folder
  594ls_files(L):- directory_filter(exists_file, L).
 ls_dirs(Filter:pred/1, L:list) is det
True when L is unfified with names of files in the current folder that satisfies Filter.
  599ls_dirs(Filter, L):- directory_filter(exists_directory, L0),
  600	collect(Filter, L0, L).
 ls_dirs(L:list) is det
True when L is unfified with names of files in the current folder
  604ls_dirs(L):- directory_filter(exists_directory, L).
 ls_files_dirs(Fs:list, Ds:list) is det
True when Fs and Ds are unfified with names of files and directories, repectively, in the current folder
  609ls_files_dirs(Fs, Ds):- ls_objects(A), object_classify(A, Fs, Ds).
 ls(-F:list, -D:list) is det
True if F and L are unified with a list of files and directoires, respectively, in the current directory.
  616% ?- eh:ls(X, Y).
  617% ?- working_directory(_, "/Users/cantor"), eh:ls(X, Y).
  618
  619ls --> ls_files_dirs.
 ls_object(A:list) is det
True if A is unifed with a list of files and directoires. ?- eh:ls_objects(A), maplist(writeln, A).
  624ls_objects(A):- getinfo_codes(ls, X),
  625	(X==[]
  626	-> A = []
  627	;  once(split(X, X0)), maplist(atom_codes, A, X0)
  628	).
  629
  630%
  631object_classify([], [], []).
  632object_classify([A|As], [A|Xs], Ys):- exists_file(A), !,
  633	object_classify(As, Xs, Ys).
  634object_classify([A|As], Xs, [A|Ys]):- object_classify(As, Xs, Ys).
  635
  636%
  637set_dir(X, Y):- working_directory(X, Y).
  638set_dir(X) :- working_directory(_, X).
  639
  640%
  641get_dir(X) :- working_directory(X, X).
 excursion(A:pred/0) is det
True if save the current directory, do the action A, and restore the saved directory.
  647excursion(A):-  get_dir(D), call(A), set_dir(D).
 dir_tree(L:list) is det
True when L is unifed with a directory structure of the current directory. The directory structure is a list of elements of the form f(x) or d(y, z), where x is a filename, y a directory name, and z a directory structure.

?- eh:dir_tree(L), maplist(writeln, L).

  658dir_tree(L):- ls(Fs, Ds),
  659	maplist(unary(f), Fs, Gs),
  660	maplist(excursion_dir_tree, Ds, Es),
  661	append(Gs, Es, L).
  662
  663dir_tree(P, L):- excursion((set_dir(P), dir_tree(L))).
  664
  665excursion_dir_tree(N, d(P, L)):-
  666	get_dir(P0),
  667	atomic_list_concat([P0,N,(/)], P),
  668	excursion((set_dir(P), dir_tree(L))).
  669%
  670unary(F, T)	:- functor(T, F, 1).
  671unary(F, A, T)	:- T =.. [F, A].
 map_directory(Act:goal) is det
True if Act is applied to each object in the current directory. ?- expand_file_name('~/', [H]), eh:(working_directory(_, H), map_directory(pred([X]:- writeln(X)))).
  677:- meta_predicate map_directory(:).  678map_directory(Act):- ls_objects(Fs), maplist(check_do(Act), Fs).
  679
  680check_do(true, _):- !.
  681check_do(false, _):- !, fail.
  682check_do((A, B), X):- !,  check_do(A, X), check_do(B, X).
  683check_do((A; B), X):- !, once(check_do(A, X); check_do(B, X)).
  684check_do(\+ A , X):- !, \+ check_do(A, X).
  685check_do(A->B , X):- !, (check_do(A, X) -> check_do(B, X)).
  686check_do(A , X):- call(A, X).
  687
  688%! escape_posix_file_name_char(+X:text, -Y:text) is det
  689%	True if Y is unified with a copy of X in which
  690%	special characters in X are escaped so that  Y is
  691%	safe for posix file name.
  692% ?- ejockey:escape_posix_file_name_char(`a : (b)`, R), atom_codes(A, R), smash(R).
  693%@ a \@ \(b\)
  694%@ R = [97, 32, 92, 64, 32, 92, 40, 98, 92, 41],
  695%@ A = 'a \\@ \\(b\\)' .
  696escape_posix_file_name_char(X, Y):-
  697  foldr(pred(	[0'(,  U, [0'\\,    0'(  | U]	] &
  698		[0'),  U, [0'\\,    0')  | U]	] &
  699		[0'\', U, [0'\\,    0'\' | U]	] &
  700		[0':,  U, [0'\\,    0'@  | U]	] &
  701		[0'/,  U, [0'\\,    0'@  | U]	] &
  702		[A,    U, [A|U]			]
  703	    ),
  704	X, [], Y).
  705
  706%'
  707%!  r_act_plus(+F:pred/3, +L:list, -Y:term) is det
  708%	True if
  709%  Y is unified with the folded L by F from the right,
  710%  so that Y is a right branching binary tree.
  711% ?- eh:foldl(variant(term(+)), [b,c,d], a, Y).
  712%@ Y = a+b+c+d.
  713:- meta_predicate r_act_plus(3, ?, ?).  714r_act_plus(F, Xs, V) :- r_act_plus(F, Xs, _, V).
is True if Y is unified with the folded L by F from the right, and X with the last element of L, so that Y is a binary tree with descendants on right branches only.

?- eh:r_act_plus(term(+), [a,b,c], X, Y). @ X = c, @ Y = a+ (b+c).

  726% ?- eh:r_act_plus(term(+), [a,b,c,d], X, Y).
  727% ?- eh:r_act_plus(term(+), [1, 2, 3], X).
  728% ?- eh:r_act_plus(variant(term(+)), [1, 2, 3], X).
  729% ?- eh:r_act_plus(cons, [1, 2, 3], X).
  730:- meta_predicate r_act_plus(3, ?, ?, ?).  731r_act_plus(_, [X], X, X):-!.
  732r_act_plus(F, [A|As], X, Y) :- call(F, A, Y0, Y),
  733	r_act_plus(F, As, X, Y0).
 apply(P:pred, Xs:[A1,...,An], V:term) is nondet
True when apply(P, [A1,...,An, V]) is true.
  739%  ?- eh:apply(append([a,b]),[[c,d]], R).
  740%@ R = [a, b, c, d].
  741
  742:- meta_predicate apply3(:, ?, ?).  743
  744apply3(A, Xs, V):-  apply_(Xs, A, V).
  745
  746%
  747apply_([], A, V)		:- !, call(A, V).
  748apply_([X], A, V)		:- !, call(A, X, V).
  749apply_([X, Y], A, V)	:- !, call(A, X, Y, V).
  750apply_([X, Y, Z], A, V)	:- !, call(A, X, Y, Z, V).
  751apply_([X, Y, Z, U], A, V)	:- !, call(A, X, Y, Z, U, V).
  752apply_(Xs, A, V)		:- append(Xs, [V], Args),  apply(A, Args).
is True if for X = f(a1,..., an), Y is unified with a term f(b1,...,bn) where call(F, ai, bi) is recursively true. mapleaves/3 is a recursive version of mapterm/3.
  759% ?- eh:mapleaves(pred([X,[X,X]]), f(a,[u,v], b([1,2])), R).
  760
  761:- meta_predicate mapleaves(2, ?, ?).  762mapleaves(F, M:X, M:Y) :- !, mapleaves(F, X, Y).
  763mapleaves(F, X, Y) :- ala_list(X), !,
  764	maplist(mapleaves(F), X, Y).
  765mapleaves(F, X, Y) :- atomic(X),  !, call(F, X, Y).
  766mapleaves(F, X, Y) :- functor(X, A, N),
  767	functor(Y, A, N),
  768	mapleaves(0, N, F, X, Y).
  769
  770:- meta_predicate mapleaves(?,?,2,?,?).  771mapleaves(N, N, _ , _ , _) :- !.
  772mapleaves(I, N, F, X, Y):- J is I + 1,
  773	arg(J, X, Z),
  774	arg(J, Y, U),
  775	mapleaves(F, Z, U),
  776	mapleaves(J, N, F, X, Y).
is True if for X = f(a1,..., an), call(F, ai) is true for all ai. mapleaves/2 is a recursive version of mapterm/2.
  783% ?-  eh:mapleaves(mapleaves(writeln), f(g(a), [c,x(j),e], h(b))).
  784:- meta_predicate mapleaves(1, ?).  785mapleaves(F, _:X) :- !, mapleaves(F, X).
  786mapleaves(F, X) :- is_list(X), !, maplist(mapleaves(F), X).
  787mapleaves(F, X) :- atomic(X),  !, call(F, X).
  788mapleaves(F, X) :- functor(X, _, N), mapleaves(0, N, F, X).
  789
  790%
  791mapleaves(N, N, _, _) :- !.
  792mapleaves(I, N, F, X) :- J is I + 1,
  793	arg(J, X, Z),
  794	mapleaves(F, Z),
  795	mapleaves(J, N, F, X).
  796
  797
  798		/****************************************
  799		*     accessing favorite directories    *
  800		****************************************/
 setup_candidate(+A:string, +P:pred/1) is det
Collect all directory names specified by P, send the list to the lisp so that it is bound to A as a lisp atom.
  807:- meta_predicate setup_candidate(?,1).  808setup_candidate(SetVar, Pred) :-
  809	setof(D, call(Pred, D), S),
  810	maplist(atom_string, S, Cs),
  811	call_lisp_wait(setq(SetVar, #(Cs))),
  812 	atom_string(SetVar, SetVarName),
  813	atomics_to_string(["variable ", SetVarName, " has been set."], String),
  814	call_lisp_wait(message(String)).
  815
  816%
  817dir(X):- config:dir_data(X, _).
 dired(?X, ?Y) is det
Get a directory from lisp by completing-read with candidate list 'dir-set', expand the directory name, and ask lisp to open by 'dired' command. Y is unified with X.
  824dired --> { call_lisp(
  825		prompt("directory name ",
  826			#('dir-set')),
  827			[value(D0), string(t)]),
  828	  term_codes(T, D0),
  829	  atom_string(A, T),
  830	  config:expand_dir_name(A, D),
  831	  lisp(dired(D))
  832	  }