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, xsh/1, pshell/1, pshell/2, 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% ?- xsh(open("/Users/cantor/.zshrc")).
   15% ?- xsh([open, "/Users/cantor/deldel"]).
   16% ?- xsh([ls, -al, "/Users/cantor/"] > "~/deldel").
   17% ?- A='/Users/cantor/Documents/Mac Fan_OCR.pdf', term_string(A, B), misc:sh(open(B)).
   18
   19:- use_module(pac(basic)).   20:- use_module(util(obj)).   21:- use_module(pac(reduce)).   22:- use_module(util(file)).   23:- use_module(util(misc)).   24:- use_module(util('prolog-elisp')).   25:- use_module(util('emacs-jockey')).   26:- use_module(util('emacs-jockey2')).   27% :- expects_dialect(pac).
   28term_expansion --> pac:expand_pac.
   29:- use_module(pac(op)).   30%
   31:- 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.
   37% ?- eh:getinfo('echo Hello', X).
   38% ?- eh:getinfo("echo Hello", X).
   39% ?- eh:getinfo_codes('echo Hello', X).
   40% ?- eh:getinfo("osascript -e 'return  POSIX path of (choose folder)'", X).
   41% ?- eh:getinfo("date +%Y-%m-%d", X).
   42% ?- eh:getinfo_codes("date +%Y-%m-%d", X), smash(X).
   43
   44% ?- run_command_to_codes([choosefolder], X, _, _),
   45%	atom_codes(A, X).
   46%@ X = [47, 85, 115, 101, 114, 115, 47, 99, 97|...],
   47%@ A = '/Users/cantor/Documents/texnotes/\n'.
   48
   49
   50% ?- run_command_to_codes([choosefolder], X, _, _).
   51%@ X = [47, 85, 115, 101, 114, 115, 47, 99, 97|...].
   52% ?- run_command_to_codes([echo, hello], X, _, _).
   53% ?- run_command_to_codes([osascript, " -e 'return  POSIX path of (choose folder)'"], X, _, _).
   54
   55%@ X = [].
   56
   57% ?- run_command_to_codes([doscript, echo,  hello], X, _, _).
   58
   59getinfo_codes(P, X):- file(pipe(P), read, getstring(X0)),
   60	( 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.
   66getinfo_string(P, X):- getinfo_codes(P, Codes),
   67					   string_codes(X, Codes).
is True if% R is unified with an atom/string as standard output of the shell command S.
   73%;; (setq module-query  "qcompile(util('emacs-hanlder')), module(eh).").
   74% ?- expand_file_name("~", [X]).
   75
   76getinfo(P, X):- getinfo_codes(P, X0),
   77		atom_codes(X, X0).
   78
   79%
   80done(_, _).
is True if X is unified with a folder name which you choose from a Finder window.
   86% ?- choose_folder(X).
   87% by Jan.
   88choose_folder(X) :- expand_file_name('~/local/bin/choose-folder.scpt', SCPT),
   89                setup_call_cleanup(
   90                    process_create(path(osascript), [SCPT],
   91                                   [ stdout(pipe(Out)), stderr(null)
   92                                   ]),
   93                    read_lines_as_atoms(Out, X),
   94                    close(Out)).
Strings is unified with a list of atoms which is the standard output of the unix command Com.
  101% ?- run_shell(echo, ["hello world\n"], Out).
  102% ?- run_shell(echo, ["hello\n", "world\n"], Out).
  103% ?- run_shell(echo, ["hello", "world\n"], Out).
  104run_shell(Com, Args, Strings) :-
  105	            setup_call_cleanup(
  106                    process_create(path(Com), Args,
  107                                   [ stdout(pipe(PipeOut)), stderr(null)
  108                                   ]),
  109                    read_lines_as_atoms(PipeOut, Strings),
  110                    close(PipeOut)).
run unix command Com with arguments Args.
  115% ?- run_shell(echo, ["hello world\n"]).
  116% ?- run_shell(rmdir, ['/Users/cantor/Desktop/deldel']).
  117% ?- run_shell(mkdir, ["$HOME/Desktop/deldel"]).
  118run_shell(Com, Args) :-
  119           process_create(path(Com), Args,
  120                          [stdout(null), stderr(null)]).
is True if X is unified with a file name which you choose from a Finder window.
  127% ?- choose_files(X), maplist(writeln, X).
  128choose_files(X) :-
  129				expand_file_name('~/local/bin/choose-files.scpt', SCPT),
  130				run_shell(osascript, [SCPT], X).
Repeats cycles of read / act / write on stadanrd I/O.
  135scriptstart :-
  136 	prompt(_, ''),
  137 	current_input(In),
  138 	set_stream(In, encoding(utf8)),
  139 	current_output(Out),
  140 	set_stream(Out, encoding(utf8)),
  141    process_loop.
  142
  143process_loop :- catch(process_step, E, handle_exception(E)),
  144  	process_loop.
  145
  146%
  147process_step :-	once(read_term_from_lisp(C)),
  148	(	phrase(C, _, R)
  149	->	insert_buffer(R)
  150	;	insert_buffer("fail")
  151	).
  152
  153%
  154handle_exception(E) :- smash(["exception: ",  E], M),
  155			message(M),
  156			lisp('start-emacshandler'()).
is True if Y is unified with the value of F(X) when A(X) is true; otherwise with X.
  162% ?-  eh:maplist(filter(atom, atom_codes), [a,f(b), c], X).
  163%@ X = [[97], f(b), [99]].
  164filter(F, A, X, Y):- call(F, X) -> call(A, X, Y); Y=X.
  165
  166term(F, X, Y, Z):- Z=..[F, X, Y].
  167
  168% ?- qcompile(util('emacs-handler')).
  169% ?- module(eh).
is True if Y is unified with the argument list of X folded by F with initial value I.
  175% ?- eh:termrec(plus, 0, f(1,2,3,5,6,7), SumOfArgs).
  176:- meta_predicate termrec(3, ?, ?, ?).  177termrec(F, I, X, Y) :- functor(X,_,N),
  178	termrec(F, 0, N, X, I, Y).
  179
  180termrec(_, N, N, _, V, V) :-!.
  181termrec(F, J, N, X, V, Y) :- J1 is J + 1,
  182	arg(J1, X, A),
  183	call(F, A, V, V1),
  184	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.
  191% ?-  eh:termrec(pred([I, J, X, a(X)]:- J is I + X), f(1,2,3,5,6,7), H, 0, S).
  192:- meta_predicate termrec(4, ?, ?, ?,?).  193termrec(A, T, T1, N, N1):- functor(T, Fun, Ar),
  194	functor(T1, Fun, Ar),
  195	termrec(A, 0, Ar, T, T1, N, N1).
  196
  197%
  198termrec(_, M, M, _, _, N, N) :- !.
  199termrec(A, J, M, T, T1, N, N1) :- J1 is J + 1,
  200    arg(J1, T, B),
  201    arg(J1, T1, C),
  202    call(A, N, N2, B, C),
  203    termrec(A, J1, M, T, T1, N2, N1).
  204%
  205power(P) --> maplist(phrase(P)).
is True if Y is unified with the value of applying F as an extended phrase to X.
  211phrase_on_car(X, [Y0|Z], [Y|Z]) :- once(perform([], X, Y0, Y)).
  212
  213% ?- eh:perform([], (=, =, =), a, X).
  214% ?- perform([], seqcal: (p2q,raster,rasterx), p(right(+),[]>>[a+ (!a)],[p(right(!),[]>>[a,!a],[p(axiom,[a]>>[a])])]), X), smash(X).
  215% :- meta_predicate perform(?,:,?,?).
  216perform(_, eval, X, Y):- eval(X, Y).
  217perform(_, true, X, X).
  218perform(Ms, M:A, X, Y):-	perform([M|Ms], A, X, Y).
  219perform(M, (A; _), X, Y):-	perform(M, A, X, Y).
  220perform(M, (_; A), X, Y):-	perform(M, A, X, Y).
  221perform(M, (A, B), X, Y):-	perform(M, A, X, Z), perform(M, B, Z, Y).
  222perform([], A, X, Y):-		call(A, X, Y).
  223perform([M|_], A, X, Y):-	call(M:A, X, Y).
  224
  225% % Prolog on emacs buffer
  226% /** ::prolog
  227%  append(X, Y,[a,b,c]), X=[_,_]
  228% **/
  229
  230% module_prefix_for_expand(eh).
  231module_prefix_for_expand(user).
  232
  233prolog --> solve_bind.
  234
  235solve_bind_once --> solve_bind, !.
  236
  237solve_bind -->  herbrand(Bind),
  238	current(X),
  239	{	module_prefix_for_expand(Mod),
  240		once(pac:expand_goal(X, Mod, Y, P, [])),
  241		maplist(assert, P),
  242		solve(Y)
  243	},
  244	peek(Bind),
  245	term_codes.
  246
  247%
  248solve((X,Y)):- solve(X), solve(Y).
  249solve(X):- call(X).
  250
  251%
  252phrase(C, G, X, Y) :- call(C, call(G, X, Y)).
  253
  254% %
  255% once(G)--> phrase(once, G).
  256
  257% once(G, U, L0, L) :- once(call(G, U, L0, L)).
  258
  259% % once(G, X, X0) --> phrase(once, call(G, X, X0)).
  260% once(G, X, X0, L0, L) :- once(call(G, X, X0, L0, L)).
  261
  262
  263% a la cd command
  264% ?- eh:walk_on_tree(up, [a,b,c], X).
  265% ?- eh:walk_on_tree(up_down([x,y]), [a,b,c], X).
  266
  267walk_on_tree(up, X, Y):- !,  (append(Y, [_], X) -> true; Y=X).
  268walk_on_tree(down(A), X, Y):- !,  append(X, A, Y).
  269walk_on_tree(up_down(A), X, Y):-  walk_on_tree(up, X, X0),
  270	walk_on_tree(down(A), X0,  Y).
  271
  272%
  273% ?- eh:change_unix_path(up, "/a", X).
  274%@ X = "".
  275
  276% ?- eh:change_unix_path(up, "/ab/cd/ef", X).
  277% ?- eh:change_unix_path(down("x/y"), "/ab/cd/ef", X).
  278%@ X = "/ab/cd/ef/x/y/".
  279% ?- eh:change_unix_path(up_down("x/y"), "/ab/cd/ef", X).
  280%@ X = "/ab/cd/x/y/".
  281
  282change_unix_path(up, P, Q):-  !, path_to_list(P, X),
  283	walk_on_tree(up, X, Y),
  284	path_to_list(Q, Y).
  285change_unix_path(down(A), P, Q):-  !,
  286	path_to_list(A, Z),
  287	path_to_list(P, X),
  288	walk_on_tree(down(Z), X, Y),
  289	path_to_list(Q, Y).
  290change_unix_path(up_down(A), P, Q):-
  291	path_to_list(A, Z),
  292	path_to_list(P, X),
  293	walk_on_tree(up_down(Z), X, Y),
  294	path_to_list(Q, Y).
  295
  296% ?- eh:path_to_list("/", X).
  297% ?- eh:path_to_list(A, []).
  298% ?- eh:path_to_list(A, [a]).
  299% ?- eh:path_to_list(A, [a,b]).
  300
  301path_to_list(A, X):- nonvar(A), !,
  302	atomics_to_string(Y, (/), A),
  303	remove_null(Y, X).
  304path_to_list(A, X):- remove_null(X, X0),
  305	list_to_unix_path(X0, A).
  306
  307%
  308list_to_unix_path([], "/"):- !.
  309list_to_unix_path(X,  A):-  append([[""],X,[""]], X0),
  310	atomics_to_string(X0, "/",  A).
  311
  312%
  313remove_null([''|A], B):-!, remove_null(A, B).
  314remove_null([""|A], B):-!, remove_null(A, B).
  315remove_null([X|A], [X|B]):- remove_null(A, B).
  316remove_null([], []).
  317
  318
  319% [2015/12/28]
  320file_string(File, Length, String):-  open(File, read, Stream, [encoding(utf8)]),
  321			     read_string(Stream, Length, String),
  322			     close(Stream).
  323%
  324file_string(File, String):- file_string(File, _, String).
  325
  326%
  327getstring(X) :- get_code(C),
  328	(C == -1 -> X=[] ; X=[C|Y], eh:getstring(Y)).
  329
  330putstring(X) :- maplist(put_code, X).
  331
  332getline(X) :- get_code(C),
  333	((C == -1; C==0'\n) -> X=[] ; X=[C|Y], getline(Y)).
  334
  335putline(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
  346assemble(Fs, F) :- expand_file_search_path(F, F1),
  347        open(F1, write, FX, [encoding(utf8)]),
  348        maplist(assemble_basic(FX), Fs),
  349        close(FX).
  350
  351assemble_basic(FX, text(F)) :- !, clean_io(FX, write, basic:smash(F)).
  352assemble_basic(FX, file(F)) :- !, expand_file_search_path(F, F1),
  353        open(F1, read, FY, [encoding(utf8)]),
  354        clean_io(FY, read, eh:getstring(D)),
  355        maplist(put_code(FX), D).
  356assemble_basic(FX, codes(Codes)) :-!, maplist(put_code(FX), Codes).
  357assemble_basic(FX, region(Codes)):-!, maplist(put_code(FX), Codes).
  358assemble_basic(FX, buffer) :-
  359	call_lisp(list('point-min'(), 'point-max'()), string(L)),
  360	list_number_list(L, [Min, Max]),
  361	get_buffer_region(Min, Max, R),
  362	maplist(put_code(FX), R).
  365mac_open(F):-  pshell(open(F)).
  366
  367mac_open(F, F):- mac_open(F).
  368
  369mac_open(P, F, F):- mac_open_prefix(P, F).
  370
  371mac_open_prefix(_, F):- prefix_chk(`/`, F ), !, mac_open(F).
  372mac_open_prefix(_, F):- prefix_chk(`~`, F), !,	mac_open(F).
  373mac_open_prefix(Prefix, F):- mac_open(Prefix+ '/'+ F).
  374
  375prefix_chk(Prefix, String):- append(Prefix, _, String).
  376
  377:- meta_predicate wild_map(1,?).  378wild_map(M, W):- expand_file_name(W, L0), maplist(M, L0).
  379
  380:- meta_predicate wild_map(2,?,?).  381wild_map(M, W, L):- expand_file_name(W, L0), maplist(M, L0, L).
  382
  383wild_open(Wildcard):- wild_map(pred([X] :- pshell(open(X))), Wildcard).
  384
  385		/******************************
  386		*     counter file handler    *
  387		******************************/
 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.
  395:- meta_predicate counter_general(1, ?, ?).  396
  397counter_general(FileProp)	-->  obj:obj_get([counter_name(C), directory(D)]),
  398{
  399	pshell(mkdir(-p, D)), !,
  400	setup_call_cleanup(	working_directory(Old, D),
  401				call(FileProp, C),
  402				working_directory(_, Old))
  403}.
 counter(+P, +X, -Y) is det
Perform action P on a file X to unify Y with the result.
  408counter(new)	-->
  409	counter_general(pred([C] :- file(C, write, format("~w.~n", [0])))),
  410	obj_put([count(0)]).
  411counter(update) --> counter_general(exists_file), !,
  412	 obj:obj_get([counter_name(C), directory(D)]),
  413	{	working_directory(Old, D),
  414		file(C, read, read(V1)),
  415		V is (V1 + 1) mod 100,
  416		file(C, write, format("~w.~n",[V])),
  417		working_directory(_, Old)
  418	},
  419	obj_put([count(V)]).
  420counter(update) --> counter(new).
 new_file(+X, -Y) is det
Create a new file according to X, and unify Y with the result.
  425new_file --> obj:obj_get([ stem(R), directory(D) ] ),
  426        counter(update),
  427        obj:obj_get([count(N)]),
  428        {	atomic_list_concat([R,  N], B),
  429		atomic_list_concat([D,  / , B], F)
  430        },
  431        obj_put([base(B), file(F)]).
 new_file_here(+X, -Y) is det
Create a new file at the current directory.
  436new_file_here	--> obj_get([stem(R), count(N)]),
  437        { atomic_list_concat([R,  N], B) },
  438        obj_put([base(B)]).
 new_base_name(+X, -Y) is det
Create a new file according to X, and unify Y with the result.
  443new_base_name -->
  444        counter(update),
  445        obj_get([count(N), stem(R), directory(D)]),
  446        {	atomic_list_concat([R,  N], B),
  447		atomic_list_concat([D,  / , B], F)
  448        },
  449        obj_put([base(B), file(F)]).
 dir_open(+X, -Y) is det
Open the file X, and unify Y with X.
  454dir_open	--> obj_get([directory(D)]),
  455	{	pshell(open(D))	}.
 dir_open(+D) is det
Open the directory D.
  460dir_open(D):-	dir_open([directory(D)], _).
 expand_cgi_path(+X, -Y) is det
Expand a CGI path in X, and unify Y with X.
  465expand_cgi_path(X, Y):-
  466	getenv(http_cgi_bin, CB),
  467    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.
  473expand_path(P, X, Y):-  getenv(user, Name),
  474        smash([`/~`, Name, `/`,  P, `/`, X], Y).
 include_text(+X, -Y) is det
Read as string from a file X into Y.
  479include_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.
  484include_text(A)--> {listp(A) -> L = A; L = [A]}, peek(L),
  485		   maplist(include_text).
 filepath(+X, -Y) is det
Expand a file path X into Y.
  490filepath(X,X) :- atomic(X), !.
  491filepath(A,X) :- A=..[P|A1],
  492     ( P= (/) ->  Q = [ /|A1] ; dir(P, D), Q = [D, /|A1] ),
  493     atomic_list_concat(Q, X).
  494filepath(A,X) :- expand_file_search_path(A, X).
  495
  496% some handy
  497singleton(X,[X]).
  498comma((X, Y), X, Y).
  499args(X, A, B):- arg(1, X, A), arg(2, X, B).
  500image(R, S) :- maplist(snd, R, S).
  501%
  502vector_term(_, [X], X).
  503vector_term(F, [X, Y|Z], U):- vector_term(F,[Y|Z], X0), U=..[F, X, X0].
  504
  505%
  506wrap(X, Y, A, [X,A,Y] ).
Goto Dir, do ShellCom, then go back to the original directory.
  511boomerang(Dir, ShellCom):- sh(cd(Dir); ShellCom).
  512
  513same_atom(X, Y, "yes"):- atom_codes(X, Y).
  514same_atom(_, _, "no").
  515
  516backquote_string(X) :- string_codes(X, [96]).
  517
  518%
  519sh(X) :- pshell(X, [c, q]).
  520
  521% ?- xsh(ls).
  522xsh(X):- qshell_string(X, S),
  523		 shell(S, Ecode),
  524		 !,
  525		 (	Ecode == 0 -> true
  526		 ;	snap(shell(S, Ecode)),
  527			fail
  528		 ).
  529
  530
  531% xsh(X):-shell_string(X, "", Str),
  532% 		shell(Str, S),
  533% 		(	S \== 0 -> throw(xsh_error(Str))
  534% 		;	true
  535% 		).
  536
  537% ?- pshell(ls, [c, q, path]).
  538% ?- pshell(ls, [path]).
  539% ?- pshell(echo("$PATH") > "~/Desktop/PATH").
  540% ?- pshell("update-all").
  541% ?- pshell("update-swipl").
  542% ?- qshell("update-all").
  543
  544user:p(X):- snap(X).
  545user:p(X,Y,Y):- snap(X).
  546
  547% ?- pshell(ls).
  548% ?- pshell(ls, [c]).
  549% ?- pshell([ls], [c]).
  550% ?- pshell(ls, [q]).
  551% ?- pshell(ls, [c, q]).
  552% ?- pshell(ls, [c, q]).
  553% ?- pshell([ls], [c, q]).
  554% ?- qshell_string([a,b,c], X).
  555
  556pshell(X, Opts):-
  557	shell_string(X, X0),
  558	(	memberchk(path(V), Opts) ->
  559		T0 = ( "PATH=" + V ; X0)
  560	;	T0 = X0
  561	),
  562	(	memberchk(c, Opts) 	->
  563		shell_string("( " +  T0 + " )", T1),
  564		term_string(T1, T2),
  565		T3 = "/bin/sh -c " + T2
  566	;   T3 = T0
  567	),
  568	(	memberchk(q, Opts) 	->
  569		T4 = T3 + " > /dev/null 2>&1"
  570	;	T4 = T3
  571	),
  572	(	memberchk(str(Str), Opts) -> true
  573	;	true
  574	),
  575	shell_string(T4, Str),
  576	(	memberchk(exit(R), Opts) -> true
  577	;	true
  578	),
  579	shell(Str, R).
  580
  581% Was
  582% pshell(X, Opts):-
  583% 	(	memberchk(path(V), Opts)
  584% 	->	T0 = shell( "PATH=" + V ; X)
  585% 	;	T0 = shell(X)
  586% 	),
  587% 	(	memberchk(q, Opts)
  588% 	->  T1 = T0 + " >> /dev/null 2>&1"
  589% 	;	T1 = T0
  590% 	),
  591% 	misc:shell_string(T1, T2),
  592% 	(	memberchk(c, Opts)
  593% 	->	term_string(T2, T3),
  594% 		T4 = "/bin/sh -c " + T3
  595% 	;   T4 = T2
  596% 	),
  597% 	misc:shell_string(T4, S),
  598% 	shell(S).
  599
  600% ?- pshell(ls).
  601% ?- pshell(pwd).
  602% pshell(T):- misc:shell_string(T, S), shell(S).
  603pshell(T):- pshell(T, []).
  604
  605% pshell in quiet mode.
  606% ?- qshell(ls).
  607% ?- pshell(ls).
  608% ?- qshell(pwd).
  609qshell(X):- pshell(X,  [q]).
  610
  611:-meta_predicate(directory(?, 0)).  % <= neccessary dcl.
  612directory(D, A):-
  613	working_directory(Old, D),
  614	call(A),
  615	working_directory(_, Old).
  616%  ?- ls_pdf_files(L).
  617%  ?- ls_pdf_files(_, L), smash(L).
  618%  ?- ls_files_suffix(['.pdf'], L).
True when L is unified with a list of pdf files in the current folder.
  622ls_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.
  626ls_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.
  630ls_files_suffix(S, L)	:- ls_files(suffix(S), L).
 suffix(+S:string, X:string) is det
True if S is a suffix of L.
  634suffix(S, X):- sub_string(X, _, _, 0, S).
is True if L is unified with the list of files filtered by F.
  640% ?- eh:directory_filter(pred(([X]:- sub_string(X, _, 3, 0, ".pl"))), PDFs).
  641:- meta_predicate directory_filter(1, ?).  642directory_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.
  647ls_files(Filter, L):- directory_filter(exists_file, L0),
  648	collect(Filter, L0, L).
 ls_files(L:list) is det
True when L is unfified with names of files in the current folder
  652ls_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.
  657ls_dirs(Filter, L):- directory_filter(exists_directory, L0),
  658	collect(Filter, L0, L).
 ls_dirs(L:list) is det
True when L is unfified with names of files in the current folder
  662ls_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
  667ls_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.
  674% ?- eh:ls(X, Y).
  675% ?- working_directory(_, "/Users/cantor"), eh:ls(X, Y).
  676
  677ls --> 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).
  682ls_objects(A):- getinfo_codes(ls, X),
  683	(X==[]
  684	-> A = []
  685	;  once(split(X, X0)), maplist(atom_codes, A, X0)
  686	).
  687
  688%
  689object_classify([], [], []).
  690object_classify([A|As], [A|Xs], Ys):- exists_file(A), !,
  691	object_classify(As, Xs, Ys).
  692object_classify([A|As], Xs, [A|Ys]):- object_classify(As, Xs, Ys).
  693
  694%
  695set_dir(X, Y):- working_directory(X, Y).
  696set_dir(X) :- working_directory(_, X).
  697
  698%
  699get_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.
  705excursion(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).

  716dir_tree(L):- ls(Fs, Ds),
  717	maplist(unary(f), Fs, Gs),
  718	maplist(excursion_dir_tree, Ds, Es),
  719	append(Gs, Es, L).
  720
  721dir_tree(P, L):- excursion((set_dir(P), dir_tree(L))).
  722
  723excursion_dir_tree(N, d(P, L)):-
  724	get_dir(P0),
  725	atomic_list_concat([P0,N,(/)], P),
  726	excursion((set_dir(P), dir_tree(L))).
  727%
  728unary(F, T)	:- functor(T, F, 1).
  729unary(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)))).
  735:- meta_predicate map_directory(:).  736map_directory(Act):- ls_objects(Fs), maplist(check_do(Act), Fs).
  737
  738check_do(true, _):- !.
  739check_do(false, _):- !, fail.
  740check_do((A, B), X):- !,  check_do(A, X), check_do(B, X).
  741check_do((A; B), X):- !, once(check_do(A, X); check_do(B, X)).
  742check_do(\+ A , X):- !, \+ check_do(A, X).
  743check_do(A->B , X):- !, (check_do(A, X) -> check_do(B, X)).
  744check_do(A , X):- call(A, X).
 escape_posix_file_name_char(+X:text, -Y:text) is det
