1:- module(ejockey, []).    2
    3:- use_module(pac(basic)).    4:- use_module(pac(reduce)).    5:- use_module(pac(meta)).    6:- use_module(pac('pac-listing')).    7:- use_module(util(misc)).    8:- use_module(util('work-command')).    9:- use_module(util(snippets)).   10:- use_module(util('term-string')).   11:- use_module(util(file)).   12:- use_module(util('prolog-elisp')).   13:- use_module(util('emacs-handler')).   14:- use_module(util('swap-args')).   15:- use_module(util(tex)).   16:- use_module(util(obj)).   17:- use_module(pac(op)).   18:- use_module(zdd('zdd-array')).   19
   20:- op(1200, xfx, -->>).   21
   22jisui_archives("/Users/cantor/Dropbox/jisui_archives").
   23
   24:- discontiguous handle/3.  % [2016/01/28]
   25
   26term_expansion --> pac:expand_pac.
 codes_to_strings(+D, +X, -Y) is det
Y is unified with a list [x1,...,xn] of strings such that X is the concatenation x1*Dx2...*D*xn as codes ?- codes_to_strings("\n", `ab\ncd\nef`, X). ?- codes_to_strings("\n", `ab\ncd\n\nef`, X). ?- A = `ab\ncd\n\nef`, codes_to_strings("\n", A, X), insert("\n", X, Y), smash_string(Y, Z), string_codes(Z, Z0), Z0=A.
   37codes_to_strings(Delim, X, Y):-
   38	string_codes(X0, X),
   39	atomics_to_string(Y, Delim, X0).
 numbering(+As, +X, -Y) is det
Y is unified with a string of the form "f(k, ...)" if f is in As and X = "f(...)" where k is the current value of global variable f, which is bumbed. Otherwise Y = X.
   47numbering(As, X, Y):-
   48	maplist(pred([A, A-A0]:-string_concat(A, "(", A0)), As, Bs),
   49	(	member(A-A0, Bs),
   50		string_concat(A0, Z, X) ->
   51		nb_getval(A, C),
   52		C0 is C+1,
   53		nb_setval(A, C0),
   54		atomics_to_string([A0, C0, " ,", Z], Y)
   55	;	Y = X
   56	).
 renumbering(Fs, +X, -Y) is det
Y is unified with a string of the form "f(k,...)" if f is in As and X = "f(_, ...)" where k is the current value of global variable f, which is bumbed. Otherwise Y = X.
   64% ?- nb_setval(abc, 0),
   65%	renumbering([abc], "",  Y),
   66%	renumbering([abc], "uvw(x)",  Z),
   67%	renumbering([abc], "abc(2, U)",  U).
   68%@ Y = "",
   69%@ Z = "uvw(x)",
   70%@ U = ["abc(1,U)", "."].
   71
   72renumbering(As, X, Y) :-
   73	(	member(A, As),
   74		string_concat(A, R, X),
   75		string_concat("(", _, R) ->
   76		nb_getval(A, C),
   77		C0 is C + 1,
   78		nb_setval(A, C0),
   79		term_string(Z, X,
   80					[	module(fol_prover),
   81						variable_names(E)]),
   82		Z =.. [_, _|U],
   83		Y0 =..[A, C0|U],
   84		maplist(call, E),
   85		term_string(Y0, Y1,
   86					[	module(fol_prover),
   87						quoted(false)]),
   88		Y = [Y1,"."]
   89	;	Y = X
   90	).
   91
   92/* consider C-<return> as setup for (re)numbering terms.
   93?- nb_setval(fs, [valid_formula, invalid_formula, unsatisfiable_formula]).
   94?- nb_getval(fs, X).
   95*/
   96
   97% ?- append([a,b],[c,d], []).
   98% ?-  X=1,
   99%	 Y=2,
  100%	Z = 3.
This handle numbering lines in the region using the numbering/3.
  106handle([numbering, terms])--> region,
  107	{	nb_getval(fs, Fs),
  108		forall(member(F, Fs), nb_setval(F, 0)) },
  109	codes_to_strings("\n"),
  110	maplist(numbering(Fs)),
  111	insert("\n"),
  112	overwrite.
This handle renumbering lines in the region using the renumbering/3.
  118handle([renumbering, terms])-->  region,
  119	{ nb_getval(fs, Fs),
  120	  forall(member(F, Fs), nb_setval(F, 0)) },
  121	codes_to_strings("\n"),
  122	maplist(renumbering(Fs)),
  123	insert("\n"),
  124	overwrite.
  125
  126handle([renumbering, terms, buffer])-->	mark_whole_buffer,
  127	handle([renumbering, terms]).
  128
  129
  130			/***********************
  131			*     Emacs Handler    *
  132			***********************/
  133%
  134handle([halt]) --> {halt}.
  135%
  136handle([count, paragraph]) -->region,
  137	  paragraph,
  138	  remove([]),
  139	  length,
  140	  fsnumber_codes.
  141
  142		/*************************
  143		*     sed-like usage.    *
  144		*************************/
  145
  146% Example.
  147% wl("(..)") >> ["hello"]
  148% abcd
  149
  150% Example.
  151% (w(".*", A), wl("b+")) >> pred(A, [A])
  152% aaabbcccbdddbeee
  153
  154handle([sed|Optional]) --> region,
  155	   phrase((wl("[^\n]*", SedCommandText), wl("\n+"))),
  156		{	herbrand(_, SedCommandText, SedPhrase),
  157			let_sed(Sed, SedPhrase)
  158		},
  159		call(Sed),
  160		optional_overwrite(Optional).
nb_setval(sed, S), where S is the sed phrase, which is converted from the region.
  165handle([let, sed, Global]) --> region, current(Region),
  166		{	herbrand(_, Region, SedPhrase),
  167			let_sed(Sed, SedPhrase),
  168			nb_setval(Global, Sed)
  169		},
  170		clear.
Apply the sed action stored in global S to the region. Optional buffer action is append/overwrite like for other handles.
  177handle([apply, sed, S|Optional]) --> region,
  178	{	nb_getval(S, Sed) },
  179	call(Sed),
  180	optional_overwrite(Optional).
  181%
  182handle([one, line]) --> region,
  183		sed(wl("[\n\s\t]+") >> "\s").
  184%
  185handle([pldoc, action]) -->
  186	region,
  187	split,
  188	maplist(insert_plus_action),
  189	insert("\n"),
  190	overwrite.
  191
  192
  193handle([prove])--> region,
  194	split,
  195	remove([]),
  196	maplist(pred(([X, Y-S]:- string_codes(S, X),
  197				 term_string(Z, S, [module(fol_prover)]),
  198				 arg(1, Z, Y)
  199				 ))),
  200	maplist(pred([F-S, [S, Out, "\n"]]:- fol_prover:prove(F, Out))).
  201
  202
  203handle([free, variant])--> region, % get region in codes.
  204	split,			% split by `\n`
  205	remove([]),		% remove empty lines.
  206	maplist(pred(([X, Y-S]:- string_codes(S, X),	% parse each line as a term.
  207				 term_string(Y, S, [module(fol_prover)])))),
  208	peek(Terms, []),	% get current contents, and put [] as a inital value.
  209	add_non_variant(Terms),	% remove terms so that no variant pairs there.
  210	maplist(pred([_-S, [S,"\n"]])),	% put orginal terms with new line code at end.
  211	reverse,
  212	overwrite.  % replace the input region with the slimmed result.
  213
  214% ?- add_non_variant([A-1, B-2, A-1], [], R). % note that A is a variant of B.
  215% ?- add_non_variant([f(A)-1, g(B)-2, f(A)-2], [], R).
  216
  217add_non_variant([], X, X).
  218add_non_variant([P|U], X, Y):- add_non_variant_one(P, X, Z),
  219	add_non_variant(U, Z, Y).
  220%
  221add_non_variant_one(A-B, X, Y):-
  222	(	member(C-_, X), variant(A, C) -> Y = X
  223	;	Y = [A-B|X]
  224	).
  225%
  226insert_plus_action --> "%c", w("[\s\t]*"),
  227					   "handle(",
  228					   peek(X, ["%%\thandle(+Action:", X]).
  229insert_plus_action --> [].
Interprete the first line of the region as the handle call with the rest of the region as an argument.
  236handle([meta, handle]) --> region,
  237	handle_parse_eval(_, _),
  238	peek(R, ["===>\n", R]).
`Overwrite' version of handle([meta, handle]).
  243handle([meta, handle, overwrite]) --> region,
  244	handle_parse_eval(Tag_codes, _),
  245	peek(R, [Tag_codes,".\n", R]),
  246	overwrite.
  247
  248handle_parse_eval(Tag, Rest, X, Y) :-
  249	 append(Tag, [0'., 0'\n | Rest], X), !,
  250	 string_codes(S, Tag),
  251	 term_string(H,  S),
  252 	 expand_arg(H, [], H0, Aux, []),
  253	 maplist(assert, Aux),
  254	 meta_handle(H0, ejockey, modify_handle, [Rest, Y]).
  255%
  256modify_handle(overwrite(X, X), _, [], true).
  257modify_handle(overwrite, _, [X, X], true).
  258modify_handle(handle(U), M, [X, Y], BodyH):-
  259	clause(M:handle(U, X, Y), BodyH),
  260	!.
  261modify_handle(handle(U, X, Y), M, [], BodyH):-
  262	clause(M:handle(U, X, Y), BodyH),
  263	!.
  264
  265%	handle([remove, double, slash, entry]) is det.
  266%	remove all lines which has a gingle "//" at end.
  267handle([remove, double, slash, lines])--> region,
  268	split,
  269	remove_double_slash_lines,
  270	insert("\n"),
  271	overwrite.
  272
  273% ?- double_slash_line(`abc // `, []).
  274% ?- double_slash_line(`abc /// `, []).
  275check_double_slash--> wl("[^/]*//"), wl("[\t\n\s]*").
  276%
  277remove_double_slash_lines([], []).
  278remove_double_slash_lines([X|Xs], Ys):-
  279	check_double_slash(X,[]),
  280	!,
  281	remove_double_slash_lines(Xs, Ys).
  282remove_double_slash_lines([X|Xs], [X|Ys]):-
  283	remove_double_slash_lines(Xs, Ys).