True if Y is unified with a copy of X in which special characters in X are escaped so that Y is safe for posix file name. ?- ejockey:escape_posix_file_name_char(`a : (b)`, R), atom_codes(A, R), smash(R). @ a \@ \(b\) @ R = [97, 32, 92, 64, 32, 92, 40, 98, 92, 41], @ A = 'a \\@ \\(b\\)' .
  754escape_posix_file_name_char(X, Y):-
  755  foldr(pred(	[0'(,  U, [0'\\,    0'(  | U]	] &
  756		[0'),  U, [0'\\,    0')  | U]	] &
  757		[0'\', U, [0'\\,    0'\' | U]	] &
  758		[0':,  U, [0'\\,    0'@  | U]	] &
  759		[0'/,  U, [0'\\,    0'@  | U]	] &
  760		[A,    U, [A|U]			]
  761	    ),
  762	X, [], Y).
  763
  764%'
  765%!  r_act_plus(+F:pred/3, +L:list, -Y:term) is det
  766%	True if
  767%  Y is unified with the folded L by F from the right,
  768%  so that Y is a right branching binary tree.
  769% ?- eh:foldl(variant(term(+)), [b,c,d], a, Y).
  770%@ Y = a+b+c+d.
  771:- meta_predicate r_act_plus(3, ?, ?).  772r_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).

  784% ?- eh:r_act_plus(term(+), [a,b,c,d], X, Y).
  785% ?- eh:r_act_plus(term(+), [1, 2, 3], X).
  786% ?- eh:r_act_plus(variant(term(+)), [1, 2, 3], X).
  787% ?- eh:r_act_plus(cons, [1, 2, 3], X).
  788:- meta_predicate r_act_plus(3, ?, ?, ?).  789r_act_plus(_, [X], X, X):-!.
  790r_act_plus(F, [A|As], X, Y) :- call(F, A, Y0, Y),
  791	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.
  797%  ?- eh:apply(append([a,b]),[[c,d]], R).
  798%@ R = [a, b, c, d].
  799
  800:- meta_predicate apply3(:, ?, ?).  801
  802apply3(A, Xs, V):-  apply_(Xs, A, V).
  803
  804%
  805apply_([], A, V)		:- !, call(A, V).
  806apply_([X], A, V)		:- !, call(A, X, V).
  807apply_([X, Y], A, V)	:- !, call(A, X, Y, V).
  808apply_([X, Y, Z], A, V)	:- !, call(A, X, Y, Z, V).
  809apply_([X, Y, Z, U], A, V)	:- !, call(A, X, Y, Z, U, V).
  810apply_(Xs, A, V)		:- is_list(Xs),
  811		append(Xs, [V], Args),
  812		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.
  819% ?- eh:mapleaves(pred([X,[X,X]]), f(a,[u,v], b([1,2])), R).
  820
  821:- meta_predicate mapleaves(2, ?, ?).  822mapleaves(F, M:X, M:Y) :- !, mapleaves(F, X, Y).
  823mapleaves(F, X, Y) :- ala_list(X), !,
  824	maplist(mapleaves(F), X, Y).
  825mapleaves(F, X, Y) :- atomic(X),  !, call(F, X, Y).
  826mapleaves(F, X, Y) :- functor(X, A, N),
  827	functor(Y, A, N),
  828	mapleaves(0, N, F, X, Y).
  829
  830:- meta_predicate mapleaves(?,?,2,?,?).  831mapleaves(N, N, _ , _ , _) :- !.
  832mapleaves(I, N, F, X, Y):- J is I + 1,
  833	arg(J, X, Z),
  834	arg(J, Y, U),
  835	mapleaves(F, Z, U),
  836	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.
  843% ?-  eh:mapleaves(mapleaves(writeln), f(g(a), [c,x(j),e], h(b))).
  844:- meta_predicate mapleaves(1, ?).  845mapleaves(F, _:X) :- !, mapleaves(F, X).
  846mapleaves(F, X) :- is_list(X), !, maplist(mapleaves(F), X).
  847mapleaves(F, X) :- atomic(X),  !, call(F, X).
  848mapleaves(F, X) :- functor(X, _, N), mapleaves(0, N, F, X).
  849
  850%
  851mapleaves(N, N, _, _) :- !.
  852mapleaves(I, N, F, X) :- J is I + 1,
  853	arg(J, X, Z),
  854	mapleaves(F, Z),
  855	mapleaves(J, N, F, X).
  856
  857
  858		/****************************************
  859		*     accessing favorite directories    *
  860		****************************************/
 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.
  867:- meta_predicate setup_candidate(?,1).  868setup_candidate(SetVar, Pred) :-
  869	setof(D, call(Pred, D), S),
  870	maplist(atom_string, S, Cs),
  871	call_lisp_wait(setq(SetVar, #(Cs))),
  872 	atom_string(SetVar, SetVarName),
  873	atomics_to_string(["variable ", SetVarName, " has been set."], String),
  874	call_lisp_wait(message(String)).
  875
  876%
  877dir(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.
  884dired --> { call_lisp(
  885		prompt("directory name ",
  886			#('dir-set')),
  887			[value(D0), string(t)]),
  888	  term_codes(T, D0),
  889	  atom_string(A, T),
  890	  config:expand_dir_name(A, D),
  891	  lisp(dired(D))
  892	  }