Reload the file at the current buffer, dropping the suffix "<..>" if exists.
  288handle([load, buffer]) -->
  289	{	load_buffer(Name),
  290		message([Name, " reconsulted."])}.
  291
  292load_buffer(Y) :-
  293	lisp(list('default-directory', 'buffer-name'()), [X, Y]),
  294	atomics_to_string([X, /, Y], Z),
  295	(	exists_file(Z) -> Z0 = Z
  296	;	sub_string(Z, _, _, 1, ">"),
  297		sub_string(Z, J, 1, _, "<"),
  298		sub_string(Z, 0, J, _, Z0)
  299	),
  300    load_files([Z0]).
  301
  302handle([wrap])-->region,
  303	split,
  304	remove([]),
  305	flip(cons(PredName)),
  306	maplist(pred(PredName, [A, [PredName, "(", A, ")."]])),
  307	insert("\n"),
  308	overwrite.
  309%
  310handle([collect, functors]) --> region,
  311 	swap_args:elem_list(X, []),
  312	{	swap_args:collect_functors(X,  Y, []),
  313		sort(Y, Y0),
  314		insert(",\n", Y0, Y1)
  315	},
  316	peek(["[", Y1, "]"]).
  317%
  318handle([set, functors, list]) --> region,
  319	herbrand,
  320	current(Sgn_list),
  321	{ nb_setval(functors_list, Sgn_list) },
  322	peek("*functors_list set*\n").
  323
  324%
  325handle([insert, last, arg]) --> region,
  326	{ nb_getval(functors_list, Sgn),
  327	  (		nb_current(arg_name, Arg), Arg \== [] -> true
  328	  ;		Arg = "State"
  329	  ),
  330	  string_concat(" ", Arg, Arg0)
  331	},
  332	swap_args:elem_list(X, []),
  333	peek(X),
  334	swap_args:edit_elem_list(swap_args:insert_last_arg, Sgn, Arg0),
  335	overwrite.
  336%
  337handle([set, string, V]) --> line,
  338	flip(string_codes),
  339	current(String),
  340	{ call_lisp(setq(V, String), noreply)},
  341	clear.
  342
  343%
  344handle([get, string, X]) -->
  345	{ call_lisp(X, string(Y)) },  % string(t) => ".."
  346	peek(Y).
  347
  348% ?- trim_line_string(` ab c \n `, X).
  349expand_tilda(X, Y):- expand_file_name(X, [Y|_]).
Remove comments in the region.
  354handle([remove, comment]) --> region,
  355							  remove_comment,
  356							  overwrite.
  357
  358handle([luatex])--> region,
  359	current(R),
  360	peek([]),
  361	{
  362		expand_tilda("~/tmp/deldel.tex", TeXFile),
  363		expand_tilda("~/tmp/preamble.tex", Preamble),
  364		Fs=	[text("\\RequirePackage{luatex85}\n"),
  365			text("\\documentclass{ltjsarticle}\n"),
  366			text("\\usepackage[hiragino-pron,jis2004]{luatexja-preset}\n"),
  367			file(Preamble),
  368			text("\\begin{document}\n"),
  369			codes(R),
  370			text("\\end{document}\n") ],
  371			assemble(Fs, TeXFile)
  372	},
  373	{	expand_tilda("~/tmp", TMP),
  374		qshell(	cd(TMP) ;
  375				lualatex("deldel") ;
  376				open(-a("Preview"), "deldel.pdf")
  377			)
  378	}.
Compile pac clauses in the region.
?- ejockey:handle([compile, pac, region], `a.\na.\n`, R).

?- ejockey:handle([compile,pac,region, dbg], `:-betrs(a).\n:-etrs.\n`, R). ?- ejockey:handle([compile,pac,region, dbg], `f:= [g/0-h].\n`, R). ?- ejockey:handle([cpr], `a:-b.\n`, R), smash(,R). ?- ejockey:handle([cpr], `a:-b(pred([x])).\n`, R), smash(R). ?- ejockey:handle([cpr], `:-bekind(f, []).\n:-ekind.\n`, R), smash(R). ?- ejockey:handle([cpr], `:-bekind(f, []).\na=b.\n:-ekind.\n`, R), basic:smash(R). ?- ejockey:handle([cpr], `:-bekind(f, []).\na=b.\n:-ekind.\n`, R), basic:smash(R).

  397% for short.
  398handle([cpr|Optional])-->handle([compile,pac,region|Optional]).
  399
  400handle([compile, pac, region|Optional]) --> region,
  401	flip(string_codes),
  402	string_to_terms,
  403	compile_terms_to_qstring,
  404	optional_overwrite(Optional).
  405
  406handle([terms|Optional]) --> region,
  407	flip(string_codes),
  408	string_to_terms,
  409	optional_overwrite(Optional).
  410
  411%
  412optional_overwrite(Optional) -->
  413	{ partial_match(Optional, overwrite) }, !,
  414	overwrite.
  415optional_overwrite(_) --> [].
  416
  417%
  418handle([region, string]) --> region, escape_codes_for_string.
  419%
  420escape_codes_for_string(X, [0'"|Y]):-	 %'
  421	escape_codes_for_string_(X, Y).
  422%
  423escape_codes_for_string_([], [0'"]):-!. %'
  424escape_codes_for_string_([X|P], Q):-
  425	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  426	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  427	;	X = 0'" -> Q = [0'", 0'"|Q0]		%"
  428	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  429	;	Q = [X|Q0]
  430	),
  431	escape_codes_for_string_(P, Q0).
  432%
  433handle([region, atom]) --> region, escape_codes_for_atom.
  434
  435escape_codes_for_atom(X, [0'\'|Y]):-  %'
  436	escape_codes_for_atom_(X, Y).
  437%
  438escape_codes_for_atom_([], [0'\']):-!. %'
  439escape_codes_for_atom_([X|P], Q):-
  440	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  441	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  442	;	X = 0'\' -> Q = [0'\', 0'\'|Q0]		%'
  443	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  444	;	Q = [X|Q0]
  445	),
  446	escape_codes_for_atom_(P, Q0).
  447
  448handle([region, bq]) --> region, escape_codes_for_BQ.
  449
  450escape_codes_for_BQ(X, [0'\`|Y]):-  %'
  451	escape_codes_for_BQ_(X, Y).
  452%
  453escape_codes_for_BQ_([], [0'\`]):-!. %'
  454escape_codes_for_BQ_([X|P], Q):-
  455	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  456	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  457	;	X = 0'\` -> Q = [0'\`, 0'\`|Q0]		%'
  458	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  459	;	Q = [X|Q0]
  460	),
  461	escape_codes_for_BQ_(P, Q0).
Compile pac clauses in the region.
  467% ?- ejockey:handle([compile, pac, generic], `~/local/lib/pacpl7/a.pl`, R).
  468handle([compile, pac, generic]) -->
  469	region,
  470	split,
  471	maplist(trim_white),
  472	remove([]),
  473	maplist(pred([X, F]:- string_codes(F,  X))),
  474	(	maplist(compile_pac_generic),
  475		peek([]),
  476		{message("done")},
  477		!
  478	;	peek([]),
  479		{message("Error ! file not exists ?")}
  480	).
  481
  482% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a.pl", X).
  483% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a.pac", X).
  484% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a", X).
  485compile_pac_generic(In, Files):-
  486	expand_file_name(In, Files),
  487	maplist(compile_pac_generic, Files).
  488%
  489compile_pac_generic(Src):-
  490	once(determine_source(Src, Src0)),
  491	setup_call_cleanup(open(Src0, read, SX, [encoding(utf8)]),
  492		stream_parse_pac_terms(SX, Xs, []),
  493		close(SX)),
  494	compile_terms_to_qstring(Xs, QuasiText),
  495	determine_target(Src0, Target),
  496	setup_call_cleanup(open(Target, write, SY, [encoding(utf8)]),
  497		write_qstring(QuasiText, SY),
  498		close(SY)).
  499%
  500determine_source(X, X):- string_drop_suffix(X, ".pl", X0), !,
  501	string_concat(X0, ".pac", X1),
  502	\+exists_file(X1).
  503determine_source(X, X):- string_end_with(X, ".pac"), !,
  504	exists_file(X).
  505determine_source(X, Y):- member(M, [".pac", ".pl"]),
  506	string_concat(X, M, Y),
  507	exists_file(Y),
  508	!.
  509%
  510determine_target(X, Y):- string_drop_suffix(X, ".pac", Z), !,
  511	string_concat(Z, ".pl", Y).
  512determine_target(X, X):- string_drop_suffix(X, ".pl", Y),
  513	modify_file_name(Y, 0, '.pac', Keep),
  514	rename_file(X, Keep).
  515
  516% ?- ejockey:string_drop_suffix("abcd", "cd", Y).
  517string_end_with(X, S):- sub_string(X, _, _, 0, S).
  518
  519% ?- ejockey:string_drop_suffix("abcd", "cd", Y).
  520string_drop_suffix(X, S, Y):- sub_string(X, J, L, 0, S),
  521	sub_string(X, 0, J, L, Y).
  522%
  523ignore_pac_term(term_expansion-->expand_pac).
  524
  525%
  526stream_parse_pac_terms(Stream, U, Q) :-
  527		stream_term_string(Eqs, X, Stream),
  528		(	at_end_of_stream(Stream)	->	U = Q
  529		;	ignore_pac_term(X)	->  stream_parse_pac_terms(Stream,  U, Q)
  530		;  	(	is_backquote_begin(X, X0),
  531				set_prolog_flag(back_quotes, symbol_char)
  532			; 	is_backquote_end(X, X0),
  533				set_prolog_flag(back_quotes, codes)
  534			; 	X0 = X
  535			),
  536			!,
  537			U = [X0-Eqs|P],
  538			stream_parse_pac_terms(Stream, P, Q)
  539		).
  540%
  541compile_terms_to_qstring(Xs, QuasiText):-
  542	compile_pac(Xs, P, []),
  543	pred_grouping(P, Blocks),
  544	maplist(maplist(pred([P, pair(X0, H0)]:-
  545							 clause_to_string(P, X0, H0))),
  546			Blocks, ExpandedBlocks),
  547	maplist(pred(([Block, [Cs,"\n", Hs]]:-
  548				maplist(pred([pair(U,V), U, V]), Block, Cs, Hs))),
  549			ExpandedBlocks, QuasiText).
  550
  551%
  552write_qstring([A|B], S):- write_qstring(A, S),
  553						  write_qstring(B, S).
  554write_qstring([], _).
  555write_qstring(A, S):- write(S, A).
Compile a pac clause at the region.
  560handle([compile, predicate|Flag]) --> region,
  561	herbrand(web, Eqs),
  562	current(X),
  563	{ pac_listing:compile_pred_word(X, Eqs, H0, R0) },
  564	peek([R0, "\n", H0, ".\n"]),
  565	overwrite(Flag).
  566
  567%	select_phrase(partial_match(Flag, overwrite), overwrite, =).
Expand pac clauses.
  572handle([expand, pac]) --> region,
  573	pred([X, Y]:- string_codes(Y, X)),
  574	parse_pac_terms,
  575	pred([Xs, P]:- compile_pac(Xs, P, [])),
  576	pred_grouping,
  577	maplist(maplist(pred([P, pair(X0, H0)]:-
  578							 pac_listing:clause_to_string(P, X0, H0)))),
  579	maplist(pred(([Block, [Cs,"\n", Hs]]:-
  580				maplist(pred([pair(U,V), U, V]), Block, Cs, Hs)))).
  581
  582
  583
  584%
  585parse_pac_terms(X, Pacs):-
  586	setup_call_cleanup(
  587		open_string(X, Stream),
  588		stream_parse_pac_terms(Stream, Pacs, []),
  589		close(Stream)).
Expand pac clauses, and rewrite the region with them.
  594handle([expand, pac, overwrite]) -->
  595	handle([expand,pac]),
  596	overwrite.
Return the string on which the cursor is.
  601handle([neighbor, string]) --> {neighbor_string("[","]", X)},
  602							   peek(X).
Collect Prolog identifiers.
  607handle([collect, identifiers]) --> region,
  608	collect_tokens(prolog_indentifier),
  609	maplist(herbrand),
  610	sort,
  611	insert("\n").
Collect keywords.
  616handle([collect, keywords]) --> region,
  617	collect_tokens(keyword),
  618	maplist(herbrand),
  619	sort,
  620	insert("\n").
Copy the current head of a clause, and insert it after modifying before the line.
  626handle([copy, head])-->
  627	 {	line_get(Obj),
  628		obj_get([line(Line)], Obj),
  629		string_codes(Line, Codes),
  630		phrase(( wl("[\s\t]*"),
  631				 w(".*", Head),
  632				 w("[\s\t]*((-->)|(:-))")),
  633			   Codes, _)
  634		},
  635	 peek(["%%\t", Head, " is det.\n%\n%\n", Line]),
  636	 overwrite.
Swap I-th argument with J-th one in for all terms with functor Name.
  642handle([swap, args, N, I, J]) -->
  643	{ atom_number(I, I0),
  644	  atom_number(J, J0) },
  645	region,
  646	pred([N, I0, J0],
  647		 ([X, Y]:-
  648			 swap_args:swap_args_of(N, I0, J0, X, Y))),
  649	overwrite.
ask LISP to eval global-set-key
  654handle([handle, kbd])  --> region,
  655	pred(([S, []] :- term_codes(E, S),
  656		arg(1, E, K),
  657		arg(2, E, P),
  658		global_set_kbd(K, P))).
Activate emacs dired with a prompt.
  663handle([dired])  --> dired.
Mark all *.pl files in DIRED.
  668handle([dired, mark, swipl]) --> {dired_mark_swipl}.
Swap the first two arguments.
  672handle([swap, args, X]) --> region,
  673	swap_args_of(X, 1, 2),
  674	overwrite.
Numbering paragraphs.
  678handle([numbering, paragraphs])  --> region,
  679	paragraph,
  680	remove([]),
  681	pred(([X, Y]:- length(X, N),
  682	      numlist(1, N, Ns),
  683	      maplist(pred([I, P,[I0, ". ", P]]:-
  684			  number_string(I, I0)),
  685		      Ns, X, Y))),
  686	insert("\n"),
  687	overwrite.
  688
  689%! 	handle([help]) is det.
  690%   Show all handle commands.
  691%!  handle([help]) --> {setof(H, P^Q^R^clause(handle(H,P,Q), R), S),
  692% 		 sort(S, S1),
  693% 		 maplist(pred(([X, Y]:-
  694% 				numbervars(X,0,_),
  695% 				write_to_chars(X, Z, []),
  696% 				string_codes(Z, Y))),
  697% 			S1, S2),
  698% 		 insert_tab_nl(4, 4, S2, R)
  699% 		},
  700% 		peek(R).
  701
  702%! 	handle([handle, list]) is det.
  703%   Set Lisp variables  handle-list to the list of all handles.
  704
  705
  706handle([handle, list]) --> region,
  707    {findall(H, clause(handle(H,_,_), _), S),
  708	 sort(S, S1),
  709	 maplist(pred(([H, H0] :-
  710			   foldl(pred([H, H0],
  711							  ( [X, ['VAR'|L], L]:- var(X) )
  712							& [X, [X|L], L]				     ),				     H, H0, []))),		 S1, S2),	remove([], S2, S3),	maplist(pred(([X, Y]:- atomics_to_string(X, " ", Y0),				  atomics_to_string(["[", Y0, "] "], Y))),				S3, Commands)%	,	List =..[list|Commands]%	,	elisp:lisp(setq('handle-list', List))%	,	elisp:lisp(message("variable 'handle-list' has been set."))	},	peek(Commands),	overwrite.
Reload the current buffer file.
  729handle([reload, buffer, file]) -->
  730	{ call_lisp('buffer-file-name'(), term(File)),
  731  	  string_codes(S, File),
  732	  unload_file(S),
  733	  load_files(S, [silent(true)]) }.
Generate edit commnad ?- edit(X) from the symbol at the current point.
  737handle([edit])--> { prolog_symbol_at_point(X) },
  738			  peek(["\n\n% ?- edit(", X, ").\n"]).
Take a time-stamped memo, and display it in the emacs window.
  743handle([take, memo]) --> region,
  744 	{   lisp('time-stamp', Dir),
  745		getinfo_string("date +%Y-%m-%d", Today),
  746		atomics_to_string([Dir, Today], File0),
  747		expand_file_name(File0, [File|_]),   % File is of type atom.
  748		pshell(touch(File))
  749	},
  750	pred([Today, File],
  751		 ( [ Note, []]
  752		   :- file:push_to_file(
  753					 basic:smash(["[", Today, "]\n",
  754								  Note,
  755								  "\n"]),
  756							File))),
  757	{	atom_string(File, File0),
  758		lisp('find-file'(File0))
  759	}.
Save the clipboard as a note. ! handle([clipboard]) --> {getinfo_codes("pbpaste", D)}, peek(D), ! handle([snippet]).
Choose a folder, and save its name to a lisp variable.
  771handle([choose, working, directory]) -->
  772	{	choose_folder(X),
  773		set_string(working_directory, X)
  774	},
  775	peek(X).
Choose a folder.
  779handle([choose, folder]) --> {choose_folder(X)}, peek(X).
Choose a file.
  783handle([choose, files]) --> {choose_files(X), insert("\n", X, X0) },
  784							peek(X0).
  785
  786%
  787handle([rename, files]) --> region,
  788	split,
  789	remove([]),
  790	maplist(flip(string_codes)),
  791	rename_files_base,
  792	overwrite.
  793
  794handle([display, renamed]) --> region,
  795	split,
  796	remove([]),
  797	maplist(flip(string_codes)),
  798	rename_files_base_display,
  799	overwrite.
  800
  801
  802% short for handle([open, pdf]).
  803handle([o]) --> handle([open, pdf]).
  804handle([m]) --> handle([jisui, archives]).
  805%
  806handle([jisui, archives])--> trim_line_string,
  807	current(A),
  808	{ jisui_archives(B),
  809	  expand_file_name(B, [B0|_]),
  810	  run_shell(mkdir, ['-p', B0]),
  811%	  pshell(mv(A, B0))
  812%  	  process_create(path(mv), [A, B0], [])
  813	  run_shell(mv, [A, B0])
  814	},
  815	clear,
  816	overwrite.
  817
  818%
  819rename_files_base([], []).
  820rename_files_base([X,Y|Z], [U, "\n"|V]):-
  821	subst_file_base(X, Y, U),
  822	rename_file(X, U),
  823	rename_files_base(Z, V).
  824
  825% ?- subst_file_base("/a/ b/b", c, Z).
  826subst_file_base(X, Y, Z):-
  827	atomic_list_concat(X0, /, X),
  828	append(U, [_], X0),
  829	append(U, [Y], V),
  830	atomic_list_concat(V, /, Z).
Choose a file and opent it.
  834handle([choose, file, open]) -->
  835	{	choose_file(X),
  836		term_string(X, Y),
  837		pshell(open(Y))
  838	},
  839	peek(X).
  840
  841% ?- atomic_list_concat([a, ' b'], C).
Choose a folder, and open it.
  845handle([choose, folder, open]) -->
  846	{	choose_folder(X),
  847		term_string(X, Y),
  848		pshell(open(Y))
  849	},
  850	peek(X).
  851
  852		/********************
  853		*     sort lines    *
  854		********************/
Sort lines.
  858handle([sort, lines]) --> region,
  859						  split,
  860						  sort,
  861						  insert("\n"),
  862						  overwrite.
Trim leading white codes and sort the trimed lines.
  867handle([trim, sort, lines]) --> region,
  868						  split,
  869						  remove([]),
  870						  maplist(phrase(wl("[\s\t]*"))),
  871						  sort,
  872						  maplist(pred([L, [L,"\n"]])),
  873						  overwrite.
  874end_of_codes([], []).
  875%
  876trim_line --> line, phrase(wl("[\s\t]*")).
  877%
  878trim_line_string --> line, trim_line, flip(string_codes).
open a file with a full path in the current line as pdf.
  882handle([open, pdf]) --> trim_line,
  883				current(X),
  884				{	string_codes(Y, X),
  885					run_shell(open, ['-a', "Preview", Y])
  886				},
  887				clear.
  888
  889
  890		/************************
  891		*     shell in buffer   *
  892		************************/
Run shell commands in the region.
  897handle([shell]) --> set_mark_region,
  898	region,
  899	split,
  900	remove([]),
  901	insert(" ; "),
  902        {
  903	    tmp_file_stream(utf8, File, Stream),
  904	    close(Stream)
  905	},
  906	peek(X, ["( ", X, " ) > ", File]),
  907	smash,
  908	pred(File, ([Shell_in_string, Codes]:-
  909			shell(Shell_in_string),
  910			read_file_to_codes(File, Codes, [tail([]), encoding(utf8)])
  911		   )
  912	    ),
  913        {
  914	    delete_file(File)
  915	}.
Run shell commnad in the region, and convert the Japanese ligature to the normal form.
  920handle([shell, dakuten]) --> handle([shell]), dakuten_convert.
Run message command of Lisp.
  925handle([message]) --> region, pred([M, []]:- message(M)).
  926
  927		/*********************
  928		*     prolog/lisp    *
  929		*********************/
  930
  931solve_once -->
  932	remove_leading_comment_chars,
  933	current(X),
  934	{	string_codes(Str, X),
  935		term_string(G, Str, [variable_names(Es)]),
  936		(	once(G)		->
  937			numbervars(Es),
  938			maplist(pred([Eq, Sol]:- term_string(Eq, Sol,
  939									 [	numbervars(true),
  940										quoted(false)])),
  941					Es, Sols0),
  942			(	Sols0 = [] -> R =  "\n%@ true.\n"
  943			;	insert(",\n%@ ", Sols0, Sols),
  944				R = ["\n%@ ", Sols,  "\n%@ true."]
  945			)
  946		;	R = "\n%@ false.\n"
  947		)},
  948	peek(R).
run the current region by once as prolog query.
  954%@ ?- append([a,c],[c,d], []).
  955%@ false.
  956
  957
  958%@ ?- append([a,b],[c,d], [a,b,c,d]).
  959%@ ?- append([a,c],[c,d], X), append(X, X, Z),
  960%@ append(Z, Z, U).
  961
  962handle([once])--> region, solve_once.
Run a Prolog goal in the paragraph between \n\n and \n\n Emacs short cut: s-M-<return>
  968% ?- 1 = 1,
  969%	2 = 2,
  970%   3 = 3.
  971
  972% ?- X = 1,
  973%	Y = 2,
  974%   Z = 3.
  975
  976handle([prolog, paragraph]) --> set_mark_region, region, solve_once.
Run a prolog goal on the current line. emacs short cut: C-<return>
  982%   ?- X = 1.
  983handle([prolog, line])  --> line, solve_once.
  984
  985
  986
  987%	Put the comment symbol to each line of the region.
  988handle([comment, region])  --> region,
  989	split,
  990	maplist(comment),
  991	insert("\n"),
  992	overwrite.
Remove the comment symbol of each line of the region.
  996handle([uncomment, region])  --> region,
  997	split,
  998	maplist(uncomment),
  999	insert("\n"),
 1000	overwrite.
(append (list 1 2 3) (list 4 5 6)) => (1 2 3 4 5 6)

! handle([lisp | Keys]) --> ( { apropos_chk(Keys, paragraph) } -> set_mark_region ; [] ), region, current(X), { handle_lisp(X, Keys, Out) }, peek(Out).

Make a LaTeX enumerate environment from the items in the region.
 1019handle([enum]) --> region, snippets:environment(enumerate), overwrite.
Make a LaTeX eitemize environment from the items in the region.
 1024handle([eit])  --> region, snippets:environment(itemize), overwrite.
Put "<code>" and "</code>" around the region.
 1028handle([html,tag,code])  --> region,
 1029			 peek(X, ["<code> ", X, " </code>"]),
 1030			 overwrite.
Run the region as a goal igonoring errors.
 1034handle([ignore, goal|R]) --> region_or_line(R),
 1035	herbrand(_),
 1036	pred([X, []]:- ignore(X)).
Run the region as a goal catching errors.
 1040handle([solve,  goal|R]) -->  region_or_line(R),
 1041	herbrand(_),
 1042	pred(B, [X, ["\n", R, "\n"]]:- catch_once(X, B, R)).
Insert tab before the each line of the region.
 1047handle([shift, region]) -->  region,
 1048	split,
 1049	maplist(pred([X, ['\t'|X]])),
 1050	insert('\n'),
 1051	overwrite.
Insert A before the each line of the region.
 1055handle([insert, before, A]) -->  region,
 1056	split,
 1057	maplist(pred(A, [X, [A|X]])),
 1058	insert('\n'),
 1059	overwrite.
 1060
 1061		/****************
 1062		*     indent    *
 1063		****************/
insert tab. ! handle([indent, region]) is det. ! handle([indent, region, N]) is det. Indent the region.
 1071handle([tab, region])	-->  indent_region(0'\t, 1). %'
 1072handle([tab, region, N])-->  { atom_number(N, N0) },
 1073	indent_region(0'\t, N0).		%'
 1074handle([indent, region])--> indent_region(0'\s, 4).		%'
 1075handle([indent, region, N]) -->  { atom_number(N, N0) },
 1076	indent_region(0'\s, N0).					%'
Put framed header without centering.
 1081handle([header]) -->  region,
 1082	split,
 1083	maplist(remove_trailing_white),
 1084	maplist(detab),
 1085	remove_enveloping_nulls,
 1086	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1087	{ Width is Max + 7,
 1088	  length(Hr, Width),
 1089	  maplist(=("*"), Hr)
 1090	},
 1091	maplist(fill_trailing_spaces(Width)),
 1092	maplist(pred([X, ["\t*", X, "*\n"]])),
 1093	peek(Body,	["\t/", Hr, "*\n",
 1094				Body,
 1095				"\t*", Hr, "/\n"]),
 1096	overwrite.
 1097
 1098%
 1099fill_trailing_spaces(Width, X, [X, Y]):-
 1100	length(X, L),
 1101	J is Width - L,
 1102	length(Y, J),
 1103	maplist(=("\s"), Y).
 1104
 1105% ?- ejockey:remove_enveloping_nulls([[], a, [], b,[]], R).
 1106%@ R = [a, [], b] .
 1107remove_enveloping_nulls -->[[]], remove_enveloping_nulls.
 1108remove_enveloping_nulls -->[], remove_trailing_nulls.
 1109%
 1110remove_trailing_nulls(X, []):- nulls(X), !.
 1111remove_trailing_nulls([X|R], [X|S]):-
 1112	remove_trailing_nulls(R, S).
 1113
 1114%
 1115nulls([[]|R]):- nulls(R).
 1116nulls([]).
 1117
 1118% ?- ejockey:remove_trailing_white(X, `abc   `, Y).
 1119% ?- trace, ejockey:remove_trailing_white(`abc   `, Y).
 1120% ?- trace, ejockey:remove_trailing_white(`a`, Y).
 1121
 1122handle([trim, trailing, white]) --> region, remove_trailing_white(X), peek(X).
 1123
 1124remove_trailing_white(X) --> w(".*", X), wl("[\s\t]*$").
 1125
 1126remove_trailing_white --> w(".*", X), wl("[\s\t]*$"), peek(X).
Removing tab from each line of the region.
 1131handle([detab]) --> region, detab, overwrite.
 1132%
 1133detab_spaces(`\s\s\s\s`).
 1134%
 1135detab(X, Y):- detab(X, Y, []).
 1136
 1137% ?- ejockey:detab(`\ta\t\b`, X, []).
 1138detab([0'\t|R], X, Y):- !, detab_spaces(S),   %'
 1139	append(S, X0, X),
 1140	detab(R, X0, Y).
 1141detab([A|R], [A|X], Y):-detab(R, X, Y).
 1142detab([], X, X).
Make a framed header wiht centering.
 1147handle([shift, frame|Optional]) --> region_or_line(Optional),
 1148	split,
 1149	maplist(trim_white),
 1150	remove_enveloping_nulls,
 1151	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1152	{ Width is Max + 11 },
 1153	maplist(pred([Width, Max], ( [A, B]:-
 1154				length(B, Width),
 1155				N is (Width - Max) div 2,
 1156				length(L, N),
 1157			       	append([ ['*'], L, A, R, ['*']], B),
 1158				maplist(=('\s'), L),
 1159			        maplist(=('\s'), R)))),
 1160	{	length(Top, Width),
 1161		length(Bottom, Width) ,
 1162		Top = ['/'|L0],
 1163		append(L1, ['/'], Bottom),
 1164		maplist(=('*'), L0),
 1165		maplist(=('*'), L1)
 1166	},
 1167	maplist(pred([X, ['\t\t', X, '\n']])),
 1168	peek(Body, ['\t\t', Top, '\n',
 1169				Body,
 1170				'\t\t', Bottom, '\n']),
 1171	overwrite.
 1172
 1173/*--------------------------------------------
 1174	long comment /* ... */
 1175--------------------------------------------*/
 1176
 1177handle([long, comment]) --> region,
 1178	peek(Block, [
 1179			"/*--------------------------------------------\n",
 1180			Block,
 1181			"--------------------------------------------*/\n"
 1182			]),
 1183	overwrite.
Convert the region to a comma list of lines in the region added with single quotation marks.
 1190handle([single, quote]) --> region,
 1191	split,
 1192	remove([]),
 1193	maplist(html:single_quote),
 1194	insert(',\n'),
 1195	overwrite.
Convert the region to a comma list of lines in the region added with double quotation marks.
 1200handle([double, quote]) --> region,
 1201	split,
 1202	remove([]),
 1203	maplist(html:double_quote),
 1204	insert(',\n'),
 1205	overwrite.
Copy region to copyboad; lualatex it with standalone class.
 1209handle([region, standalone])  -->
 1210	{ call_lisp(pbcopy()),
 1211	  shell(standalone, 0)
 1212	}.
lualatex pasteboard text with standalone class.
 1216handle([pasteboard, standalone])  --> { shell(standalone, 0)}.
Show a LaTeX description environment.
 1222handle([description]) -->  peek([
 1223	"\\begin{description}[style=multiline, labelwidth=1.5cm]",
 1224	"\\item[\\namedlabel{itm:rule1}{Rule 1}] Everything is easy with \\LaTeX",
 1225	"\\item[\\namedlabel{itm:rule2}{Rule 2}] Sometimes it is not that easy\\\\",
 1226	"$\\to$ \\ref{itm:rule1} applies",
 1227	"\\end{description}\n"	]),
 1228	insert("\n"),
 1229	overwrite.
Generate a LaTeX listlisting environment.
 1234handle([list, listing]) --> region,
 1235	pred([	X, [	"\\begin{lstlisting}[caption={},label=src:]\n",
 1236			X,
 1237			"\\end{lstlisting}\n"	]]),
 1238	overwrite.
Generate a LaTeX align* environment.
 1241handle([begin, align]) --> region,
 1242	pred([	X, [	"\\begin{align*}\n",
 1243			X,
 1244			"\\end{align*}\n"	]]),
 1245	overwrite.
Generate TeX \vbox template.
 1248handle([vbox]) --> peek([
 1249	"$$\\vbox{\\offinterlineskip",
 1250        "\\halign{\\strut",
 1251        "\\vrule\\vrule\\quad\\textbf{#}\\hfill\\quad & \\vrule\\quad\\hfill #cm \\quad ",
 1252         "& \\vrule\\quad\\hfill #kg \\quad\\vrule\\vrule\\cr",
 1253        "\\noalign{\\hrule\\hrule}",
 1254        "鈴木 一太郎 & 168 & 74 \\cr",
 1255        "\\noalign{\\hrule} ",
 1256        "山田 太郎   & 170 & 72 \\cr",
 1257        "\\noalign{\\hrule} ",
 1258        "渡辺 次郎   & 192 & 103 \\cr",
 1259        "\\noalign{\\hrule\\hrule} ",
 1260        "}}$$"		]),
 1261	insert("\n").
Generate TeX halign
 1265handle([halign]) --> peek([
 1266	"\\halign{",
 1267%	"\\hfill$#$\\hfill\\qquad&\\hfill$#$\\hfill&\\quad\\text{#}\\cr\n",
 1268	"\\hfill$#=\\>$ & $#$ \\hfill & \\qquad \\mbox{#} \\cr\n",
 1269	" &  &   \\cr\n",
 1270      	" &  &   \\cr\n",
 1271	" &  &   \\cr\n",
 1272	"}"	]).
Generate a LaTeX cases environment.
 1276handle([case, equation]) --> region,
 1277	pred([	Left, [		"$", Left, "= \n",
 1278				"\\begin{cases}\n",
 1279				"     &  \\mbox{} \\\\\n",
 1280				"     &  \\mbox{} \\\\\n",
 1281				"     &  \\mbox{} \n",
 1282				"\\end{cases}$\n"	]]),
 1283	overwrite.
Generate a LaTex eqnarray* environment.
 1288handle([eqn, array]) --> region,
 1289	pred([	_, [	"\\begin{eqnarray*}\n",
 1290			"     &=&          \\\\\n",
 1291			"     &=&          \\\\\n",
 1292			"     &=&          \\\\\n",
 1293			"\\end{eqnarray*}\n"	]]),
 1294	overwrite.
Parse and Generate a LaTeX eqnarray* environment.
 1299handle([parse, eqn, array]) --> region, split, remove([]),
 1300	maplist(split(`=`)),
 1301	maplist(pred([[X|Y],	[X, " &=& ", Y]])),
 1302	insert("\\\\\n"),
 1303	pred([Body, [	"\\begin{eqnarray*}\n",
 1304			Body,
 1305			"\n\\end{eqnarray*}\n"	]]),
 1306	overwrite.
! handle([q, F,X, N]) is det.
 1314handle([q, F,X, N]) -->
 1315	peek([F, "(", X, "_1, ", X, "_2, ", "\\ldots ,", X, "_", N, ")"]).
 1319handle([q, F, X, N0, N]) -->
 1320	peek([F, "(", X, "_", N0, ", ", X, "_1, ", "\\ldots ,", X, "_", N, ")"]).
 1321%! 	handle([q]) is det.
 1322%
 1323%
 1324handle([q]) --> region, split(` `), remove([]),
 1325	pred(	([[F, X, N], E]:- handle([q, F, X, N], _, E))
 1326		&		([[F, X, N0|N], E]:- handle([q, F, X, N0, N], _, E))),	overwrite.
 1332handle([ref])	--> region, pred([X, ["\\ref{", X, "}"]]), overwrite.
 1336handle([cite])	--> region, pred([X, ["\\cite{", X, "}"]]), overwrite.
 1340handle([cs, N]) --> region,
 1341	pred([N],[X, ["\\", N, "{", X, "}"]]),
 1342	overwrite.
 1343%
 1344%! 	handle([parse, bind, context]) is det.
 1345%
 1346%
 1347handle([parse, bind, context])	--> region,	parse_bind_context, overwrite.
 1351handle([parse, bind, context, append])	--> region, parse_bind_context.
 1355handle([eval, markup, text])		--> region, eval_markup_text, overwrite.
 1359handle([eval, markup, text, append])	--> region, eval_markup_text.
 1360%
 1361%! 	handle([tag, l]) is det.
 1362%
 1363%
 1364handle([tag, l])	--> {nb_getval(phrase_tag, G), herbrand_opp(G, G0)},  % to list the saved tag
 1365	peek(G0).
 1369handle([tag, s|P])	--> region_or_line(P),		% to save the tag
 1370	peek(Q),
 1371	{parse_phrase_save(Q)},
 1372	peek("\n the tag saved.\n").
 1376handle([tag, a])  --> region,
 1377	{ nb_getval(phrase_tag, G) },
 1378	act(G),
 1379	overwrite.
 1384region_debug(X, Y):- var(X), !, region(X, Y).
 1385region_debug(X, X).
 1386
 1387
 1388handle([t, a])  --> handle([tag,a]).
Generate bibliography commands.
 1391handle([bib]) --> peek(["\\bibliographystyle{plain}\n",
 1392	"\\bibliography{jmukai,mukai}\n"]).
 1393
 1394% Convert  delicious 3 data in book/1 to bibtex form.
 1395handle([book, bibtex]) --> region,
 1396		paragraph,
 1397		remove([]),
 1398		maplist(herbrand),
 1399		maplist(book_bibitem),
 1400		insert("\n"),
 1401	    overwrite.
 1402
 1403% Convert  csv data to a dict  with keywords.
 1404handle([csv, bibtex])	--> region,
 1405						csv_to_dict,
 1406						peek(key_dict(_, L), L),
 1407						maplist(dict_bibtex).
 1408
 1409% Convert  csv data to a dict  with keywords.
 1410% ?- ejockey:csv_to_dict(`a\tb\tc\n1\t2\t3\n4\t5\t6`, R).
 1411%@ R = key_dict([a, b, c], [[a="1", b="2", c="3"], [a="4", b="5", c="6"]]) .
 1412
 1413csv_to_dict --> split,
 1414		remove([]),
 1415		maplist(split("\t")),
 1416		peek([H|R], R),
 1417		{	maplist(atom_codes, Keys0, H),
 1418			map_key_tbl(M),
 1419			map_key(Keys0, M, Keys)
 1420		},
 1421		maplist(pred(Keys,
 1422					 ([A, B]:-
 1423						 maplist(pred([K, A0, K=A1]:-
 1424									 string_codes(A1, A0)),
 1425								 Keys, A, B)))),
 1426		peek(D, key_dict(Keys, D)).
 1427
 1428%
 1429dict_bibtex(L, BB):-
 1430	maplist(pred([K=V, [K, " = ", "{", V, "}"]]), L, Items),
 1431	insert(",\n", Items, Items0),
 1432	smash(["@book{", "to be filled", ",\n", Items0, "\n}\n"], BB).
 1433%
 1434map_key_tbl([creator-author, 'ISBN'-isbn]).
 1435
 1436%
 1437map_key([],_,[]).
 1438map_key([K|R],M,[K0|R0]):- memberchk(K-K0, M), !,
 1439						   map_key(R, M, R0).
 1440map_key([K|R],M,[K|R0]):-  map_key(R, M, R0).
Generate a LaTeX thm environment.
 1445handle([thm|X])--> region_or_line(X),
 1446	peek(Y, ["\\begin{thm}\\label{thm:}\n", Y, "\\end{thm}\n"]),
 1447	overwrite.
Generate a LaTeX prop environment.
 1453handle([prop|X])--> region_or_line(X),
 1454	peek(Y, ["\\begin{prop}\\label{prop:}\n", Y, "\\end{prop}\n"]),
 1455	overwrite.
Generate a LaTeX lemma environment.
 1460handle([lem|X])--> !, region_or_line(X),
 1461	peek(Y, ["\\begin{lemma}\\label{lem:}\n", Y, "\\end{lemma}\n"]),
 1462	overwrite.
Generate a LaTeX cor environment.
 1466handle([cor|X])-->region_or_line(X),
 1467	peek(Y, ["\\begin{cor}\\label{cor:}\n", Y,"\\end{cor}\n"]),
 1468	overwrite.
Generate a LaTeX ex environment.
 1472handle([ex|X])--> region_or_line(X),
 1473	peek(Y, ["\\begin{ex}\n", Y, "\\end{ex}\n"]),
 1474	overwrite.
Generate a LaTeX df environment.
 1478handle([df|X])--> region_or_line(X),
 1479	peek(Y, ["\\begin{df}\\label{df:}\n", Y, "\\end{df}\n"]),
 1480	overwrite.
Generate a LaTeX cases environment template. For example try for f(x)
 1485handle([cases|X])--> region_or_line(X),
 1486	peek(Y, ["\\[", Y, " =\n",
 1487			 "\t\\begin{cases}\n",
 1488				 "\t\t  & (\t\t\t  ) \\\\\n",
 1489				 "\t\t  & (\t\t\t  ) \\\\\n",
 1490				 "\t\t  & (\t\t\t  ) \n",
 1491			  "\t\\end{cases}\n",
 1492			"\\]\n"
 1493			]),
 1494	overwrite.
 1495%
 1496handle([emph|X])--> region_or_line(X),
 1497	peek(Y, ["\\emph{", Y, "}"]),
 1498	overwrite.
 1499
 1500handle([mbox|X])--> region_or_line(X),
 1501	peek(Y, ["\\mbox{", Y, "}"]),
 1502	overwrite.
Generate a LaTeX rem environment.
 1506handle([rem|X])--> region_or_line(X),
 1507	peek(Y, ["\\begin{remark}\\label{rem:}\n",Y,"\\end{remark}\n"]),
 1508	overwrite.
Generate a LaTeX proof environment.
 1512handle([proof|X])-->region_or_line(X),
 1513	peek(Y, ["\\begin{Proof}\n",Y,"\\end{Proof}\n"]),
 1514	overwrite.
Insert red color macro.
 1518handle([red|X])	--> region_or_line(X),
 1519					peek(Y, ["\\Red{", Y, "}"]), overwrite.
Insert blue color macro.
 1522handle([blue|X])	--> region_or_line(X),
 1523						peek(Y, ["\\Blue{", Y, "}"]), overwrite.
Insert green color macro.
 1527handle([green|X]) --> region_or_line(X),
 1528					  peek(Y, ["\\Green{", Y, "}"]),
 1529					  overwrite.
 1530
 1531% I don't remember what is the purpose of the following handle.
 1532%!  handle([mkh])	--> region,
 1533% 	split,
 1534% 	maplist(pred( ( [X, Y]:-
 1535% 						html:single_quote(X, X0),
 1536% 						atom_codes(Y, X0)))),
 1537% 	pred([L, ( handle([names]
 1538% 					 ) --> peek(L), insert_nl, ".")]).
Put font macro \mathscr
 1542handle([ms|X])	--> region_or_line(X),
 1543					peek(Y, ["\\mathscr{", Y, "}"]), overwrite.
Generate a LaTeX euation environment with a label command.
 1547handle([eq|X])	--> region_or_line(X),
 1548	peek(Y, ["\\begin{equation}\\label{eq:}\n",
 1549				Y, "\n",
 1550			"\\end{equation}\n"]),
 1551	overwrite.
get the module name from the source in the current buffer defined by ":- module(<name>, ...)."
 1556handle([get, module, name]) -->
 1557 {
 1558	wait(progn(
 1559		setq(point_saved, point()),
 1560		'goto-char'('point-min'()))),
 1561	line_get(Obj),
 1562	obj_get([line(Line)], Obj),
 1563	string_codes(Line, Codes),
 1564	module_name(Codes, Name),
 1565	wait('goto-char'(point_saved))
 1566    },
 1567    peek(Name).
Set query context.
 1570handle([sqc]) --> handle([set, query, context]).  % for short
To make Prolog mode to expand queries in the context module   loaded in the current Emacs buffer. Otherwise, the query may cause 'undefined predicate' errors in the query unless the query is fully module prefixed.
 1577handle([set, query, context]) -->
 1578		handle([get, module, name]),
 1579		peek(C, ["% ?- module(", C, ")."]),
 1580		current(X),
 1581		{	smash(X) },
 1582		peek([]),
 1583		{	wait('keyboard-quit'()) }.
 1584
 1585		/*******************
 1586		*     directory    *
 1587		*******************/
Run the shell command pwd.
 1591handle([pwd])	-->
 1592	{
 1593		get_string(working_directory, Path)
 1594	},
 1595	peek(Path).
Set target directory.
 1599handle([set, target, directory])	-->
 1600	{	line_get(Obj),
 1601		obj_get([line(Line)], Obj),
 1602		trim_white(Line, DirPath),
 1603		string_codes(S, DirPath),
 1604		expand_file_name(S, [S0|_]),
 1605		set_string(target_directory, S0)
 1606	}.
Choose working directory, and set the working_directory to it.
 1612handle([cwd]) -->
 1613	{	choose_folder(X),
 1614		set_string(working_directory, X),
 1615		working_directory(_, X)
 1616	},
 1617	peek(X).
Change director to the HOME.
 1622handle([cd]) -->
 1623	{	expand_file_name("~/", [D]),
 1624		set_string(working_directory, D),
 1625		working_directory(_, D)
 1626	},
 1627	peek(D).
Change directory like "../"
 1632handle([cd, up]) -->
 1633	{
 1634		get_string(working_directory, Path),
 1635		change_unix_path(up, Path, New_Path),
 1636		set_string(working_directory, New_Path),
 1637		working_directory(_, New_Path)
 1638	},
 1639	peek(New_Path).
Call Finder open.
 1644handle([open])	-->
 1645	{
 1646		line_get(Obj),
 1647		obj_get([line(Line)], Obj),
 1648		trim_white(Line, Line0),
 1649		double_quote(Line0, X),
 1650		(	Line0 = [0'/|_]						% '
 1651		-> 	sh_core(open(X))
 1652		;	string_codes(XStr, X),
 1653			handle_open_relative(XStr)
 1654		)
 1655	}.
Call Finder open all files in the region.
 1658handle([open, *]) -->
 1659	{	get_string(working_directory, S),
 1660		S\== ""
 1661	},
 1662	region,
 1663	split,
 1664	remove([]),
 1665	reverse,
 1666	current(L),
 1667	{
 1668	maplist(pred(S, ([X] :-
 1669			double_quote([S, X], SX),
 1670			sh_core(open(SX)))),
 1671		L)
 1672	},
 1673	clear
 1674	;
 1675	peek("**** directory not found. ****\n").
 1676
 1677
 1678
 1679		/*****************************
 1680		*     Accessing Directory    *
 1681		*****************************/
Call Finder open for directory.
 1684handle([finder, open, directory])	-->
 1685	{
 1686		line_get(Obj),
 1687		obj_get([line(Line)], Obj),
 1688		first_token_codes(Line, Directory),
 1689		sh(open(-a('Finder'), Directory))
 1690	}.
 1691
 1692%
 1693append_slash_code([], [0'/]):-!.	%'
 1694append_slash_code(Line, Line0):- last(Line, C),
 1695	(	C == 0'/ -> Line0 = Line		%'
 1696	;   append(Line, [0'/], Line0)		%'
 1697	).
Set working directory to working_directory.
 1702handle([swd])	-->
 1703	{	line_get(Obj),
 1704		obj_get([line(Line)], Obj),
 1705		trim_white(Line, Line0),
 1706		append_slash_code(Line0, Line1),
 1707		first_token_codes(Line1, Directory),
 1708		string_codes(Dir_string, Directory),
 1709		expand_file_name(Dir_string, [Full_path|_]),
 1710		nb_setval(working_directory, Full_path),
 1711		atom_string(Full_path, S),
 1712		set_string(working_directory,S)
 1713	},
 1714	peek(Full_path).
Set working directory to the default directory.
 1720handle([swd, (.)])-->
 1721	{	call_lisp_value('default-directory', D),
 1722		string_codes(X, D),
 1723		expand_file_name(X, [Full_path|_]),
 1724		nb_setval(working_directory, Full_path),
 1725		atom_string(Full_path, S),
 1726		set_string(working_directory, S)
 1727	},
 1728	peek([]).
Open the default directory.
 1733handle([finder, default, directory])	-->
 1734	{	call_lisp_value('default-directory', D),
 1735		string_codes(X, D),
 1736		sh(open(X))
 1737	}.
 1738
 1739%
 1740handle([directory, path])	-->
 1741	{	call_lisp_value('default-directory', D)
 1742	},
 1743	peek(D).
 1744%
 1745handle([file, path]) -->
 1746	{ lisp(list('default-directory', 'buffer-name'()), List)
 1747	},
 1748	peek(List).
List all files in the working directory.
 1753handle([list, files])		--> % ls
 1754	{	get_string(working_directory, S),
 1755		S \== "",
 1756		directory_files(S, Files)
 1757	},
 1758	peek(Files),
 1759	insert("\n")
 1760	;
 1761	peek("**** directory not found. ****\n").
Convert the text possibly with ligatures to the normal normal sequences of chars.
 1767handle([dakuten])--> region,
 1768					flip(string_codes),
 1769					dakuten_convert,
 1770					overwrite.
Inverse of handle([dakuten]).
 1774handle([dakuten, flip]) --> region,
 1775					flip(string_codes),
 1776					flip(dakuten_convert),
 1777					overwrite.
List files with the ligatures resolved as in handle([dakuten]).
 1781handle([list, files, dakuten])	--> % ls
 1782	{	get_string(working_directory, S),
 1783		S \== "",
 1784		directory_files(S, Files)
 1785	},
 1786	peek(Files),
 1787	maplist(string_codes),
 1788	maplist(dakuten_convert),
 1789	insert("\n")
 1790	;
 1791	peek("**** directory not found. ****\n").
List files with a regex filter.
 1796handle([list, regex])	--> region_term,
 1797	current(Regex),
 1798	{	let(Parser, pred(Regex, [X]:- phrase(w(Regex), X, []))),
 1799		get_string(working_directory, S),
 1800		S \== "",
 1801		directory_files(S, Files)
 1802	},
 1803	peek(Files),
 1804	maplist(dakuten_convert),
 1805	maplist(string_codes),
 1806	collect(Parser),
 1807	insert("\n")
 1808	;
 1809	peek("**** directory not found. ****\n").
List all of time-stamped pdf files.
 1813handle([list, timed, pdf])	--> % ls
 1814	{	get_string(working_directory, S),
 1815		S \== "",
 1816		directory_files(S, Files),
 1817		maplist(atom_codes, Files, Codes_list),
 1818		collect(pred([Codes]:- phrase(w("[0-9]+\\.pdf"), Codes,[])),
 1819			Codes_list,
 1820			Pdf_files)
 1821	},
 1822	peek(Pdf_files),
 1823	insert("\n")
 1824	;
 1825	peek("**** directory not found. ****\n").
Move files.
 1830handle([mv])	--> % move a file over directories
 1831	{	get_string(working_directory, S),
 1832		S\== "" ,
 1833		get_string(target_directory, T),
 1834		T\== ""
 1835	},
 1836	rename(S, T)
 1837	;
 1838	peek("**** directory not found. ****\n").
Rename a file.
 1842handle([mv, (.)]) --> % rename a file at a directory
 1843	{	get_string(working_directory, S),
 1844		S \== ""
 1845	},
 1846	rename(S, S)
 1847	;
 1848	peek("**** directory not found. ****\n").
Move files at the source directory to the target directory with renaming.
 1854handle([mv, *])	-->
 1855	{	get_string(working_directory, S),
 1856		S\== "",
 1857		get_string(target_directory, T),
 1858		T\== ""
 1859	},
 1860	region,
 1861	paragraph,
 1862	remove([]),
 1863	maplist(trim_nl_mv(S,T)),
 1864	insert("\n"),
 1865	overwrite
 1866	;
 1867	peek("**** directory not found. ****\n").
 1868
 1869% c handle([rename]) is det.
 1870%   Rename a file.
 1871
 1872handle([rename]) --> handle([mv, (.)]).
Rename multi files.
 1876handle([rename, *]) -->
 1877	{	get_string(working_directory, S),
 1878		S\==""
 1879	},
 1880	region,
 1881	paragraph,
 1882	remove([]),
 1883	maplist(trim_nl_mv(S,S)),
 1884	insert("\n"),
 1885	overwrite
 1886	;
 1887	peek("**** directory not found. ****\n").
Get working directory.
 1892handle([wd])	--> {working_directory(X, X)}, peek(X).
Change working directory.
 1896handle([wd, change])	--> { line_get(Obj),
 1897		      obj_get([line(D0)], Obj),
 1898		      atom_codes(D, D0),
 1899		      working_directory(_, D)
 1900		    }.
 1901
 1902% !! Experimental !!
 1903%	handle([doc, latex]) is det.
 1904%   under debugging.
 1905%
 1906%!  handle([doc, latex]) --> region,   % @see => C-c-ee
 1907% 	paragraph,
 1908% 	remove([]),
 1909% 	maplist(split),
 1910% 	maplist(remove([])),
 1911% 	pred(([[X, [Y|_]],[X0, Y0]]:-
 1912% 	     maplist(flip(atom_codes), X, X1),
 1913% 	     maplist(expand_file_name, X1, X2),
 1914% 	     append(X2, X0),
 1915% 	     atom_codes(Y1, Y),
 1916% 	     expand_file_name(Y1, [Y0|_]))),
 1917% 	pred(([[X, Y], Y]:-
 1918% 	    doc_latex(X, Y, [public_only(false)]))).
 1919
 1920% % 	handle([global,set,key]) is det.
 1921% %   Run global-set-key lisp command.
 1922%!  handle([global,set,key]) --> region, paragraph, maplist(split),
 1923% 	maplist(remove_comment_line),
 1924% 	remove([]),
 1925% 	maplist([[X,Y], done]
 1926% 		:- (herbrand(Y, H),
 1927% 		    elisp:global_set_key(X, H))
 1928% 	       ),
 1929% 	herbrand_opp.
Run global-unset-key Lisp command.
 1933handle([global, unset, key])	-->
 1934	region_or_line(K),
 1935	{global_unset_key(K)},
 1936	peek(`unset.`).
View the source in the current buffer as an html file generated by the pldoc library.
 1942handle([pldoc]) -->
 1943	{ Doc_html = 'TMPPLDOC.html',
 1944	  atomics_to_string(['~/public_html/', Doc_html], Local_html),
 1945	  expand_file_name(Local_html,[HTML|_]),
 1946	  lisp(list('default-directory', 'buffer-name'()), List),
 1947	  atomics_to_string(List, File_source_name),
 1948	  open(HTML, write, Out_stream),
 1949	  set_output(Out_stream),
 1950	  pldoc_html:doc_for_file(File_source_name,
 1951							  [edit(false),
 1952							  public_only(false)]),
 1953	  close(Out_stream),
 1954  	  getenv(user, User_name),
 1955	  sh(open(-a('Safari'),
 1956				"http://localhost/"
 1957				+ "~"
 1958				+ User_name
 1959			    + "/"
 1960				+ Doc_html))
 1961	}.
 1962
 1963		/***************************
 1964		*     make-reftex-label    *
 1965		***************************/
 1966
 1967tex_command(Comm, Arg)--> w(".*\\"),
 1968						  w(".*", Comm0),
 1969						  "{",
 1970						  w(".*", Arg0),
 1971						  "}",
 1972						 {	string_codes(Comm, Comm0),
 1973							string_codes(Arg, Arg0)
 1974						  }.
 1975%
 1976reftex_label_prefix("subsection", "sec").
 1977reftex_label_prefix(S, Pref):- string_length(S, L),
 1978							   (	L =< 3
 1979							   ->	Pref = S
 1980							   ;	sub_string(S, 0, 3, _, Pref)
 1981							   ).
 1982
 1983%
 1984make_reftex_label("begin", Beg, Rem,
 1985				  ["\n\\label{", Pref, ":", Rem0, "}"]):- !,
 1986		reftex_label_prefix(Beg, Pref),
 1987		trim_white(Rem0, Rem, []).
 1988make_reftex_label(Comm, Arg, _,
 1989				  ["\n\\label{", Pref, ":", Arg, "}"]):-
 1990		reftex_label_prefix(Comm, Pref).
 1991
 1992%
 1993handle([reftex, label])--> line,
 1994						tex_command(Comm, Arg),
 1995						make_reftex_label(Comm, Arg).
 1996
 1997		/*****************************************
 1998		*     helper predicates for handle/4.    *
 1999		*****************************************/
 2000
 2001%  \C-l  help  (for help)
 2002
 2003%  trim_white(+X:codes, -Y:codes) is det.
 2004%	Trim white codes from both ends of X as long as possible,
 2005%	and unify Y with the remainder of X.
 2006% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P),
 2007% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P), basic:smash(P).
 2008% ?- ejockey:trim_white(`\n \t/a\tb c/ \t`, P), basic:smash(P).
 2009% ?- ejockey:trim_white(`\n \t/a\tb c/ \t\n\n`, P), basic:smash(P).
 2010% ?- ejockey:trim_white(`\n ab\n cd \nef \n\n\n`, P), basic:smash(P).
 2011trim_white --> wl("[\s\t\n]*"),
 2012			   w(".*", A),
 2013			   wl("[\s\t\n]*"),
 2014			   end_of_codes,
 2015			   peek(A).
 2016
 2017%  Qcompile: /Users/cantor/devel/zdd/prolog/util/emacs-jockey.pl
 2018%  trim_white_prefix(+X:codes, -Y:codes) is det.
 2019%	Trim white codes of the prefix of X,
 2020%	and unify Y with the remainder of X.
 2021trim_white_prefix --> wl("[\s\t]*").
 2022
 2023%  catch_once(+G:goal, +A:term, -R:term) is det.
 2024%	Unify R with A if G is true, with E if exception E is thrown
 2025%	from a child process of G, and fail if G fails.
 2026
 2027catch_once(X, A, R):- catch((once(X), R=A), E, (R = E)), !.
 2028catch_once(_, _, fail).
 2029
 2030%  line(_, -L:codes) is det.
 2031%	Get the codes of the current line with  the cursor on.
 2032line(_, Line) :- line_get(I), obj_get([line(Line)], I, _).
 2033
 2034%  partial_match(As:list, B:atom) is det.
 2035%	True if some atom in As is a prefix atom of B.
 2036
 2037% ?- ejockey:partial_match([reg, a], region).
 2038partial_match(Atoms, Fullname):-
 2039	once((
 2040	member(Shortname, Atoms),
 2041	atom(Shortname),
 2042	sub_atom(Fullname, 0, N, _, Shortname),
 2043	N>0)).
 2044
 2045% %c select_phrase(+C:cond, +P:phrase, +Q:phrase) is det.
 2046% %	Conditional phrase depending on arguments abbreviation;
 2047% %	Use default unless otherwise being specified.
 2048% select_phrase(Cond, P, _) --> {call(Cond)}, !, phrase(P).
 2049% select_phrase( _, _, Q)	  -->  phrase(Q).
 2050
 2051%  region_or_line(As:list, ?X, ?Y) is det.
 2052%	Apply region/2 or line/2 to  X, Y depending on X.
 2053
 2054region_or_line([]) --> !, region.   % region is default.
 2055region_or_line([X|_]) --> {partial_match([X], line)}, !, line.
 2056region_or_line([X|_]) --> {partial_match([X], region)}, region.
 2057
 2058%  trim_nl_mv(+S, +T, +X, -Y) is det.
 2059%	Move a file over directories.
 2060trim_nl_mv(S, T) --> trim_nl(L, R),
 2061	handle_mv(S, T),
 2062	peek(X, [L, X, R]).
 2063
 2064%  rename(S:directory, T:directory, +X:codes, -Y:codes) is det.
 2065%	Move a file over directories with specified new name.
 2066rename(S, T)-->  set_mark_region,
 2067	region,
 2068	trim_nl_mv(S, T),
 2069	overwrite.
 2070
 2071%  indent_region(+C:code, +N:int, +X, -Y) is det.
 2072%	Indent the region by padding the code C  N times.
 2073
 2074indent_region(CharCode, N) -->  region,
 2075	split,
 2076	{ 	length(Indent, N),
 2077		maplist(=(CharCode), Indent)
 2078	},
 2079	maplist(pred(Indent,
 2080		     [[], []]
 2081		    &		     [X, [Indent|X]])),	insert('\n'),	overwrite.
 handle_open_relative(+P:codes) is det
Open the object located at P given as a path relative to the working directory.
 2090handle_open_relative(Line) :-
 2091		get_string(working_directory, Path),
 2092		(	Path \== ""
 2093		->	PathStr = Path
 2094		;	PathStr = ""
 2095		),
 2096		atomics_to_string([PathStr, /, Line], X),
 2097		sh_core(open(X)).
 2098
 2099%  remove_comment_line(X:codes, Y:codes) is det.
 2100%	Remove the comment lines from X, and Unify Y with the
 2101%	remaining.
 2102
 2103% ?- ejockey:remove_comment_line([`%abc`, `%xyz`, `%hello`], R).
 2104remove_comment_line([],[]).
 2105remove_comment_line([[0'%|_]|R], R0):- !, remove_comment_line(R, R0). %'
 2106remove_comment_line([X|R], [X|R0]):- remove_comment_line(R, R0).
 2107
 2108%!  handle_mv(+S, +T, +X, -Y) is det.
 2109%	Move a file from directory S to T, whose source and target names
 2110%	are coded in X.
 2111
 2112handle_mv(S_dir, T_dir) -->
 2113	trim_nl(Left, Right),
 2114	pred([X, Y]:- foldr(  % : ===>  @
 2115		pred(   [0':,  U, [0'@  | U]]
 2116			&
 2117				[0'/,  U, [0'-  | U]]
 2118			&
 2119				[A,    U, [A|U]] ) ,
 2120		X, [], Y)),
 2121	mv_over_directory(S_dir, T_dir),
 2122	peek(A, [Left, A, Right]).
 2123
 2124
 2125%  A -->>  B   is a genral form of rules, tentatively called a `DCGX' (DCG extended) rule.
 2126%	Syntactically, A and B must be prolog terms such that A --> B forms a DCG rule.
 2127%	This rule is translated like a DCG rule, but into a predicate H that acts on contextual
 2128%	object of the form (X, E), which is called here a `state'.
 2129%	Procedually, H acts on states as a state transition action, so that we write
 2130%
 2131%	                H
 2132%		(X, E) ~~> (X', E')
 2133%
 2134%	for H((X, E), (X', E')).
 2135%
 2136%	Let H1, ..., Hn be actions for instances of the lefthand side of rules defined
 2137%	by '-->>' rules and (X0, E0) given an initial contextual objects. Then,  a sequence (H1,...,Hn)
 2138%	acts on a state (X0, E0) as an intial state, and then  produce a next state (X1, E1),
 2139%	and does successively so on  like this with a final state (Xn, En).
 2140%
 2141%	                 H1           H2      Hn
 2142%		(X0, E0) ~~> (X1, E1) ~~> ... ~~> (Xn, En).
 2143%
 2144
 2145%  mv_at_directory(+L:directory, +S:state, -S0:state) is det.
 2146%	Rename a file under L, whose  source and target names are
 2147%	coded in the state S.
 2148
 2149mv_at_directory(L) -->> dcl([dir(L)]),
 2150	paragraph,
 2151	remove([]),
 2152	maplist(split),
 2153	maplist(remove([])),
 2154	remove([]),
 2155	obj(obj_get([dir(F)])),
 2156	maplist(pred(F, ([[X|Y], "renamed."]:-
 2157		maplist(split(` `), Y, Y0),
 2158		maplist(remove([]), Y0, Y1),
 2159		maplist(insert("\\ "), Y1, Y2),
 2160		insert("@", Y2, Y3),
 2161		file_extension(Ext, X, _),
 2162		sh(mv(-i, F + X, F + Y3 + Ext)))
 2163		&
 2164		([P,Q]:- insert("\n", P, Q)))),
 2165	insert("\n").
 2166
 2167%   mv_over_directory(+L:directory, +M:directory, +S:state, -S0:state) is det.
 2168%   Move files over from L to M. The source and target name of a file
 2169%   are in the given state S.
 2170
 2171mv_over_directory(L, M) -->> dcl([dir(L), dir_target(M)]),
 2172	paragraph,
 2173	maplist(split),
 2174	maplist(remove([])),
 2175	remove([]),
 2176	obj(obj_get([dir(F), dir_target(G)])),
 2177	maplist(pred([F,G],
 2178			([[X|Y], "Renamed and moved."]:-
 2179				file_name(Y, Y0),
 2180				atomics_to_string([G,/, Y0], Y1),
 2181		 		file_extension(Ext, X, _),
 2182				modify_file_name(Y1, 0, Ext, Y2),
 2183				atom_codes(X0, X),
 2184				atomics_to_string([F,/, X0], X1),
 2185				rename_file(X1, Y2))
 2186			&
 2187			([P,Q]:- insert("\n", P, Q))
 2188		    )
 2189	       ),
 2190	insert("\n").
 2191
 2192%  file_name(+X:text, -Y:atom) is det.
 2193%	Concatenate a list X of blocks of codes into an atom Y
 2194%	with '@' as a block separator character.
 2195
 2196file_name --> insert(`@`), flatten, flip(string_codes).
 2197
 2198%  modify_file_name(+F:file_name, +I:integer, +E:extension, -G:File_name) is det.
 2199%	Modify the file name F to G by adding a minimum integer suffix J >= I
 2200%	to F when F conflicts with an existing one so that G does not so, otherwise,
 2201%	unify G with F.
 2202
 2203% ?- ejockey:modify_file_name('emacs-jockey', 0, '.pl', G).
 2204% ?- ejockey:modify_file_name('~/Desktop/test', 0, '.bib', G).
 2205% ?- ejockey:modify_file_name('~/Desktop/test', 1, '.bib', G).
 2206
 2207modify_file_name(F, 0, Ext, G):- !,
 2208	atomic_list_concat([F, Ext], F0),
 2209	(	exists_file(F0)
 2210	->	modify_file_name(F, 1, Ext, G)
 2211	;	G = F0
 2212	).
 2213modify_file_name(F, I, Ext, G):- atom_number(A, I),
 2214	atomic_list_concat([F, @, A, Ext], F0),
 2215	(	exists_file(F0)
 2216	->	J is I+1,
 2217		modify_file_name(F, J, Ext, G)
 2218	;	G = F0
 2219	).
 2220
 2221%  file_extension(-Ext:atom, +P:codes, -Q:codes) is det.
 2222%	Unify Ext with a file extension codes (including the '.' character) of
 2223%	P, and Q with the remainder prefix of P.  If no extension of P is found,
 2224%	unify Ext and Q with the empty atom '' and P, respective.
 2225
 2226% ?- ejockey:file_extension(X, `abc/.efg/a.b.c`, R).
 2227% ?- ejockey:file_extension(X, `abc/.efg/a.b.c/x`, R).
 2228
 2229file_extension(Ext) --> w(*(.)),  ".",  wl("[^\\./]*", X), end_of_list, !,
 2230	{ atom_codes(Ext, [0'. | X]) }.		%'
 2231file_extension('') --> [].
 2232
 2233%  insert_tab_nl(+N:int, +I:int, +T:list, -T0:list) is det.
 2234%	Insert tab codes or newline codes between each successive elements
 2235%	of T, and unify T0 with it, so that  writing all elements of the list T0
 2236%	in order shows up an array of raws of  N-elements, provided that I = N.
 2237
 2238% ?- ejockey:insert_tab_nl(3, 3, [a,b,c,d,e], R).
 2239insert_tab_nl(_, _, [], []).
 2240insert_tab_nl(N, 0, [X|Y], [[X,'\n']|Y0]):- !, insert_tab_nl(N, N, Y, Y0).
 2241insert_tab_nl(N, J, [X|Y], [[X,'\t']|Y0]):- J0 is J-1, insert_tab_nl(N, J0, Y, Y0).
 2242
 2243%  insert_nl(+X:list, -Y:list) is det.
 2244%	Shorthand for insert(`\n`, X, Y).
 2245
 2246insert_nl --> insert(`\n`).
 2247
 2248			/****************************************
 2249			*     listing tex command sequences.    *
 2250			****************************************/
 2251
 2252%  	handle([list, tex, cs]) is det.
 2253%   Listing tex command sequeces.
 2254%
 2255handle([list, tex, cs]) --> region,
 2256	texparse,
 2257	list_texcs,
 2258	sort,
 2259	insert("\n").
 2260
 2261%
 2262list_texcs_file(File, R):- read_file_to_codes(File, R0, []),
 2263	texparse(R0, R1),
 2264	list_texcs(R2, [], R1, []),
 2265	sort(R2, R).
 2266%
 2267list_texcs(X, Y):-  list_texcs(Y, [], X, []).
 2268
 2269%
 2270list_texcs([A|X], Y)	--> [cs(A)], !, list_texcs(X, Y).
 2271list_texcs([F|X], Y)	--> [env(F, B)], !,
 2272	{ list_texcs(X, X0, B, []) },
 2273	 list_texcs(X0, Y).
 2274list_texcs(X, Y)	--> [L], { listp(L) } , !,
 2275	{ list_texcs(X, X0, L, []) },
 2276	list_texcs(X0, Y).
 2277list_texcs(X, Y)	--> [_], !, list_texcs(X, Y).
 2278list_texcs(X, X)	--> [].
 2279
 2280
 2281		/************************************************
 2282		*     bi-directional converter for file name    *
 2283		%     with dakuten characters                   *
 2284		************************************************/
 2285
 2286%  dakuten_convert(?X:text, ?Y:text) is det and bi-directional.
 2287%	Replace each 'dakuten' and 'semi-dakuten' (voiced sound mark) ligature with
 2288%	the one character in utf8 encoding, and unify Y with the result so that Y is from
 2289%	from such ligatures; and vice versa. Note that copy-paste of Japanese file names
 2290%	of ligature free in Finder may yield codes that has (semi-)dakuten ligatures,
 2291%	which may cause troubles.
 2292
 2293% [2013/09, 2014/12]
 2294%  ex. "ば" <==> "ば”   (bi-directional)
 2295
 2296% ?- ejockey:dakuten_convert("プロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2297% ?- ejockey:dakuten_convert(`プロジェクト`, Y), ejockey:dakuten_convert(X, Y).
 2298% ?- ejockey:dakuten_convert('プロジェクト', Y), ejockey:dakuten_convert(X, Y).
 2299% ?- ejockey:dakuten_convert("プロジェクトプロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2300% 濁点 '゙'	半濁点 '゚'
 2301
 2302dakuten_convert(X, Y):- var(Y), !,
 2303	string_chars(X, U),
 2304	once(convert_chars(U, V)),
 2305	string_chars(Y, V).
 2306dakuten_convert(X, Y):-
 2307	string_chars(Y, V),
 2308	once(convert_chars(U, V)),
 2309	string_chars(X, U).
 2310
 2311convert_chars([], []).
 2312convert_chars([X, Y|R], [Z|S]):- conversion_table(Y, D, E),
 2313	chars_table_check(X, D, E, Z),
 2314	convert_chars(R, S).
 2315convert_chars([X|R], [X|S]):- convert_chars(R, S).
 2316
 2317%
 2318chars_table_check(X, [X|_], [Z|_], Z).
 2319chars_table_check(X, [_|U], [_|V], Z):- chars_table_check(X, U, V, Z).
 2320
 2321% conversion_table(a, X, Y) means that  ba <==> c  for each b in X and c in Y.
 2322conversion_table('゙',
 2323		['か', 'き', 'く', 'け', 'こ',
 2324		 'さ', 'し', 'す', 'せ', 'そ',
 2325		 'た', 'ち', 'つ', 'て', 'と',
 2326		 'は', 'ひ', 'ふ', 'へ', 'ほ'],
 2327		['が', 'ぎ', 'ぐ', 'げ', 'ご',
 2328		 'ざ', 'じ', 'ず', 'ぜ', 'ぞ',
 2329		 'だ', 'ぢ', 'づ', 'で', 'ど',
 2330		 'ば', 'び', 'ぶ', 'べ', 'ぼ']).
 2331conversion_table('゙',
 2332		['ウ',
 2333		 'カ', 'キ', 'ク', 'ケ', 'コ',
 2334		 'サ', 'シ', 'ス', 'セ', 'ソ',
 2335		 'タ', 'チ', 'ツ', 'テ', 'ト',
 2336		 'ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2337		['ヴ',
 2338		 'ガ', 'ギ', 'グ', 'ゲ', 'ゴ',
 2339		 'ザ', 'ジ', 'ズ', 'ゼ', 'ゾ',
 2340		 'ダ', 'ヂ', 'ヅ', 'デ', 'ド',
 2341		 'バ', 'ビ', 'ブ', 'ベ', 'ボ']).
 2342conversion_table('゚',
 2343		['は', 'ひ', 'ふ', 'へ', 'ほ'],
 2344		['ぱ', 'ぴ', 'ぷ', 'ぺ', 'ぽ`']).
 2345conversion_table('゚',
 2346		['ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2347		['パ', 'ピ', 'プ', 'ペ', 'ポ']
 2348	      ).
 2349
 2350
 2351
 2352%  trim_nl(-L:codes, -R:codes, +X:codes, -Y:codes) is det.
 2353%	Trim successive new line codes from both ends of X  as long as possible,
 2354%	and unify Y with the remainder of X.
 2355
 2356% ?-ejockey:trim_nl(L, R, `abc`, Y).
 2357% ?-ejockey:trim_nl(L, R, `\n\n\n`, Y).
 2358% ?-ejockey:trim_nl(L, R, `\nabc\n`, Y).
 2359% ?-ejockey:trim_nl(L, R, `\n\nabc\n\n`, Y).
 2360% ?-ejockey:trim_nl(L, R, `\n\n向井\n国昭\nabc\n\n`, Y).
 2361
 2362%
 2363trim_nl(L, R) --> wl(*("\n"), L),
 2364	w(*(.), Y),
 2365	wl(*("\n"), R),
 2366	end_of_list,
 2367	peek(Y).
 2368
 2369%
 2370end_of_list([], []).
 2371
 2372%  meta_handle(?X, -Y) is det.
 2373%	Parse the first line of the region for a handle command,
 2374%	and apply the command to the rest of the region.
 2375
 2376meta_handle --> region,
 2377	w("[^\n]*$", L),
 2378	{ parse_line(X, L, []),
 2379	  maplist(atom_codes, A, X)
 2380	},
 2381	pred([A, L], [U, V]:-
 2382		once(find_handle_call(A, L, U, V))).
 2383
 2384%  parse_line(+X:list, +Y:codes, -Z:codes) is det.
 2385%	Unify X with a list of (S-expression) tokens that
 2386%	appears in the deference between Y and Z.
 2387
 2388% ?- ejockey:parse_line(X, `a b c`, []).
 2389% ?- ejockey:parse_line(X, `a "b c""d e"`, []).
 2390% ?- ejockey:parse_line(X, `a "b c"'d \\"e'`, []).
 2391% ?- ejockey:parse_line(X, `'d\\e'`, []).
 2392% ?- ejockey:parse_line(X, `'d\e'`, []).
 2393% ?- ejockey:parse_line(X, `'d\\\\e'`, []).
 2394% ?- ejockey:parse_line(X, `"d\\\\\e"`, []).
 2395% ?- ejockey:parse_line(X, `"a"`, []).
 2396
 2397parse_line(X) --> wl("[\s\t]*"), parse_line0(X).
 2398
 2399parse_line0([A|X]) --> token(A), !, parse_line(X).
 2400parse_line0([]) --> [].
 2401
 2402
 2403% ?-coalgebra:show_am("\"([^\"\\\\]|(\\\\.))*\"" | "'([^'\\\\]|(\\\\.))*'" | "[^ \t\"']+").
 2404
 2405
 2406%  token(-X:token, +Y:codes, -Z:codes) is det.
 2407%	Unify X with a token in S-expression for the difference betwee Y and Z.
 2408
 2409% ?- ejockey:token(X, `abcd  `, Y).
 2410% ?- ejockey:token(X, `"ab\\\"d"`, Y), smash(X).
 2411%@ "ab\"d"
 2412% ?- ejockey:token(X, `"ab\\\"c\\\"d"`, Y), smash(X).
 2413%@ "ab\"c\"d"
 2414
 2415token(X) --> wl( "\"([^\"\\\\]|(\\\\.))*\""
 2416	       | "'([^'\\\\]|(\\\\.))*'"
 2417	       | "[^\s\t\"']+",
 2418		X).
 2419
 2420%  prolog_identifier(N:, X:codes, Y:codes) is det.
 2421%	Unify N with a list of codes
 2422%	such that N is the longest prolog_identifier prefix of X,
 2423%	and Y with the remaining suffix of X.
 2424%
 2425
 2426prolog_identifier(N) --> wl("[a-z][a-zA-Z0-9_]*", N, []).
 2427
 2428%  keyword(N:, X:codes, Y:codes) is det.
 2429%	Unify N with a list of codes
 2430%	such that N is the longest keyword prefix of X,
 2431%	and Y with the remaining suffix of X.
 2432%
 2433
 2434keyword(N) --> wl("[a-zA-Z][a-zA-Z0-9_]*", N, []).
 2435
 2436%  collect_tokens(+W:type, +X:codes, -Y:tokens) is det.
 2437%	Collect tokens in X that satisfies W, and
 2438%	unify Y with it.
 2439
 2440collect_tokens(W, X, Y):- collect_tokens(W, Y, [], X, []).
 2441
 2442%
 2443collect_tokens(W, X, Y) --> [_], collect_tokens(W, X, Y).
 2444collect_tokens(_, X, X)-->[].
 2445
 2446% % [2013/10/07] To escape special characters of the file name
 2447% % in order to pass it to sh/1.
 2448% % ?- ejockey:escape_shell_char(`a : (b)`, R), atom_codes(A, R).
 2449% %@ A = 'a \\@ \\(b\\)' .
 2450
 2451escape_shell_char(X, Y):-
 2452  foldr(pred(	[0'(,  U, [0'\\,    0'(  | U]	] &		%'
 2453		[0'),  U, [0'\\,    0')  | U]	] &
 2454		[0'\', U, [0'\\,    0'\' | U]	] &
 2455		[0':,  U, [0'\\,    0'@  | U]	] &
 2456		[0'/,  U, [0'\\,    0'@  | U]	] &
 2457		[A,    U, [A|U]			]
 2458	    ),
 2459	X, [], Y).
 2460
 2461% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X).
 2462
 2463% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X),
 2464%	basic:smash(X).
 2465
 2466remove_leading_comment_chars(X, Y) :-
 2467	remove_leading_comment_chars(Y, [], X, []).
 2468
 2469%
 2470remove_leading_comment_chars(X, Y) -->
 2471	wl("([% \t]|(%@*)|(\\?-))*"),
 2472	wl("[^\n]*", X, X0),
 2473	remove_leading_comment_chars_continue(X0, Y).
 2474%
 2475remove_leading_comment_chars_continue([0'\n|X], Y) --> "\n",  %' %
 2476	remove_leading_comment_chars(X, Y).
 2477remove_leading_comment_chars_continue(X, X) --> [].
 2478
 2479%
 2480comment([], []).
 2481comment(X, ["% "|X]).
 2482
 2483uncomment --> wl("%+ ?"|[]).
 2484
 2485module_name(Codes, Name):- once(module_name(Name, Codes, _)).
 2486
 2487module_name(Name) --> wl("[\s\t]*:-[\s\t]*"),
 2488		      "module(",
 2489		      wl("[^,\s\t]+", Name).
 2490module_name(????) --> [].
 2491
 2492%
 2493white_filler --> wl("[\s\t\n]*").
 2494%
 2495non_white_line(X):- \+ white_filler(X, []).
 2496
 2497% ?- C = `ab cd`, ejockey:to_ascii_space(`ab cd`, R).
 2498%@ C = [97, 98, 12288, 99, 100],
 2499%@ R = [97, 98, 32, 99, 100].
 2500
 2501to_ascii_space(X, Y) :- once(to_ascii_space(Y, [], X, [])).
 2502
 2503to_ascii_space([0'\s|X], Y) --> " ", to_ascii_space(X, Y).  % '
 2504to_ascii_space([C|X], Y)--> [C], to_ascii_space(X, Y).
 2505to_ascii_space(X, X)--> []