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.
Asssuming a global variable paragraph_width is set, the region is filled so that the width of each line fits the specified width.
   33% ?- nb_setval(paragraph_width, 3).
   34
   35% for exampe, the region of this content
   36% a
   37%   b    c
   38% d e t
   39
   40% ==>  is filled as this:
   41% a b
   42% c d
   43% e t
   44
   45handle([fill, paragraph]) --> region,
   46	current(X),
   47	{	words(Words, [], X, []),
   48		maplist(string_codes, SWords, Words),
   49		(	nb_current(paragraph_width, Width)->true
   50		;	Width = 10
   51		),
   52		fill_paragraph(Width, P, [], SWords)
   53	},
   54	peek(P),
   55	maplist(insert(" ")),
   56	insert("\n"),
   57	overwrite.
   58
   59% ?- fill_string_paragraph(5, "a  b  c  d", P).
   60%@ P = [["a", "b", "c"], ["d"]].
   61% ?- fill_string_paragraph(5, "a\t\t\r\n  b\n  c\n  d\n", P).
   62%@ P = [["a", "b", "c"], ["d"]].
   63
   64fill_string_paragraph(K, X, P):- string_codes(X, Y),
   65	words(Words_in_codes, [], Y, []),
   66	maplist(string_codes, Words_in_string, Words_in_codes),
   67	fill_paragraph(K, P, [], Words_in_string).
   68
   69% ?-words(X, [], `abc`, []), maplist(flip(string_codes), X, R).
   70% ?-words(X, [], `\t\t`,[]), maplist(flip(string_codes), X, R).
   71% ?-words(X, [], ` ab c\td \n`,[]), maplist(flip(string_codes), X, R).
   72
   73words([X|Y], Z) --> wl("[^\s\t\n\r]+", X, []), !, words(Y, Z).
   74words(X, Y) --> wl("[\s\t\n\r]+"), !, words(X, Y).
   75words(X, X) --> [].
   76
   77% ?- fill_paragraph(3, P, [], [a,a,a,a,a,a,a]).
   78
   79fill_paragraph(_, P, P, []):-!.
   80fill_paragraph(W, P, Q, R):-
   81	fill_line(W, W, P, U, R, U),
   82	fill_paragraph(W, U, Q, U).
   83
   84% ?- fill_line(5, 5, X, [], [a, a, a, a, a, a, a, a, a], R).
   85% ?- fill_line(5, 5, X, [], [a, a, a, a, a, a], R).
   86% ?- fill_line(1, 1, X, [], [a, a, a], R).
   87% ?- fill_line(10, 10,  X, [], [ab, cd, e, f, ghi, a, a, a, a], R).
   88% ?- fill_line(10, 10,  X, [], [ab], R).
   89
   90fill_line(W, W, X, X, [], []):-!.
   91fill_line(_, _, [[]|X], X, [], []):-!.
   92fill_line(Width, K, X, Y, [Word|U], V):-
   93	insert_word_at_end(Width, K, K0, X, Z, Word),
   94	fill_line(Width, K0, Z, Y, U, V).
   95
   96%
   97insert_word_at_end(Width, K, K0, X, Y, Word):-!,
   98	string_length(Word, A),
   99	compare(C, A, K),
  100	(	C = (=) ->
  101		X = [[Word]|Y],
  102		K0 = Width
  103	;	C = (<) ->
  104		X = [[Word|P]|X0],
  105		Y = [P|X0],
  106		K0 is K-(A + 1)
  107	;	Width =< A  ->
  108		X = [[]|[[Word]|Y]],
  109		K0 is Width
  110	;   X = [[],[Word|P] | Q],
  111		Y = [P|Q],
  112		K0 is Width -(A + 1)
  113	).
 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.
  123codes_to_strings(Delim, X, Y):-
  124	string_codes(X0, X),
  125	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.
  133numbering(As, X, Y):-
  134	maplist(pred([A, A-A0]:-string_concat(A, "(", A0)), As, Bs),
  135	(	member(A-A0, Bs),
  136		string_concat(A0, Z, X) ->
  137		nb_getval(A, C),
  138		C0 is C+1,
  139		nb_setval(A, C0),
  140		atomics_to_string([A0, C0, " ,", Z], Y)
  141	;	Y = X
  142	).
 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.
  151% ?- nb_setval(abc, 0),
  152%	renumbering([abc], "",  Y),
  153%	renumbering([abc], "uvw(x)",  Z),
  154%	renumbering([abc], "abc(2, U)",  U).
  155%@ Y = "",
  156%@ Z = "uvw(x)",
  157%@ U = ["abc(1,U)", "."].
  158
  159renumbering(As, X, Y) :-
  160	(	member(A, As),
  161		string_concat(A, R, X),
  162		string_concat("(", _, R) ->
  163		nb_getval(A, C),
  164		C0 is C + 1,
  165		nb_setval(A, C0),
  166		term_string(Z, X,
  167					[	module(fol_prover),
  168						variable_names(E)]),
  169		Z =.. [_, _|U],
  170		Y0 =..[A, C0|U],
  171		maplist(call, E),
  172		term_string(Y0, Y1,
  173					[	module(fol_prover),
  174						quoted(false)]),
  175		Y = [Y1,"."]
  176	;	Y = X
  177	).
  178
  179/* consider C-<return> as setup for (re)numbering terms.
  180?- nb_setval(fs, [valid_formula, invalid_formula, unsatisfiable_formula]).
  181?- nb_getval(fs, X).
  182*/
  183
  184% ?- append([a,b],[c,d], []).
  185% ?-  X=1,
  186%	 Y=2,
  187%	Z = 3.
This handle numbering lines in the region using the numbering/3.
  193handle([numbering, terms])--> region,
  194	{	nb_getval(fs, Fs),
  195		forall(member(F, Fs), nb_setval(F, 0)) },
  196	codes_to_strings("\n"),
  197	maplist(numbering(Fs)),
  198	insert("\n"),
  199	overwrite.
This handle renumbering lines in the region using the renumbering/3.
  205handle([renumbering, terms])-->  region,
  206	{ nb_getval(fs, Fs),
  207	  forall(member(F, Fs), nb_setval(F, 0)) },
  208	codes_to_strings("\n"),
  209	maplist(renumbering(Fs)),
  210	insert("\n"),
  211	overwrite.
  212
  213handle([renumbering, terms, buffer])-->	mark_whole_buffer,
  214	handle([renumbering, terms]).
  215
  216
  217			/***********************
  218			*     Emacs Handler    *
  219			***********************/
  220%
  221handle([halt]) --> {halt}.
  222%
  223handle([count, paragraph]) -->region,
  224	  paragraph,
  225	  remove([]),
  226	  length,
  227	  fsnumber_codes.
  228
  229		/*************************
  230		*     sed-like usage.    *
  231		*************************/
  232
  233% Example.
  234% wl("(..)") >> ["hello"]
  235% abcd
  236
  237% Example.
  238% (w(".*", A), wl("b+")) >> pred(A, [A])
  239% aaabbcccbdddbeee
  240
  241handle([sed|Optional]) --> region,
  242	   phrase((wl("[^\n]*", SedCommandText), wl("\n+"))),
  243		{	herbrand(_, SedCommandText, SedPhrase),
  244			let_sed(Sed, SedPhrase)
  245		},
  246		call(Sed),
  247		optional_overwrite(Optional).
nb_setval(sed, S), where S is the sed phrase, which is converted from the region.
  252handle([let, sed, Global]) --> region, current(Region),
  253		{	herbrand(_, Region, SedPhrase),
  254			let_sed(Sed, SedPhrase),
  255			nb_setval(Global, Sed)
  256		},
  257		clear.
Apply the sed action stored in global S to the region. Optional buffer action is append/overwrite like for other handles.
  264handle([apply, sed, S|Optional]) --> region,
  265	{	nb_getval(S, Sed) },
  266	call(Sed),
  267	optional_overwrite(Optional).
  268%
  269handle([one, line]) --> region,
  270		sed(wl("[\n\s\t]+") >> "\s").
  271%
  272handle([pldoc, action]) -->
  273	region,
  274	split,
  275	maplist(insert_plus_action),
  276	insert("\n"),
  277	overwrite.
  278
  279
  280handle([prove])--> region,
  281	split,
  282	remove([]),
  283	maplist(pred(([X, Y-S]:- string_codes(S, X),
  284				 term_string(Z, S, [module(fol_prover)]),
  285				 arg(1, Z, Y)
  286				 ))),
  287	maplist(pred([F-S, [S, Out, "\n"]]:- fol_prover:prove(F, Out))).
  288
  289
  290handle([free, variant])--> region, % get region in codes.
  291	split,			% split by `\n`
  292	remove([]),		% remove empty lines.
  293	maplist(pred(([X, Y-S]:- string_codes(S, X),	% parse each line as a term.
  294				 term_string(Y, S, [module(fol_prover)])))),
  295	peek(Terms, []),	% get current contents, and put [] as a inital value.
  296	add_non_variant(Terms),	% remove terms so that no variant pairs there.
  297	maplist(pred([_-S, [S,"\n"]])),	% put orginal terms with new line code at end.
  298	reverse,
  299	overwrite.  % replace the input region with the slimmed result.
  300
  301% ?- add_non_variant([A-1, B-2, A-1], [], R). % note that A is a variant of B.
  302% ?- add_non_variant([f(A)-1, g(B)-2, f(A)-2], [], R).
  303
  304add_non_variant([], X, X).
  305add_non_variant([P|U], X, Y):- add_non_variant_one(P, X, Z),
  306	add_non_variant(U, Z, Y).
  307%
  308add_non_variant_one(A-B, X, Y):-
  309	(	member(C-_, X), variant(A, C) -> Y = X
  310	;	Y = [A-B|X]
  311	).
  312%
  313insert_plus_action --> "%c", w("[\s\t]*"),
  314					   "handle(",
  315					   peek(X, ["%%\thandle(+Action:", X]).
  316insert_plus_action --> [].
Interprete the first line of the region as the handle call with the rest of the region as an argument.
  323handle([meta, handle]) --> region,
  324	handle_parse_eval(_, _),
  325	peek(R, ["===>\n", R]).
`Overwrite' version of handle([meta, handle]).
  330handle([meta, handle, overwrite]) --> region,
  331	handle_parse_eval(Tag_codes, _),
  332	peek(R, [Tag_codes,".\n", R]),
  333	overwrite.
  334
  335handle_parse_eval(Tag, Rest, X, Y) :-
  336	 append(Tag, [0'., 0'\n | Rest], X), !,
  337	 string_codes(S, Tag),
  338	 term_string(H,  S),
  339 	 expand_arg(H, [], H0, Aux, []),
  340	 maplist(assert, Aux),
  341	 meta_handle(H0, ejockey, modify_handle, [Rest, Y]).
  342%
  343modify_handle(overwrite(X, X), _, [], true).
  344modify_handle(overwrite, _, [X, X], true).
  345modify_handle(handle(U), M, [X, Y], BodyH):-
  346	clause(M:handle(U, X, Y), BodyH),
  347	!.
  348modify_handle(handle(U, X, Y), M, [], BodyH):-
  349	clause(M:handle(U, X, Y), BodyH),
  350	!.
  351
  352%	handle([remove, double, slash, entry]) is det.
  353%	remove all lines which has a gingle "//" at end.
  354handle([remove, double, slash, lines])--> region,
  355	split,
  356	remove_double_slash_lines,
  357	insert("\n"),
  358	overwrite.
  359
  360% ?- double_slash_line(`abc // `, []).
  361% ?- double_slash_line(`abc /// `, []).
  362check_double_slash--> wl("[^/]*//"), wl("[\t\n\s]*").
  363%
  364remove_double_slash_lines([], []).
  365remove_double_slash_lines([X|Xs], Ys):-
  366	check_double_slash(X,[]),
  367	!,
  368	remove_double_slash_lines(Xs, Ys).
  369remove_double_slash_lines([X|Xs], [X|Ys]):-
  370	remove_double_slash_lines(Xs, Ys).
Reload the file at the current buffer, dropping the suffix "<..>" if exists.
  375handle([load, buffer]) -->
  376	{	load_buffer(Name),
  377		message([Name, " reconsulted."])}.
  378
  379load_buffer(Y) :-
  380	lisp(list('default-directory', 'buffer-name'()), [X, Y]),
  381	atomics_to_string([X, /, Y], Z),
  382	(	exists_file(Z) -> Z0 = Z
  383	;	sub_string(Z, _, _, 1, ">"),
  384		sub_string(Z, J, 1, _, "<"),
  385		sub_string(Z, 0, J, _, Z0)
  386	),
  387    load_files([Z0]).
  388
  389handle([wrap])-->region,
  390	split,
  391	remove([]),
  392	flip(cons(PredName)),
  393	maplist(pred(PredName, [A, [PredName, "(", A, ")."]])),
  394	insert("\n"),
  395	overwrite.
  396%
  397handle([collect, functors]) --> region,
  398 	swap_args:elem_list(X, []),
  399	{	swap_args:collect_functors(X,  Y, []),
  400		sort(Y, Y0),
  401		insert(",\n", Y0, Y1)
  402	},
  403	peek(["[", Y1, "]"]).
  404%
  405handle([set, functors, list]) --> region,
  406	herbrand,
  407	current(Sgn_list),
  408	{ nb_setval(functors_list, Sgn_list) },
  409	peek("*functors_list set*\n").
  410
  411%
  412handle([insert, last, arg]) --> region,
  413	{ nb_getval(functors_list, Sgn),
  414	  (		nb_current(arg_name, Arg), Arg \== [] -> true
  415	  ;		Arg = "State"
  416	  ),
  417	  string_concat(" ", Arg, Arg0)
  418	},
  419	swap_args:elem_list(X, []),
  420	peek(X),
  421	swap_args:edit_elem_list(swap_args:insert_last_arg, Sgn, Arg0),
  422	overwrite.
  423%
  424handle([set, string, V]) --> line,
  425	flip(string_codes),
  426	current(String),
  427	{ call_lisp(setq(V, String), noreply)},
  428	clear.
  429
  430%
  431handle([get, string, X]) -->
  432	{ call_lisp(X, string(Y)) },  % string(t) => ".."
  433	peek(Y).
  434
  435% ?- trim_line_string(` ab c \n `, X).
  436expand_tilda(X, Y):- expand_file_name(X, [Y|_]).
Remove comments in the region.
  441handle([remove, comment]) --> region,
  442							  remove_comment,
  443							  overwrite.
  444
  445handle([luatex])--> region,
  446	current(R),
  447	peek([]),
  448	{
  449		expand_tilda("~/tmp/deldel.tex", TeXFile),
  450		expand_tilda("~/tmp/preamble.tex", Preamble),
  451		Fs=	[text("\\RequirePackage{luatex85}\n"),
  452			text("\\documentclass{ltjsarticle}\n"),
  453			text("\\usepackage[hiragino-pron,jis2004]{luatexja-preset}\n"),
  454			file(Preamble),
  455			text("\\begin{document}\n"),
  456			codes(R),
  457			text("\\end{document}\n") ],
  458			assemble(Fs, TeXFile)
  459	},
  460	{	expand_tilda("~/tmp", TMP),
  461		qshell(	cd(TMP) ;
  462				lualatex("deldel") ;
  463				open(-a("Preview"), "deldel.pdf")
  464			)
  465	}.
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).

  484% for short.
  485handle([cpr|Optional])-->handle([compile,pac,region|Optional]).
  486
  487handle([compile, pac, region|Optional]) --> region,
  488	flip(string_codes),
  489	string_to_terms,
  490	compile_terms_to_qstring,
  491	optional_overwrite(Optional).
  492
  493handle([terms|Optional]) --> region,
  494	flip(string_codes),
  495	string_to_terms,
  496	optional_overwrite(Optional).
  497
  498%
  499optional_overwrite(Optional) -->
  500	{ partial_match(Optional, overwrite) }, !,
  501	overwrite.
  502optional_overwrite(_) --> [].
  503
  504%
  505handle([region, string]) --> region, escape_codes_for_string.
  506%
  507escape_codes_for_string(X, [0'"|Y]):-	 %'
  508	escape_codes_for_string_(X, Y).
  509%
  510escape_codes_for_string_([], [0'"]):-!. %'
  511escape_codes_for_string_([X|P], Q):-
  512	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  513	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  514	;	X = 0'" -> Q = [0'", 0'"|Q0]		%"
  515	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  516	;	Q = [X|Q0]
  517	),
  518	escape_codes_for_string_(P, Q0).
  519%
  520handle([region, atom]) --> region, escape_codes_for_atom.
  521
  522escape_codes_for_atom(X, [0'\'|Y]):-  %'
  523	escape_codes_for_atom_(X, Y).
  524%
  525escape_codes_for_atom_([], [0'\']):-!. %'
  526escape_codes_for_atom_([X|P], Q):-
  527	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  528	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  529	;	X = 0'\' -> Q = [0'\', 0'\'|Q0]		%'
  530	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  531	;	Q = [X|Q0]
  532	),
  533	escape_codes_for_atom_(P, Q0).
  534
  535handle([region, bq]) --> region, escape_codes_for_BQ.
  536
  537escape_codes_for_BQ(X, [0'\`|Y]):-  %'
  538	escape_codes_for_BQ_(X, Y).
  539%
  540escape_codes_for_BQ_([], [0'\`]):-!. %'
  541escape_codes_for_BQ_([X|P], Q):-
  542	(	X = 0'\n -> Q = [0'\\, 0'n|Q0]		%'
  543	;	X = 0'\t -> Q = [0'\\, 0't|Q0]		%'
  544	;	X = 0'\` -> Q = [0'\`, 0'\`|Q0]		%'
  545	;	X = 0'\\ -> Q = [0'\\, 0'\\|Q0]		%'
  546	;	Q = [X|Q0]
  547	),
  548	escape_codes_for_BQ_(P, Q0).
Compile pac clauses in the region.
  554% ?- ejockey:handle([compile, pac, generic], `~/local/lib/pacpl7/a.pl`, R).
  555handle([compile, pac, generic]) -->
  556	region,
  557	split,
  558	maplist(trim_white),
  559	remove([]),
  560	maplist(pred([X, F]:- string_codes(F,  X))),
  561	(	maplist(compile_pac_generic),
  562		peek([]),
  563		{message("done")},
  564		!
  565	;	peek([]),
  566		{message("Error ! file not exists ?")}
  567	).
  568
  569% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a.pl", X).
  570% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a.pac", X).
  571% ?- ejockey:compile_pac_generic("~/local/lib/pacpl7/a", X).
  572compile_pac_generic(In, Files):-
  573	expand_file_name(In, Files),
  574	maplist(compile_pac_generic, Files).
  575%
  576compile_pac_generic(Src):-
  577	once(determine_source(Src, Src0)),
  578	setup_call_cleanup(open(Src0, read, SX, [encoding(utf8)]),
  579		stream_parse_pac_terms(SX, Xs, []),
  580		close(SX)),
  581	compile_terms_to_qstring(Xs, QuasiText),
  582	determine_target(Src0, Target),
  583	setup_call_cleanup(open(Target, write, SY, [encoding(utf8)]),
  584		write_qstring(QuasiText, SY),
  585		close(SY)).
  586%
  587determine_source(X, X):- string_drop_suffix(X, ".pl", X0), !,
  588	string_concat(X0, ".pac", X1),
  589	\+exists_file(X1).
  590determine_source(X, X):- string_end_with(X, ".pac"), !,
  591	exists_file(X).
  592determine_source(X, Y):- member(M, [".pac", ".pl"]),
  593	string_concat(X, M, Y),
  594	exists_file(Y),
  595	!.
  596%
  597determine_target(X, Y):- string_drop_suffix(X, ".pac", Z), !,
  598	string_concat(Z, ".pl", Y).
  599determine_target(X, X):- string_drop_suffix(X, ".pl", Y),
  600	modify_file_name(Y, 0, '.pac', Keep),
  601	rename_file(X, Keep).
  602
  603% ?- ejockey:string_drop_suffix("abcd", "cd", Y).
  604string_end_with(X, S):- sub_string(X, _, _, 0, S).
  605
  606% ?- ejockey:string_drop_suffix("abcd", "cd", Y).
  607string_drop_suffix(X, S, Y):- sub_string(X, J, L, 0, S),
  608	sub_string(X, 0, J, L, Y).
  609%
  610ignore_pac_term(term_expansion-->expand_pac).
  611
  612%
  613stream_parse_pac_terms(Stream, U, Q) :-
  614		stream_term_string(Eqs, X, Stream),
  615		(	at_end_of_stream(Stream)	->	U = Q
  616		;	ignore_pac_term(X)	->  stream_parse_pac_terms(Stream,  U, Q)
  617		;  	(	is_backquote_begin(X, X0),
  618				set_prolog_flag(back_quotes, symbol_char)
  619			; 	is_backquote_end(X, X0),
  620				set_prolog_flag(back_quotes, codes)
  621			; 	X0 = X
  622			),
  623			!,
  624			U = [X0-Eqs|P],
  625			stream_parse_pac_terms(Stream, P, Q)
  626		).
  627%
  628compile_terms_to_qstring(Xs, QuasiText):-
  629	compile_pac(Xs, P, []),
  630	pred_grouping(P, Blocks),
  631	maplist(maplist(pred([P, pair(X0, H0)]:-
  632							 clause_to_string(P, X0, H0))),
  633			Blocks, ExpandedBlocks),
  634	maplist(pred(([Block, [Cs,"\n", Hs]]:-
  635				maplist(pred([pair(U,V), U, V]), Block, Cs, Hs))),
  636			ExpandedBlocks, QuasiText).
  637
  638%
  639write_qstring([A|B], S):- write_qstring(A, S),
  640						  write_qstring(B, S).
  641write_qstring([], _).
  642write_qstring(A, S):- write(S, A).
Compile a pac clause at the region.
  647handle([compile, predicate|Flag]) --> region,
  648	herbrand(web, Eqs),
  649	current(X),
  650	{ pac_listing:compile_pred_word(X, Eqs, H0, R0) },
  651	peek([R0, "\n", H0, ".\n"]),
  652	overwrite(Flag).
  653
  654%	select_phrase(partial_match(Flag, overwrite), overwrite, =).
Expand pac clauses.
  659handle([expand, pac]) --> region,
  660	pred([X, Y]:- string_codes(Y, X)),
  661	parse_pac_terms,
  662	pred([Xs, P]:- compile_pac(Xs, P, [])),
  663	pred_grouping,
  664	maplist(maplist(pred([P, pair(X0, H0)]:-
  665							 pac_listing:clause_to_string(P, X0, H0)))),
  666	maplist(pred(([Block, [Cs,"\n", Hs]]:-
  667				maplist(pred([pair(U,V), U, V]), Block, Cs, Hs)))).
  668
  669
  670
  671%
  672parse_pac_terms(X, Pacs):-
  673	setup_call_cleanup(
  674		open_string(X, Stream),
  675		stream_parse_pac_terms(Stream, Pacs, []),
  676		close(Stream)).
Expand pac clauses, and rewrite the region with them.
  681handle([expand, pac, overwrite]) -->
  682	handle([expand,pac]),
  683	overwrite.
Return the string on which the cursor is.
  688handle([neighbor, string]) --> {neighbor_string("[","]", X)},
  689							   peek(X).
Collect Prolog identifiers.
  694handle([collect, identifiers]) --> region,
  695	collect_tokens(prolog_indentifier),
  696	maplist(herbrand),
  697	sort,
  698	insert("\n").
Collect keywords.
  703handle([collect, keywords]) --> region,
  704	collect_tokens(keyword),
  705	maplist(herbrand),
  706	sort,
  707	insert("\n").
Copy the current head of a clause, and insert it after modifying before the line.
  713handle([copy, head])-->
  714	 {	line_get(Obj),
  715		obj_get([line(Line)], Obj),
  716		string_codes(Line, Codes),
  717		phrase(( wl("[\s\t]*"),
  718				 w(".*", Head),
  719				 w("[\s\t]*((-->)|(:-))")),
  720			   Codes, _)
  721		},
  722	 peek(["%%\t", Head, " is det.\n%\n%\n", Line]),
  723	 overwrite.
Swap I-th argument with J-th one in for all terms with functor Name.
  729handle([swap, args, N, I, J]) -->
  730	{ atom_number(I, I0),
  731	  atom_number(J, J0) },
  732	region,
  733	pred([N, I0, J0],
  734		 ([X, Y]:-
  735			 swap_args:swap_args_of(N, I0, J0, X, Y))),
  736	overwrite.
ask LISP to eval global-set-key
  741handle([handle, kbd])  --> region,
  742	pred(([S, []] :- term_codes(E, S),
  743		arg(1, E, K),
  744		arg(2, E, P),
  745		global_set_kbd(K, P))).
Activate emacs dired with a prompt.
  750handle([dired])  --> dired.
Mark all *.pl files in DIRED.
  755handle([dired, mark, swipl]) --> {dired_mark_swipl}.
Swap the first two arguments.
  759handle([swap, args, X]) --> region,
  760	swap_args_of(X, 1, 2),
  761	overwrite.
Numbering paragraphs.
  765handle([numbering, paragraphs])  --> region,
  766	paragraph,
  767	remove([]),
  768	pred(([X, Y]:- length(X, N),
  769	      numlist(1, N, Ns),
  770	      maplist(pred([I, P,[I0, ". ", P]]:-
  771			  number_string(I, I0)),
  772		      Ns, X, Y))),
  773	insert("\n"),
  774	overwrite.
Show all handle commands. ! handle([help]) --> {setof(H, P^Q^R^clause(handle(H,P,Q), R), S), sort(S, S1), maplist(pred(([X, Y]:- numbervars(X,0,_), write_to_chars(X, Z, []), string_codes(Z, Y))), S1, S2), insert_tab_nl(4, 4, S2, R) }, peek(R).
Set Lisp variables handle-list to the list of all handles.
  793handle([handle, list]) --> region,
  794    {findall(H, clause(handle(H,_,_), _), S),
  795	 sort(S, S1),
  796	 maplist(pred(([H, H0] :-
  797			   foldl(pred([H, H0],
  798							  ( [X, ['VAR'|L], L]:- var(X) )
  799							& [X, [X|L], L]
  800				     ),
  801				     H, H0, []))),
  802		 S1, S2),
  803	remove([], S2, S3),
  804	maplist(pred(([X, Y]:- atomics_to_string(X, " ", Y0),
  805				  atomics_to_string(["[", Y0, "] "], Y))),
  806				S3, Commands)
  807%	,	List =..[list|Commands]
  808%	,	elisp:lisp(setq('handle-list', List))
  809%	,	elisp:lisp(message("variable 'handle-list' has been set."))
  810	},
  811	peek(Commands),
  812	overwrite.
Reload the current buffer file.
  816handle([reload, buffer, file]) -->
  817	{ call_lisp('buffer-file-name'(), term(File)),
  818  	  string_codes(S, File),
  819	  unload_file(S),
  820	  load_files(S, [silent(true)]) }.
Generate edit commnad ?- edit(X) from the symbol at the current point.
  824handle([edit])--> { prolog_symbol_at_point(X) },
  825			  peek(["\n\n% ?- edit(", X, ").\n"]).
Take a time-stamped memo, and display it in the emacs window.
  830handle([take, memo]) --> region,
  831 	{   lisp('time-stamp', Dir),
  832		getinfo_string("date +%Y-%m-%d", Today),
  833		atomics_to_string([Dir, Today], File0),
  834		expand_file_name(File0, [File|_]),   % File is of type atom.
  835		pshell(touch(File))
  836	},
  837	pred([Today, File],
  838		 ( [ Note, []]
  839		   :- file:push_to_file(
  840					 basic:smash(["[", Today, "]\n",
  841								  Note,
  842								  "\n"]),
  843							File))),
  844	{	atom_string(File, File0),
  845		lisp('find-file'(File0))
  846	}.
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.
  858handle([choose, working, directory]) -->
  859	{	choose_folder(X),
  860		set_string(working_directory, X)
  861	},
  862	peek(X).
Choose a folder.
  866handle([choose, folder]) --> {choose_folder(X)}, peek(X).
Choose a file.
  870handle([choose, files]) --> {choose_files(X), insert("\n", X, X0) },
  871							peek(X0).
  872
  873%
  874handle([rename, files]) --> region,
  875	split,
  876	remove([]),
  877	maplist(flip(string_codes)),
  878	rename_files_base,
  879	overwrite.
  880
  881handle([display, renamed]) --> region,
  882	split,
  883	remove([]),
  884	maplist(flip(string_codes)),
  885	rename_files_base_display,
  886	overwrite.
  887
  888
  889% short for handle([open, pdf]).
  890handle([o]) --> handle([open, pdf]).
  891handle([m]) --> handle([jisui, archives]).
  892%
  893handle([jisui, archives])--> trim_line_string,
  894	current(A),
  895	{ jisui_archives(B),
  896	  expand_file_name(B, [B0|_]),
  897	  run_shell(mkdir, ['-p', B0]),
  898%	  pshell(mv(A, B0))
  899%  	  process_create(path(mv), [A, B0], [])
  900	  run_shell(mv, [A, B0])
  901	},
  902	clear,
  903	overwrite.
  904
  905%
  906rename_files_base([], []).
  907rename_files_base([X,Y|Z], [U, "\n"|V]):-
  908	subst_file_base(X, Y, U),
  909	rename_file(X, U),
  910	rename_files_base(Z, V).
  911
  912% ?- subst_file_base("/a/ b/b", c, Z).
  913subst_file_base(X, Y, Z):-
  914	atomic_list_concat(X0, /, X),
  915	append(U, [_], X0),
  916	append(U, [Y], V),
  917	atomic_list_concat(V, /, Z).
Choose a file and opent it.
  921handle([choose, file, open]) -->
  922	{	choose_file(X),
  923		term_string(X, Y),
  924		pshell(open(Y))
  925	},
  926	peek(X).
  927
  928% ?- atomic_list_concat([a, ' b'], C).
Choose a folder, and open it.
  932handle([choose, folder, open]) -->
  933	{	choose_folder(X),
  934		term_string(X, Y),
  935		pshell(open(Y))
  936	},
  937	peek(X).
  938
  939		/********************
  940		*     sort lines    *
  941		********************/
Sort lines.
  945handle([sort, lines]) --> region,
  946						  split,
  947						  sort,
  948						  insert("\n"),
  949						  overwrite.
Trim leading white codes and sort the trimed lines.
  954handle([trim, sort, lines]) --> region,
  955						  split,
  956						  remove([]),
  957						  maplist(phrase(wl("[\s\t]*"))),
  958						  sort,
  959						  maplist(pred([L, [L,"\n"]])),
  960						  overwrite.
  961end_of_codes([], []).
  962%
  963trim_line --> line, phrase(wl("[\s\t]*")).
  964%
  965trim_line_string --> line, trim_line, flip(string_codes).
open a file with a full path in the current line as pdf.
  969handle([open, pdf]) --> trim_line,
  970				current(X),
  971				{	string_codes(Y, X),
  972					run_shell(open, ['-a', "Preview", Y])
  973				},
  974				clear.
  975
  976
  977		/************************
  978		*     shell in buffer   *
  979		************************/
Run shell commands in the region.
  984handle([shell]) --> set_mark_region,
  985	region,
  986	split,
  987	remove([]),
  988	insert(" ; "),
  989        {
  990	    tmp_file_stream(utf8, File, Stream),
  991	    close(Stream)
  992	},
  993	peek(X, ["( ", X, " ) > ", File]),
  994	smash,
  995	pred(File, ([Shell_in_string, Codes]:-
  996			shell(Shell_in_string),
  997			read_file_to_codes(File, Codes, [tail([]), encoding(utf8)])
  998		   )
  999	    ),
 1000        {
 1001	    delete_file(File)
 1002	}.
Run shell commnad in the region, and convert the Japanese ligature to the normal form.
 1007handle([shell, dakuten]) --> handle([shell]), dakuten_convert.
Run message command of Lisp.
 1012handle([message]) --> region, pred([M, []]:- message(M)).
 1013
 1014		/*********************
 1015		*     prolog/lisp    *
 1016		*********************/
 1017
 1018solve_once -->
 1019	remove_leading_comment_chars,
 1020	current(X),
 1021	{	string_codes(Str, X),
 1022		term_string(G, Str, [variable_names(Es)]),
 1023		(	once(G)		->
 1024			numbervars(Es),
 1025			maplist(pred([Eq, Sol]:- term_string(Eq, Sol,
 1026									 [	numbervars(true),
 1027										quoted(false)])),
 1028					Es, Sols0),
 1029			(	Sols0 = [] -> R =  "\n%@ true.\n"
 1030			;	insert(",\n%@ ", Sols0, Sols),
 1031				R = ["\n%@ ", Sols,  "\n%@ true."]
 1032			)
 1033		;	R = "\n%@ false.\n"
 1034		)},
 1035	peek(R).
run the current region by once as prolog query.
 1041%@ ?- append([a,c],[c,d], []).
 1042%@ false.
 1043
 1044
 1045%@ ?- append([a,b],[c,d], [a,b,c,d]).
 1046%@ ?- append([a,c],[c,d], X), append(X, X, Z),
 1047%@ append(Z, Z, U).
 1048
 1049handle([once])--> region, solve_once.
Run a Prolog goal in the paragraph between \n\n and \n\n Emacs short cut: s-M-<return>
 1055% ?- 1 = 1,
 1056%	2 = 2,
 1057%   3 = 3.
 1058
 1059% ?- X = 1,
 1060%	Y = 2,
 1061%   Z = 3.
 1062
 1063handle([prolog, paragraph]) --> set_mark_region, region, solve_once.
Run a prolog goal on the current line. emacs short cut: C-<return>
 1069%   ?- X = 1.
 1070handle([prolog, line])  --> line, solve_once.
 1071
 1072
 1073
 1074%	Put the comment symbol to each line of the region.
 1075handle([comment, region])  --> region,
 1076	split,
 1077	maplist(comment),
 1078	insert("\n"),
 1079	overwrite.
Remove the comment symbol of each line of the region.
 1083handle([uncomment, region])  --> region,
 1084	split,
 1085	maplist(uncomment),
 1086	insert("\n"),
 1087	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.
 1106handle([enum]) --> region, snippets:environment(enumerate), overwrite.
Make a LaTeX eitemize environment from the items in the region.
 1111handle([eit])  --> region, snippets:environment(itemize), overwrite.
Put "<code>" and "</code>" around the region.
 1115handle([html,tag,code])  --> region,
 1116			 peek(X, ["<code> ", X, " </code>"]),
 1117			 overwrite.
Run the region as a goal igonoring errors.
 1121handle([ignore, goal|R]) --> region_or_line(R),
 1122	herbrand(_),
 1123	pred([X, []]:- ignore(X)).
Run the region as a goal catching errors.
 1127handle([solve,  goal|R]) -->  region_or_line(R),
 1128	herbrand(_),
 1129	pred(B, [X, ["\n", R, "\n"]]:- catch_once(X, B, R)).
Insert tab before the each line of the region.
 1134handle([shift, region]) -->  region,
 1135	split,
 1136	maplist(pred([X, ['\t'|X]])),
 1137	insert('\n'),
 1138	overwrite.
Insert A before the each line of the region.
 1142handle([insert, before, A]) -->  region,
 1143	split,
 1144	maplist(pred(A, [X, [A|X]])),
 1145	insert('\n'),
 1146	overwrite.
 1147
 1148		/****************
 1149		*     indent    *
 1150		****************/
insert tab. ! handle([indent, region]) is det. ! handle([indent, region, N]) is det. Indent the region.
 1158handle([tab, region])	-->  indent_region(0'\t, 1). %'
 1159handle([tab, region, N])-->  { atom_number(N, N0) },
 1160	indent_region(0'\t, N0).		%'
 1161handle([indent, region])--> indent_region(0'\s, 4).		%'
 1162handle([indent, region, N]) -->  { atom_number(N, N0) },
 1163	indent_region(0'\s, N0).					%'
Put framed header without centering.
 1168handle([header]) -->  region,
 1169	split,
 1170	maplist(remove_trailing_white),
 1171	maplist(detab),
 1172	remove_enveloping_nulls,
 1173	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1174	{ Width is Max + 7,
 1175	  length(Hr, Width),
 1176	  maplist(=("*"), Hr)
 1177	},
 1178	maplist(fill_trailing_spaces(Width)),
 1179	maplist(pred([X, ["\t*", X, "*\n"]])),
 1180	peek(Body,	["\t/", Hr, "*\n",
 1181				Body,
 1182				"\t*", Hr, "/\n"]),
 1183	overwrite.
 1184
 1185%
 1186fill_trailing_spaces(Width, X, [X, Y]):-
 1187	length(X, L),
 1188	J is Width - L,
 1189	length(Y, J),
 1190	maplist(=("\s"), Y).
 1191
 1192% ?- ejockey:remove_enveloping_nulls([[], a, [], b,[]], R).
 1193%@ R = [a, [], b] .
 1194remove_enveloping_nulls -->[[]], remove_enveloping_nulls.
 1195remove_enveloping_nulls -->[], remove_trailing_nulls.
 1196%
 1197remove_trailing_nulls(X, []):- nulls(X), !.
 1198remove_trailing_nulls([X|R], [X|S]):-
 1199	remove_trailing_nulls(R, S).
 1200
 1201%
 1202nulls([[]|R]):- nulls(R).
 1203nulls([]).
 1204
 1205% ?- ejockey:remove_trailing_white(X, `abc   `, Y).
 1206% ?- trace, ejockey:remove_trailing_white(`abc   `, Y).
 1207% ?- trace, ejockey:remove_trailing_white(`a`, Y).
 1208
 1209handle([trim, trailing, white]) --> region, remove_trailing_white(X), peek(X).
 1210
 1211remove_trailing_white(X) --> w(".*", X), wl("[\s\t]*$").
 1212
 1213remove_trailing_white --> w(".*", X), wl("[\s\t]*$"), peek(X).
Removing tab from each line of the region.
 1218handle([detab]) --> region, detab, overwrite.
 1219%
 1220detab_spaces(`\s\s\s\s`).
 1221%
 1222detab(X, Y):- detab(X, Y, []).
 1223
 1224% ?- ejockey:detab(`\ta\t\b`, X, []).
 1225detab([0'\t|R], X, Y):- !, detab_spaces(S),   %'
 1226	append(S, X0, X),
 1227	detab(R, X0, Y).
 1228detab([A|R], [A|X], Y):-detab(R, X, Y).
 1229detab([], X, X).
Make a framed header wiht centering.
 1234handle([shift, frame|Optional]) --> region_or_line(Optional),
 1235	split,
 1236	maplist(trim_white),
 1237	remove_enveloping_nulls,
 1238	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1239	{ Width is Max + 11 },
 1240	maplist(pred([Width, Max], ( [A, B]:-
 1241				length(B, Width),
 1242				N is (Width - Max) div 2,
 1243				length(L, N),
 1244			       	append([ ['*'], L, A, R, ['*']], B),
 1245				maplist(=('\s'), L),
 1246			        maplist(=('\s'), R)))),
 1247	{	length(Top, Width),
 1248		length(Bottom, Width) ,
 1249		Top = ['/'|L0],
 1250		append(L1, ['/'], Bottom),
 1251		maplist(=('*'), L0),
 1252		maplist(=('*'), L1)
 1253	},
 1254	maplist(pred([X, ['\t\t', X, '\n']])),
 1255	peek(Body, ['\t\t', Top, '\n',
 1256				Body,
 1257				'\t\t', Bottom, '\n']),
 1258	overwrite.
 1259
 1260/*--------------------------------------------
 1261	long comment /* ... */
 1262--------------------------------------------*/
 1263
 1264handle([long, comment]) --> region,
 1265	peek(Block, [
 1266			"/*--------------------------------------------\n",
 1267			Block,
 1268			"--------------------------------------------*/\n"
 1269			]),
 1270	overwrite.
Convert the region to a comma list of lines in the region added with single quotation marks.
 1277handle([single, quote]) --> region,
 1278	split,
 1279	remove([]),
 1280	maplist(html:single_quote),
 1281	insert(',\n'),
 1282	overwrite.
Convert the region to a comma list of lines in the region added with double quotation marks.
 1287handle([double, quote]) --> region,
 1288	split,
 1289	remove([]),
 1290	maplist(html:double_quote),
 1291	insert(',\n'),
 1292	overwrite.
Copy region to copyboad; lualatex it with standalone class.
 1296handle([region, standalone])  -->
 1297	{ call_lisp(pbcopy()),
 1298	  shell(standalone, 0)
 1299	}.
lualatex pasteboard text with standalone class.
 1303handle([pasteboard, standalone])  --> { shell(standalone, 0)}.
Show a LaTeX description environment.
 1309handle([description]) -->  peek([
 1310	"\\begin{description}[style=multiline, labelwidth=1.5cm]",
 1311	"\\item[\\namedlabel{itm:rule1}{Rule 1}] Everything is easy with \\LaTeX",
 1312	"\\item[\\namedlabel{itm:rule2}{Rule 2}] Sometimes it is not that easy\\\\",
 1313	"$\\to$ \\ref{itm:rule1} applies",
 1314	"\\end{description}\n"	]),
 1315	insert("\n"),
 1316	overwrite.
Generate a LaTeX listlisting environment.
 1321handle([list, listing]) --> region,
 1322	pred([	X, [	"\\begin{lstlisting}[caption={},label=src:]\n",
 1323			X,
 1324			"\\end{lstlisting}\n"	]]),
 1325	overwrite.
Generate a LaTeX align* environment.
 1328handle([begin, align]) --> region,
 1329	pred([	X, [	"\\begin{align*}\n",
 1330			X,
 1331			"\\end{align*}\n"	]]),
 1332	overwrite.
Generate TeX \vbox template.
 1335handle([vbox]) --> peek([
 1336	"$$\\vbox{\\offinterlineskip",
 1337        "\\halign{\\strut",
 1338        "\\vrule\\vrule\\quad\\textbf{#}\\hfill\\quad & \\vrule\\quad\\hfill #cm \\quad ",
 1339         "& \\vrule\\quad\\hfill #kg \\quad\\vrule\\vrule\\cr",
 1340        "\\noalign{\\hrule\\hrule}",
 1341        "鈴木 一太郎 & 168 & 74 \\cr",
 1342        "\\noalign{\\hrule} ",
 1343        "山田 太郎   & 170 & 72 \\cr",
 1344        "\\noalign{\\hrule} ",
 1345        "渡辺 次郎   & 192 & 103 \\cr",
 1346        "\\noalign{\\hrule\\hrule} ",
 1347        "}}$$"		]),
 1348	insert("\n").
Generate TeX halign
 1352handle([halign]) --> peek([
 1353	"\\halign{",
 1354%	"\\hfill$#$\\hfill\\qquad&\\hfill$#$\\hfill&\\quad\\text{#}\\cr\n",
 1355	"\\hfill$#=\\>$ & $#$ \\hfill & \\qquad \\mbox{#} \\cr\n",
 1356	" &  &   \\cr\n",
 1357      	" &  &   \\cr\n",
 1358	" &  &   \\cr\n",
 1359	"}"	]).
Generate a LaTeX cases environment.
 1363handle([case, equation]) --> region,
 1364	pred([	Left, [		"$", Left, "= \n",
 1365				"\\begin{cases}\n",
 1366				"     &  \\mbox{} \\\\\n",
 1367				"     &  \\mbox{} \\\\\n",
 1368				"     &  \\mbox{} \n",
 1369				"\\end{cases}$\n"	]]),
 1370	overwrite.
Generate a LaTex eqnarray* environment.
 1375handle([eqn, array]) --> region,
 1376	pred([	_, [	"\\begin{eqnarray*}\n",
 1377			"     &=&          \\\\\n",
 1378			"     &=&          \\\\\n",
 1379			"     &=&          \\\\\n",
 1380			"\\end{eqnarray*}\n"	]]),
 1381	overwrite.
Parse and Generate a LaTeX eqnarray* environment.
 1386handle([parse, eqn, array]) --> region, split, remove([]),
 1387	maplist(split(`=`)),
 1388	maplist(pred([[X|Y],	[X, " &=& ", Y]])),
 1389	insert("\\\\\n"),
 1390	pred([Body, [	"\\begin{eqnarray*}\n",
 1391			Body,
 1392			"\n\\end{eqnarray*}\n"	]]),
 1393	overwrite.
! handle([q, F,X, N]) is det.
 1401handle([q, F,X, N]) -->
 1402	peek([F, "(", X, "_1, ", X, "_2, ", "\\ldots ,", X, "_", N, ")"]).
 1406handle([q, F, X, N0, N]) -->
 1407	peek([F, "(", X, "_", N0, ", ", X, "_1, ", "\\ldots ,", X, "_", N, ")"]).
 1411handle([q]) --> region, split(` `), remove([]),
 1412	pred(	([[F, X, N], E]:- handle([q, F, X, N], _, E))
 1413		&
 1414		([[F, X, N0|N], E]:- handle([q, F, X, N0, N], _, E))),
 1415	overwrite.
 1419handle([ref])	--> region, pred([X, ["\\ref{", X, "}"]]), overwrite.
 1423handle([cite])	--> region, pred([X, ["\\cite{", X, "}"]]), overwrite.
 1427handle([cs, N]) --> region,
 1428	pred([N],[X, ["\\", N, "{", X, "}"]]),
 1429	overwrite.
 1430%
 1431%! 	handle([parse, bind, context]) is det.
 1432%
 1433%
 1434handle([parse, bind, context])	--> region,	parse_bind_context, overwrite.
 1438handle([parse, bind, context, append])	--> region, parse_bind_context.
 1442handle([eval, markup, text])		--> region, eval_markup_text, overwrite.
 1446handle([eval, markup, text, append])	--> region, eval_markup_text.
 1447%
 1448%! 	handle([tag, l]) is det.
 1449%
 1450%
 1451handle([tag, l])	--> {nb_getval(phrase_tag, G), herbrand_opp(G, G0)},  % to list the saved tag
 1452	peek(G0).
 1456handle([tag, s|P])	--> region_or_line(P),		% to save the tag
 1457	peek(Q),
 1458	{parse_phrase_save(Q)},
 1459	peek("\n the tag saved.\n").
 1463handle([tag, a])  --> region,
 1464	{ nb_getval(phrase_tag, G) },
 1465	act(G),
 1466	overwrite.
 1471region_debug(X, Y):- var(X), !, region(X, Y).
 1472region_debug(X, X).
 1473
 1474
 1475handle([t, a])  --> handle([tag,a]).
Generate bibliography commands.
 1478handle([bib]) --> peek(["\\bibliographystyle{plain}\n",
 1479	"\\bibliography{jmukai,mukai}\n"]).
 1480
 1481% Convert  delicious 3 data in book/1 to bibtex form.
 1482handle([book, bibtex]) --> region,
 1483		paragraph,
 1484		remove([]),
 1485		maplist(herbrand),
 1486		maplist(book_bibitem),
 1487		insert("\n"),
 1488	    overwrite.
 1489
 1490% Convert  csv data to a dict  with keywords.
 1491handle([csv, bibtex])	--> region,
 1492						csv_to_dict,
 1493						peek(key_dict(_, L), L),
 1494						maplist(dict_bibtex).
 1495
 1496% Convert  csv data to a dict  with keywords.
 1497% ?- ejockey:csv_to_dict(`a\tb\tc\n1\t2\t3\n4\t5\t6`, R).
 1498%@ R = key_dict([a, b, c], [[a="1", b="2", c="3"], [a="4", b="5", c="6"]]) .
 1499
 1500csv_to_dict --> split,
 1501		remove([]),
 1502		maplist(split("\t")),
 1503		peek([H|R], R),
 1504		{	maplist(atom_codes, Keys0, H),
 1505			map_key_tbl(M),
 1506			map_key(Keys0, M, Keys)
 1507		},
 1508		maplist(pred(Keys,
 1509					 ([A, B]:-
 1510						 maplist(pred([K, A0, K=A1]:-
 1511									 string_codes(A1, A0)),
 1512								 Keys, A, B)))),
 1513		peek(D, key_dict(Keys, D)).
 1514
 1515%
 1516dict_bibtex(L, BB):-
 1517	maplist(pred([K=V, [K, " = ", "{", V, "}"]]), L, Items),
 1518	insert(",\n", Items, Items0),
 1519	smash(["@book{", "to be filled", ",\n", Items0, "\n}\n"], BB).
 1520%
 1521map_key_tbl([creator-author, 'ISBN'-isbn]).
 1522
 1523%
 1524map_key([],_,[]).
 1525map_key([K|R],M,[K0|R0]):- memberchk(K-K0, M), !,
 1526						   map_key(R, M, R0).
 1527map_key([K|R],M,[K|R0]):-  map_key(R, M, R0).
Generate a LaTeX thm environment.
 1532handle([thm|X])--> region_or_line(X),
 1533	peek(Y, ["\\begin{thm}\\label{thm:}\n", Y, "\\end{thm}\n"]),
 1534	overwrite.
Generate a LaTeX prop environment.
 1540handle([prop|X])--> region_or_line(X),
 1541	peek(Y, ["\\begin{prop}\\label{prop:}\n", Y, "\\end{prop}\n"]),
 1542	overwrite.
Generate a LaTeX lemma environment.
 1547handle([lem|X])--> !, region_or_line(X),
 1548	peek(Y, ["\\begin{lemma}\\label{lem:}\n", Y, "\\end{lemma}\n"]),
 1549	overwrite.
Generate a LaTeX cor environment.
 1553handle([cor|X])-->region_or_line(X),
 1554	peek(Y, ["\\begin{cor}\\label{cor:}\n", Y,"\\end{cor}\n"]),
 1555	overwrite.
Generate a LaTeX ex environment.
 1559handle([ex|X])--> region_or_line(X),
 1560	peek(Y, ["\\begin{ex}\n", Y, "\\end{ex}\n"]),
 1561	overwrite.
Generate a LaTeX df environment.
 1565handle([df|X])--> region_or_line(X),
 1566	peek(Y, ["\\begin{df}\\label{df:}\n", Y, "\\end{df}\n"]),
 1567	overwrite.
Generate a LaTeX cases environment template. For example try for f(x)
 1572handle([cases|X])--> region_or_line(X),
 1573	peek(Y, ["\\[", Y, " =\n",
 1574			 "\t\\begin{cases}\n",
 1575				 "\t\t  & (\t\t\t  ) \\\\\n",
 1576				 "\t\t  & (\t\t\t  ) \\\\\n",
 1577				 "\t\t  & (\t\t\t  ) \n",
 1578			  "\t\\end{cases}\n",
 1579			"\\]\n"
 1580			]),
 1581	overwrite.
 1582%
 1583handle([emph|X])--> region_or_line(X),
 1584	peek(Y, ["\\emph{", Y, "}"]),
 1585	overwrite.
 1586
 1587handle([mbox|X])--> region_or_line(X),
 1588	peek(Y, ["\\mbox{", Y, "}"]),
 1589	overwrite.
Generate a LaTeX rem environment.
 1593handle([rem|X])--> region_or_line(X),
 1594	peek(Y, ["\\begin{remark}\\label{rem:}\n",Y,"\\end{remark}\n"]),
 1595	overwrite.
Generate a LaTeX proof environment.
 1599handle([proof|X])-->region_or_line(X),
 1600	peek(Y, ["\\begin{Proof}\n",Y,"\\end{Proof}\n"]),
 1601	overwrite.
Insert red color macro.
 1605handle([red|X])	--> region_or_line(X),
 1606					peek(Y, ["\\Red{", Y, "}"]), overwrite.
Insert blue color macro.
 1609handle([blue|X])	--> region_or_line(X),
 1610						peek(Y, ["\\Blue{", Y, "}"]), overwrite.
Insert green color macro.
 1614handle([green|X]) --> region_or_line(X),
 1615					  peek(Y, ["\\Green{", Y, "}"]),
 1616					  overwrite.
 1617
 1618% I don't remember what is the purpose of the following handle.
 1619%!  handle([mkh])	--> region,
 1620% 	split,
 1621% 	maplist(pred( ( [X, Y]:-
 1622% 						html:single_quote(X, X0),
 1623% 						atom_codes(Y, X0)))),
 1624% 	pred([L, ( handle([names]
 1625% 					 ) --> peek(L), insert_nl, ".")]).
Put font macro \mathscr
 1629handle([ms|X])	--> region_or_line(X),
 1630					peek(Y, ["\\mathscr{", Y, "}"]), overwrite.
Generate a LaTeX euation environment with a label command.
 1634handle([eq|X])	--> region_or_line(X),
 1635	peek(Y, ["\\begin{equation}\\label{eq:}\n",
 1636				Y, "\n",
 1637			"\\end{equation}\n"]),
 1638	overwrite.
get the module name from the source in the current buffer defined by ":- module(<name>, ...)."
 1643handle([get, module, name]) -->
 1644 {
 1645	wait(progn(
 1646		setq(point_saved, point()),
 1647		'goto-char'('point-min'()))),
 1648	line_get(Obj),
 1649	obj_get([line(Line)], Obj),
 1650	string_codes(Line, Codes),
 1651	module_name(Codes, Name),
 1652	wait('goto-char'(point_saved))
 1653    },
 1654    peek(Name).
Set query context.
 1657handle([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.
 1664handle([set, query, context]) -->
 1665		handle([get, module, name]),
 1666		peek(C, ["% ?- module(", C, ")."]),
 1667		current(X),
 1668		{	smash(X) },
 1669		peek([]),
 1670		{	wait('keyboard-quit'()) }.
 1671
 1672		/*******************
 1673		*     directory    *
 1674		*******************/
Run the shell command pwd.
 1678handle([pwd])	-->
 1679	{
 1680		get_string(working_directory, Path)
 1681	},
 1682	peek(Path).
Set target directory.
 1686handle([set, target, directory])	-->
 1687	{	line_get(Obj),
 1688		obj_get([line(Line)], Obj),
 1689		trim_white(Line, DirPath),
 1690		string_codes(S, DirPath),
 1691		expand_file_name(S, [S0|_]),
 1692		set_string(target_directory, S0)
 1693	}.
Choose working directory, and set the working_directory to it.
 1699handle([cwd]) -->
 1700	{	choose_folder(X),
 1701		set_string(working_directory, X),
 1702		working_directory(_, X)
 1703	},
 1704	peek(X).
Change director to the HOME.
 1709handle([cd]) -->
 1710	{	expand_file_name("~/", [D]),
 1711		set_string(working_directory, D),
 1712		working_directory(_, D)
 1713	},
 1714	peek(D).
Change directory like "../"
 1719handle([cd, up]) -->
 1720	{
 1721		get_string(working_directory, Path),
 1722		change_unix_path(up, Path, New_Path),
 1723		set_string(working_directory, New_Path),
 1724		working_directory(_, New_Path)
 1725	},
 1726	peek(New_Path).
Call Finder open.
 1731handle([open])	-->
 1732	{
 1733		line_get(Obj),
 1734		obj_get([line(Line)], Obj),
 1735		trim_white(Line, Line0),
 1736		double_quote(Line0, X),
 1737		(	Line0 = [0'/|_]						% '
 1738		-> 	sh_core(open(X))
 1739		;	string_codes(XStr, X),
 1740			handle_open_relative(XStr)
 1741		)
 1742	}.
 1743%! 	handle([open, *]) is det.
 1744%	Call Finder open  all files in the region.
 1745handle([open, *]) -->
 1746	{	get_string(working_directory, S),
 1747		S\== ""
 1748	},
 1749	region,
 1750	split,
 1751	remove([]),
 1752	reverse,
 1753	current(L),
 1754	{
 1755	maplist(pred(S, ([X] :-
 1756			double_quote([S, X], SX),
 1757			sh_core(open(SX)))),
 1758		L)
 1759	},
 1760	clear
 1761	;
 1762	peek("**** directory not found. ****\n").
 1763
 1764
 1765
 1766		/*****************************
 1767		*     Accessing Directory    *
 1768		*****************************/
Call Finder open for directory.
 1771handle([finder, open, directory])	-->
 1772	{
 1773		line_get(Obj),
 1774		obj_get([line(Line)], Obj),
 1775		first_token_codes(Line, Directory),
 1776		sh(open(-a('Finder'), Directory))
 1777	}.
 1778
 1779%
 1780append_slash_code([], [0'/]):-!.	%'
 1781append_slash_code(Line, Line0):- last(Line, C),
 1782	(	C == 0'/ -> Line0 = Line		%'
 1783	;   append(Line, [0'/], Line0)		%'
 1784	).
Set working directory to working_directory.
 1789handle([swd])	-->
 1790	{	line_get(Obj),
 1791		obj_get([line(Line)], Obj),
 1792		trim_white(Line, Line0),
 1793		append_slash_code(Line0, Line1),
 1794		first_token_codes(Line1, Directory),
 1795		string_codes(Dir_string, Directory),
 1796		expand_file_name(Dir_string, [Full_path|_]),
 1797		nb_setval(working_directory, Full_path),
 1798		atom_string(Full_path, S),
 1799		set_string(working_directory,S)
 1800	},
 1801	peek(Full_path).
Set working directory to the default directory.
 1807handle([swd, (.)])-->
 1808	{	call_lisp_value('default-directory', D),
 1809		string_codes(X, D),
 1810		expand_file_name(X, [Full_path|_]),
 1811		nb_setval(working_directory, Full_path),
 1812		atom_string(Full_path, S),
 1813		set_string(working_directory, S)
 1814	},
 1815	peek([]).
Open the default directory.
 1820handle([finder, default, directory])	-->
 1821	{	call_lisp_value('default-directory', D),
 1822		string_codes(X, D),
 1823		sh(open(X))
 1824	}.
 1825
 1826%
 1827handle([directory, path])	-->
 1828	{	call_lisp_value('default-directory', D)
 1829	},
 1830	peek(D).
 1831%
 1832handle([file, path]) -->
 1833	{ lisp(list('default-directory', 'buffer-name'()), List)
 1834	},
 1835	peek(List).
List all files in the working directory.
 1840handle([list, files])		--> % ls
 1841	{	get_string(working_directory, S),
 1842		S \== "",
 1843		directory_files(S, Files)
 1844	},
 1845	peek(Files),
 1846	insert("\n")
 1847	;
 1848	peek("**** directory not found. ****\n").
Convert the text possibly with ligatures to the normal normal sequences of chars.
 1854handle([dakuten])--> region,
 1855					flip(string_codes),
 1856					dakuten_convert,
 1857					overwrite.
Inverse of handle([dakuten]).
 1861handle([dakuten, flip]) --> region,
 1862					flip(string_codes),
 1863					flip(dakuten_convert),
 1864					overwrite.
List files with the ligatures resolved as in handle([dakuten]).
 1868handle([list, files, dakuten])	--> % ls
 1869	{	get_string(working_directory, S),
 1870		S \== "",
 1871		directory_files(S, Files)
 1872	},
 1873	peek(Files),
 1874	maplist(string_codes),
 1875	maplist(dakuten_convert),
 1876	insert("\n")
 1877	;
 1878	peek("**** directory not found. ****\n").
List files with a regex filter.
 1883handle([list, regex])	--> region_term,
 1884	current(Regex),
 1885	{	let(Parser, pred(Regex, [X]:- phrase(w(Regex), X, []))),
 1886		get_string(working_directory, S),
 1887		S \== "",
 1888		directory_files(S, Files)
 1889	},
 1890	peek(Files),
 1891	maplist(dakuten_convert),
 1892	maplist(string_codes),
 1893	collect(Parser),
 1894	insert("\n")
 1895	;
 1896	peek("**** directory not found. ****\n").
List all of time-stamped pdf files.
 1900handle([list, timed, pdf])	--> % ls
 1901	{	get_string(working_directory, S),
 1902		S \== "",
 1903		directory_files(S, Files),
 1904		maplist(atom_codes, Files, Codes_list),
 1905		collect(pred([Codes]:- phrase(w("[0-9]+\\.pdf"), Codes,[])),
 1906			Codes_list,
 1907			Pdf_files)
 1908	},
 1909	peek(Pdf_files),
 1910	insert("\n")
 1911	;
 1912	peek("**** directory not found. ****\n").
Move files.
 1917handle([mv])	--> % move a file over directories
 1918	{	get_string(working_directory, S),
 1919		S\== "" ,
 1920		get_string(target_directory, T),
 1921		T\== ""
 1922	},
 1923	rename(S, T)
 1924	;
 1925	peek("**** directory not found. ****\n").
Rename a file.
 1929handle([mv, (.)]) --> % rename a file at a directory
 1930	{	get_string(working_directory, S),
 1931		S \== ""
 1932	},
 1933	rename(S, S)
 1934	;
 1935	peek("**** directory not found. ****\n").
Move files at the source directory to the target directory with renaming.
 1941handle([mv, *])	-->
 1942	{	get_string(working_directory, S),
 1943		S\== "",
 1944		get_string(target_directory, T),
 1945		T\== ""
 1946	},
 1947	region,
 1948	paragraph,
 1949	remove([]),
 1950	maplist(trim_nl_mv(S,T)),
 1951	insert("\n"),
 1952	overwrite
 1953	;
 1954	peek("**** directory not found. ****\n").
 1955
 1956% c handle([rename]) is det.
 1957%   Rename a file.
 1958
 1959handle([rename]) --> handle([mv, (.)]).
Rename multi files.
 1963handle([rename, *]) -->
 1964	{	get_string(working_directory, S),
 1965		S\==""
 1966	},
 1967	region,
 1968	paragraph,
 1969	remove([]),
 1970	maplist(trim_nl_mv(S,S)),
 1971	insert("\n"),
 1972	overwrite
 1973	;
 1974	peek("**** directory not found. ****\n").
Get working directory.
 1979handle([wd])	--> {working_directory(X, X)}, peek(X).
Change working directory.
 1983handle([wd, change])	--> { line_get(Obj),
 1984		      obj_get([line(D0)], Obj),
 1985		      atom_codes(D, D0),
 1986		      working_directory(_, D)
 1987		    }.
 1988
 1989% !! Experimental !!
 1990%	handle([doc, latex]) is det.
 1991%   under debugging.
 1992%
 1993%!  handle([doc, latex]) --> region,   % @see => C-c-ee
 1994% 	paragraph,
 1995% 	remove([]),
 1996% 	maplist(split),
 1997% 	maplist(remove([])),
 1998% 	pred(([[X, [Y|_]],[X0, Y0]]:-
 1999% 	     maplist(flip(atom_codes), X, X1),
 2000% 	     maplist(expand_file_name, X1, X2),
 2001% 	     append(X2, X0),
 2002% 	     atom_codes(Y1, Y),
 2003% 	     expand_file_name(Y1, [Y0|_]))),
 2004% 	pred(([[X, Y], Y]:-
 2005% 	    doc_latex(X, Y, [public_only(false)]))).
 2006
 2007% % 	handle([global,set,key]) is det.
 2008% %   Run global-set-key lisp command.
 2009%!  handle([global,set,key]) --> region, paragraph, maplist(split),
 2010% 	maplist(remove_comment_line),
 2011% 	remove([]),
 2012% 	maplist([[X,Y], done]
 2013% 		:- (herbrand(Y, H),
 2014% 		    elisp:global_set_key(X, H))
 2015% 	       ),
 2016% 	herbrand_opp.
Run global-unset-key Lisp command.
 2020handle([global, unset, key])	-->
 2021	region_or_line(K),
 2022	{global_unset_key(K)},
 2023	peek(`unset.`).
View the source in the current buffer as an html file generated by the pldoc library.
 2029handle([pldoc]) -->
 2030	{ Doc_html = 'TMPPLDOC.html',
 2031	  atomics_to_string(['~/public_html/', Doc_html], Local_html),
 2032	  expand_file_name(Local_html,[HTML|_]),
 2033	  lisp(list('default-directory', 'buffer-name'()), List),
 2034	  atomics_to_string(List, File_source_name),
 2035	  open(HTML, write, Out_stream),
 2036	  set_output(Out_stream),
 2037	  pldoc_html:doc_for_file(File_source_name,
 2038							  [edit(false),
 2039							  public_only(false)]),
 2040	  close(Out_stream),
 2041  	  getenv(user, User_name),
 2042	  sh(open(-a('Safari'),
 2043				"http://localhost/"
 2044				+ "~"
 2045				+ User_name
 2046			    + "/"
 2047				+ Doc_html))
 2048	}.
 2049
 2050		/***************************
 2051		*     make-reftex-label    *
 2052		***************************/
 2053
 2054tex_command(Comm, Arg)--> w(".*\\"),
 2055						  w(".*", Comm0),
 2056						  "{",
 2057						  w(".*", Arg0),
 2058						  "}",
 2059						 {	string_codes(Comm, Comm0),
 2060							string_codes(Arg, Arg0)
 2061						  }.
 2062%
 2063reftex_label_prefix("subsection", "sec").
 2064reftex_label_prefix(S, Pref):- string_length(S, L),
 2065							   (	L =< 3
 2066							   ->	Pref = S
 2067							   ;	sub_string(S, 0, 3, _, Pref)
 2068							   ).
 2069
 2070%
 2071make_reftex_label("begin", Beg, Rem,
 2072				  ["\n\\label{", Pref, ":", Rem0, "}"]):- !,
 2073		reftex_label_prefix(Beg, Pref),
 2074		trim_white(Rem0, Rem, []).
 2075make_reftex_label(Comm, Arg, _,
 2076				  ["\n\\label{", Pref, ":", Arg, "}"]):-
 2077		reftex_label_prefix(Comm, Pref).
 2078
 2079%
 2080handle([reftex, label])--> line,
 2081						tex_command(Comm, Arg),
 2082						make_reftex_label(Comm, Arg).
 2083
 2084		/*****************************************
 2085		*     helper predicates for handle/4.    *
 2086		*****************************************/
 2087
 2088%  \C-l  help  (for help)
 2089
 2090%  trim_white(+X:codes, -Y:codes) is det.
 2091%	Trim white codes from both ends of X as long as possible,
 2092%	and unify Y with the remainder of X.
 2093% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P),
 2094% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P), basic:smash(P).
 2095% ?- ejockey:trim_white(`\n \t/a\tb c/ \t`, P), basic:smash(P).
 2096% ?- ejockey:trim_white(`\n \t/a\tb c/ \t\n\n`, P), basic:smash(P).
 2097% ?- ejockey:trim_white(`\n ab\n cd \nef \n\n\n`, P), basic:smash(P).
 2098trim_white --> wl("[\s\t\n]*"),
 2099			   w(".*", A),
 2100			   wl("[\s\t\n]*"),
 2101			   end_of_codes,
 2102			   peek(A).
 2103
 2104%  Qcompile: /Users/cantor/devel/zdd/prolog/util/emacs-jockey.pl
 2105%  trim_white_prefix(+X:codes, -Y:codes) is det.
 2106%	Trim white codes of the prefix of X,
 2107%	and unify Y with the remainder of X.
 2108trim_white_prefix --> wl("[\s\t]*").
 2109
 2110%  catch_once(+G:goal, +A:term, -R:term) is det.
 2111%	Unify R with A if G is true, with E if exception E is thrown
 2112%	from a child process of G, and fail if G fails.
 2113
 2114catch_once(X, A, R):- catch((once(X), R=A), E, (R = E)), !.
 2115catch_once(_, _, fail).
 2116
 2117%  line(_, -L:codes) is det.
 2118%	Get the codes of the current line with  the cursor on.
 2119line(_, Line) :- line_get(I), obj_get([line(Line)], I, _).
 2120
 2121%  partial_match(As:list, B:atom) is det.
 2122%	True if some atom in As is a prefix atom of B.
 2123
 2124% ?- ejockey:partial_match([reg, a], region).
 2125partial_match(Atoms, Fullname):-
 2126	once((
 2127	member(Shortname, Atoms),
 2128	atom(Shortname),
 2129	sub_atom(Fullname, 0, N, _, Shortname),
 2130	N>0)).
 2131
 2132% %c select_phrase(+C:cond, +P:phrase, +Q:phrase) is det.
 2133% %	Conditional phrase depending on arguments abbreviation;
 2134% %	Use default unless otherwise being specified.
 2135% select_phrase(Cond, P, _) --> {call(Cond)}, !, phrase(P).
 2136% select_phrase( _, _, Q)	  -->  phrase(Q).
 2137
 2138%  region_or_line(As:list, ?X, ?Y) is det.
 2139%	Apply region/2 or line/2 to  X, Y depending on X.
 2140
 2141region_or_line([]) --> !, region.   % region is default.
 2142region_or_line([X|_]) --> {partial_match([X], line)}, !, line.
 2143region_or_line([X|_]) --> {partial_match([X], region)}, region.
 2144
 2145%  trim_nl_mv(+S, +T, +X, -Y) is det.
 2146%	Move a file over directories.
 2147trim_nl_mv(S, T) --> trim_nl(L, R),
 2148	handle_mv(S, T),
 2149	peek(X, [L, X, R]).
 2150
 2151%  rename(S:directory, T:directory, +X:codes, -Y:codes) is det.
 2152%	Move a file over directories with specified new name.
 2153rename(S, T)-->  set_mark_region,
 2154	region,
 2155	trim_nl_mv(S, T),
 2156	overwrite.
 2157
 2158%  indent_region(+C:code, +N:int, +X, -Y) is det.
 2159%	Indent the region by padding the code C  N times.
 2160
 2161indent_region(CharCode, N) -->  region,
 2162	split,
 2163	{ 	length(Indent, N),
 2164		maplist(=(CharCode), Indent)
 2165	},
 2166	maplist(pred(Indent,
 2167		     [[], []]
 2168		    &
 2169		     [X, [Indent|X]])),
 2170	insert('\n'),
 2171	overwrite.
 handle_open_relative(+P:codes) is det
Open the object located at P given as a path relative to the working directory.
 2177handle_open_relative(Line) :-
 2178		get_string(working_directory, Path),
 2179		(	Path \== ""
 2180		->	PathStr = Path
 2181		;	PathStr = ""
 2182		),
 2183		atomics_to_string([PathStr, /, Line], X),
 2184		sh_core(open(X)).
 2185
 2186%  remove_comment_line(X:codes, Y:codes) is det.
 2187%	Remove the comment lines from X, and Unify Y with the
 2188%	remaining.
 2189
 2190% ?- ejockey:remove_comment_line([`%abc`, `%xyz`, `%hello`], R).
 2191remove_comment_line([],[]).
 2192remove_comment_line([[0'%|_]|R], R0):- !, remove_comment_line(R, R0). %'
 2193remove_comment_line([X|R], [X|R0]):- remove_comment_line(R, R0).
 handle_mv(+S, +T, +X, -Y) is det
Move a file from directory S to T, whose source and target names are coded in X.
 2199handle_mv(S_dir, T_dir) -->
 2200	trim_nl(Left, Right),
 2201	pred([X, Y]:- foldr(  % : ===>  @
 2202		pred(   [0':,  U, [0'@  | U]]
 2203			&
 2204				[0'/,  U, [0'-  | U]]
 2205			&
 2206				[A,    U, [A|U]] ) ,
 2207		X, [], Y)),
 2208	mv_over_directory(S_dir, T_dir),
 2209	peek(A, [Left, A, Right]).
 2210
 2211
 2212%  A -->>  B   is a genral form of rules, tentatively called a `DCGX' (DCG extended) rule.
 2213%	Syntactically, A and B must be prolog terms such that A --> B forms a DCG rule.
 2214%	This rule is translated like a DCG rule, but into a predicate H that acts on contextual
 2215%	object of the form (X, E), which is called here a `state'.
 2216%	Procedually, H acts on states as a state transition action, so that we write
 2217%
 2218%	                H
 2219%		(X, E) ~~> (X', E')
 2220%
 2221%	for H((X, E), (X', E')).
 2222%
 2223%	Let H1, ..., Hn be actions for instances of the lefthand side of rules defined
 2224%	by '-->>' rules and (X0, E0) given an initial contextual objects. Then,  a sequence (H1,...,Hn)
 2225%	acts on a state (X0, E0) as an intial state, and then  produce a next state (X1, E1),
 2226%	and does successively so on  like this with a final state (Xn, En).
 2227%
 2228%	                 H1           H2      Hn
 2229%		(X0, E0) ~~> (X1, E1) ~~> ... ~~> (Xn, En).
 2230%
 2231
 2232%  mv_at_directory(+L:directory, +S:state, -S0:state) is det.
 2233%	Rename a file under L, whose  source and target names are
 2234%	coded in the state S.
 2235
 2236mv_at_directory(L) -->> dcl([dir(L)]),
 2237	paragraph,
 2238	remove([]),
 2239	maplist(split),
 2240	maplist(remove([])),
 2241	remove([]),
 2242	obj(obj_get([dir(F)])),
 2243	maplist(pred(F, ([[X|Y], "renamed."]:-
 2244		maplist(split(` `), Y, Y0),
 2245		maplist(remove([]), Y0, Y1),
 2246		maplist(insert("\\ "), Y1, Y2),
 2247		insert("@", Y2, Y3),
 2248		file_extension(Ext, X, _),
 2249		sh(mv(-i, F + X, F + Y3 + Ext)))
 2250		&
 2251		([P,Q]:- insert("\n", P, Q)))),
 2252	insert("\n").
 2253
 2254%   mv_over_directory(+L:directory, +M:directory, +S:state, -S0:state) is det.
 2255%   Move files over from L to M. The source and target name of a file
 2256%   are in the given state S.
 2257
 2258mv_over_directory(L, M) -->> dcl([dir(L), dir_target(M)]),
 2259	paragraph,
 2260	maplist(split),
 2261	maplist(remove([])),
 2262	remove([]),
 2263	obj(obj_get([dir(F), dir_target(G)])),
 2264	maplist(pred([F,G],
 2265			([[X|Y], "Renamed and moved."]:-
 2266				file_name(Y, Y0),
 2267				atomics_to_string([G,/, Y0], Y1),
 2268		 		file_extension(Ext, X, _),
 2269				modify_file_name(Y1, 0, Ext, Y2),
 2270				atom_codes(X0, X),
 2271				atomics_to_string([F,/, X0], X1),
 2272				rename_file(X1, Y2))
 2273			&
 2274			([P,Q]:- insert("\n", P, Q))
 2275		    )
 2276	       ),
 2277	insert("\n").
 2278
 2279%  file_name(+X:text, -Y:atom) is det.
 2280%	Concatenate a list X of blocks of codes into an atom Y
 2281%	with '@' as a block separator character.
 2282
 2283file_name --> insert(`@`), flatten, flip(string_codes).
 2284
 2285%  modify_file_name(+F:file_name, +I:integer, +E:extension, -G:File_name) is det.
 2286%	Modify the file name F to G by adding a minimum integer suffix J >= I
 2287%	to F when F conflicts with an existing one so that G does not so, otherwise,
 2288%	unify G with F.
 2289
 2290% ?- ejockey:modify_file_name('emacs-jockey', 0, '.pl', G).
 2291% ?- ejockey:modify_file_name('~/Desktop/test', 0, '.bib', G).
 2292% ?- ejockey:modify_file_name('~/Desktop/test', 1, '.bib', G).
 2293
 2294modify_file_name(F, 0, Ext, G):- !,
 2295	atomic_list_concat([F, Ext], F0),
 2296	(	exists_file(F0)
 2297	->	modify_file_name(F, 1, Ext, G)
 2298	;	G = F0
 2299	).
 2300modify_file_name(F, I, Ext, G):- atom_number(A, I),
 2301	atomic_list_concat([F, @, A, Ext], F0),
 2302	(	exists_file(F0)
 2303	->	J is I+1,
 2304		modify_file_name(F, J, Ext, G)
 2305	;	G = F0
 2306	).
 2307
 2308%  file_extension(-Ext:atom, +P:codes, -Q:codes) is det.
 2309%	Unify Ext with a file extension codes (including the '.' character) of
 2310%	P, and Q with the remainder prefix of P.  If no extension of P is found,
 2311%	unify Ext and Q with the empty atom '' and P, respective.
 2312
 2313% ?- ejockey:file_extension(X, `abc/.efg/a.b.c`, R).
 2314% ?- ejockey:file_extension(X, `abc/.efg/a.b.c/x`, R).
 2315
 2316file_extension(Ext) --> w(*(.)),  ".",  wl("[^\\./]*", X), end_of_list, !,
 2317	{ atom_codes(Ext, [0'. | X]) }.		%'
 2318file_extension('') --> [].
 2319
 2320%  insert_tab_nl(+N:int, +I:int, +T:list, -T0:list) is det.
 2321%	Insert tab codes or newline codes between each successive elements
 2322%	of T, and unify T0 with it, so that  writing all elements of the list T0
 2323%	in order shows up an array of raws of  N-elements, provided that I = N.
 2324
 2325% ?- ejockey:insert_tab_nl(3, 3, [a,b,c,d,e], R).
 2326insert_tab_nl(_, _, [], []).
 2327insert_tab_nl(N, 0, [X|Y], [[X,'\n']|Y0]):- !, insert_tab_nl(N, N, Y, Y0).
 2328insert_tab_nl(N, J, [X|Y], [[X,'\t']|Y0]):- J0 is J-1, insert_tab_nl(N, J0, Y, Y0).
 2329
 2330%  insert_nl(+X:list, -Y:list) is det.
 2331%	Shorthand for insert(`\n`, X, Y).
 2332
 2333insert_nl --> insert(`\n`).
 2334
 2335			/****************************************
 2336			*     listing tex command sequences.    *
 2337			****************************************/
 2338
 2339%  	handle([list, tex, cs]) is det.
 2340%   Listing tex command sequeces.
 2341%
 2342handle([list, tex, cs]) --> region,
 2343	texparse,
 2344	list_texcs,
 2345	sort,
 2346	insert("\n").
 2347
 2348%
 2349list_texcs_file(File, R):- read_file_to_codes(File, R0, []),
 2350	texparse(R0, R1),
 2351	list_texcs(R2, [], R1, []),
 2352	sort(R2, R).
 2353%
 2354list_texcs(X, Y):-  list_texcs(Y, [], X, []).
 2355
 2356%
 2357list_texcs([A|X], Y)	--> [cs(A)], !, list_texcs(X, Y).
 2358list_texcs([F|X], Y)	--> [env(F, B)], !,
 2359	{ list_texcs(X, X0, B, []) },
 2360	 list_texcs(X0, Y).
 2361list_texcs(X, Y)	--> [L], { listp(L) } , !,
 2362	{ list_texcs(X, X0, L, []) },
 2363	list_texcs(X0, Y).
 2364list_texcs(X, Y)	--> [_], !, list_texcs(X, Y).
 2365list_texcs(X, X)	--> [].
 2366
 2367
 2368		/************************************************
 2369		*     bi-directional converter for file name    *
 2370		%     with dakuten characters                   *
 2371		************************************************/
 2372
 2373%  dakuten_convert(?X:text, ?Y:text) is det and bi-directional.
 2374%	Replace each 'dakuten' and 'semi-dakuten' (voiced sound mark) ligature with
 2375%	the one character in utf8 encoding, and unify Y with the result so that Y is from
 2376%	from such ligatures; and vice versa. Note that copy-paste of Japanese file names
 2377%	of ligature free in Finder may yield codes that has (semi-)dakuten ligatures,
 2378%	which may cause troubles.
 2379
 2380% [2013/09, 2014/12]
 2381%  ex. "ば" <==> "ば”   (bi-directional)
 2382
 2383% ?- ejockey:dakuten_convert("プロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2384% ?- ejockey:dakuten_convert(`プロジェクト`, Y), ejockey:dakuten_convert(X, Y).
 2385% ?- ejockey:dakuten_convert('プロジェクト', Y), ejockey:dakuten_convert(X, Y).
 2386% ?- ejockey:dakuten_convert("プロジェクトプロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2387% 濁点 '゙'	半濁点 '゚'
 2388
 2389dakuten_convert(X, Y):- var(Y), !,
 2390	string_chars(X, U),
 2391	once(convert_chars(U, V)),
 2392	string_chars(Y, V).
 2393dakuten_convert(X, Y):-
 2394	string_chars(Y, V),
 2395	once(convert_chars(U, V)),
 2396	string_chars(X, U).
 2397
 2398convert_chars([], []).
 2399convert_chars([X, Y|R], [Z|S]):- conversion_table(Y, D, E),
 2400	chars_table_check(X, D, E, Z),
 2401	convert_chars(R, S).
 2402convert_chars([X|R], [X|S]):- convert_chars(R, S).
 2403
 2404%
 2405chars_table_check(X, [X|_], [Z|_], Z).
 2406chars_table_check(X, [_|U], [_|V], Z):- chars_table_check(X, U, V, Z).
 2407
 2408% conversion_table(a, X, Y) means that  ba <==> c  for each b in X and c in Y.
 2409conversion_table('゙',
 2410		['か', 'き', 'く', 'け', 'こ',
 2411		 'さ', 'し', 'す', 'せ', 'そ',
 2412		 'た', 'ち', 'つ', 'て', 'と',
 2413		 'は', 'ひ', 'ふ', 'へ', 'ほ'],
 2414		['が', 'ぎ', 'ぐ', 'げ', 'ご',
 2415		 'ざ', 'じ', 'ず', 'ぜ', 'ぞ',
 2416		 'だ', 'ぢ', 'づ', 'で', 'ど',
 2417		 'ば', 'び', 'ぶ', 'べ', 'ぼ']).
 2418conversion_table('゙',
 2419		['ウ',
 2420		 'カ', 'キ', 'ク', 'ケ', 'コ',
 2421		 'サ', 'シ', 'ス', 'セ', 'ソ',
 2422		 'タ', 'チ', 'ツ', 'テ', 'ト',
 2423		 'ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2424		['ヴ',
 2425		 'ガ', 'ギ', 'グ', 'ゲ', 'ゴ',
 2426		 'ザ', 'ジ', 'ズ', 'ゼ', 'ゾ',
 2427		 'ダ', 'ヂ', 'ヅ', 'デ', 'ド',
 2428		 'バ', 'ビ', 'ブ', 'ベ', 'ボ']).
 2429conversion_table('゚',
 2430		['は', 'ひ', 'ふ', 'へ', 'ほ'],
 2431		['ぱ', 'ぴ', 'ぷ', 'ぺ', 'ぽ`']).
 2432conversion_table('゚',
 2433		['ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2434		['パ', 'ピ', 'プ', 'ペ', 'ポ']
 2435	      ).
 2436
 2437
 2438
 2439%  trim_nl(-L:codes, -R:codes, +X:codes, -Y:codes) is det.
 2440%	Trim successive new line codes from both ends of X  as long as possible,
 2441%	and unify Y with the remainder of X.
 2442
 2443% ?-ejockey:trim_nl(L, R, `abc`, Y).
 2444% ?-ejockey:trim_nl(L, R, `\n\n\n`, Y).
 2445% ?-ejockey:trim_nl(L, R, `\nabc\n`, Y).
 2446% ?-ejockey:trim_nl(L, R, `\n\nabc\n\n`, Y).
 2447% ?-ejockey:trim_nl(L, R, `\n\n向井\n国昭\nabc\n\n`, Y).
 2448
 2449%
 2450trim_nl(L, R) --> wl(*("\n"), L),
 2451	w(*(.), Y),
 2452	wl(*("\n"), R),
 2453	end_of_list,
 2454	peek(Y).
 2455
 2456%
 2457end_of_list([], []).
 2458
 2459%  meta_handle(?X, -Y) is det.
 2460%	Parse the first line of the region for a handle command,
 2461%	and apply the command to the rest of the region.
 2462
 2463meta_handle --> region,
 2464	w("[^\n]*$", L),
 2465	{ parse_line(X, L, []),
 2466	  maplist(atom_codes, A, X)
 2467	},
 2468	pred([A, L], [U, V]:-
 2469		once(find_handle_call(A, L, U, V))).
 2470
 2471%  parse_line(+X:list, +Y:codes, -Z:codes) is det.
 2472%	Unify X with a list of (S-expression) tokens that
 2473%	appears in the deference between Y and Z.
 2474
 2475% ?- ejockey:parse_line(X, `a b c`, []).
 2476% ?- ejockey:parse_line(X, `a "b c""d e"`, []).
 2477% ?- ejockey:parse_line(X, `a "b c"'d \\"e'`, []).
 2478% ?- ejockey:parse_line(X, `'d\\e'`, []).
 2479% ?- ejockey:parse_line(X, `'d\e'`, []).
 2480% ?- ejockey:parse_line(X, `'d\\\\e'`, []).
 2481% ?- ejockey:parse_line(X, `"d\\\\\e"`, []).
 2482% ?- ejockey:parse_line(X, `"a"`, []).
 2483
 2484parse_line(X) --> wl("[\s\t]*"), parse_line0(X).
 2485
 2486parse_line0([A|X]) --> token(A), !, parse_line(X).
 2487parse_line0([]) --> [].
 2488
 2489
 2490% ?-coalgebra:show_am("\"([^\"\\\\]|(\\\\.))*\"" | "'([^'\\\\]|(\\\\.))*'" | "[^ \t\"']+").
 2491
 2492
 2493%  token(-X:token, +Y:codes, -Z:codes) is det.
 2494%	Unify X with a token in S-expression for the difference betwee Y and Z.
 2495
 2496% ?- ejockey:token(X, `abcd  `, Y).
 2497% ?- ejockey:token(X, `"ab\\\"d"`, Y), smash(X).
 2498%@ "ab\"d"
 2499% ?- ejockey:token(X, `"ab\\\"c\\\"d"`, Y), smash(X).
 2500%@ "ab\"c\"d"
 2501
 2502token(X) --> wl( "\"([^\"\\\\]|(\\\\.))*\""
 2503	       | "'([^'\\\\]|(\\\\.))*'"
 2504	       | "[^\s\t\"']+",
 2505		X).
 2506
 2507%  prolog_identifier(N:, X:codes, Y:codes) is det.
 2508%	Unify N with a list of codes
 2509%	such that N is the longest prolog_identifier prefix of X,
 2510%	and Y with the remaining suffix of X.
 2511%
 2512
 2513prolog_identifier(N) --> wl("[a-z][a-zA-Z0-9_]*", N, []).
 2514
 2515%  keyword(N:, X:codes, Y:codes) is det.
 2516%	Unify N with a list of codes
 2517%	such that N is the longest keyword prefix of X,
 2518%	and Y with the remaining suffix of X.
 2519%
 2520
 2521keyword(N) --> wl("[a-zA-Z][a-zA-Z0-9_]*", N, []).
 2522
 2523%  collect_tokens(+W:type, +X:codes, -Y:tokens) is det.
 2524%	Collect tokens in X that satisfies W, and
 2525%	unify Y with it.
 2526
 2527collect_tokens(W, X, Y):- collect_tokens(W, Y, [], X, []).
 2528
 2529%
 2530collect_tokens(W, X, Y) --> [_], collect_tokens(W, X, Y).
 2531collect_tokens(_, X, X)-->[].
 2532
 2533% % [2013/10/07] To escape special characters of the file name
 2534% % in order to pass it to sh/1.
 2535% % ?- ejockey:escape_shell_char(`a : (b)`, R), atom_codes(A, R).
 2536% %@ A = 'a \\@ \\(b\\)' .
 2537
 2538escape_shell_char(X, Y):-
 2539  foldr(pred(	[0'(,  U, [0'\\,    0'(  | U]	] &		%'
 2540		[0'),  U, [0'\\,    0')  | U]	] &
 2541		[0'\', U, [0'\\,    0'\' | U]	] &
 2542		[0':,  U, [0'\\,    0'@  | U]	] &
 2543		[0'/,  U, [0'\\,    0'@  | U]	] &
 2544		[A,    U, [A|U]			]
 2545	    ),
 2546	X, [], Y).
 2547
 2548% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X).
 2549
 2550% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X),
 2551%	basic:smash(X).
 2552
 2553remove_leading_comment_chars(X, Y) :-
 2554	remove_leading_comment_chars(Y, [], X, []).
 2555%
 2556remove_leading_comment_chars(X, Y) -->
 2557	wl("([% \t]|(%@*)|(\\?-))*"),
 2558	wl("[^\n]*", X, X0),
 2559	remove_leading_comment_chars_continue(X0, Y).
 2560%
 2561remove_leading_comment_chars_continue([0'\n|X], Y) --> "\n",  %' %
 2562	remove_leading_comment_chars(X, Y).
 2563remove_leading_comment_chars_continue(X, X) --> [].
 2564
 2565% ?- comment(X, [], `/* abc   \ndef */xyz`, R), smash(X), nl, smash(R).
 2566%@ /* abc   def */
 2567%@ xyz
 2568
 2569comment --> w(@comment).
 2570%
 2571comment(X, Y)-->w(@comment, X, Y).
 2572%
 2573uncomment --> wl("%+ ?"|[]).
 2574
 2575module_name(Codes, Name):- once(module_name(Name, Codes, _)).
 2576%
 2577module_name(Name) --> wl("[\s\t]*:-[\s\t]*"),
 2578		      "module(",
 2579		      wl("[^,\s\t]+", Name).
 2580module_name(????) --> [].
 2581
 2582%
 2583white_filler --> wl("[\s\t\n]*").
 2584%
 2585non_white_line(X):- \+ white_filler(X, []).
 2586
 2587% ?- C = `ab cd`, ejockey:to_ascii_space(`ab cd`, R).
 2588%@ C = [97, 98, 12288, 99, 100],
 2589%@ R = [97, 98, 32, 99, 100].
 2590
 2591to_ascii_space(X, Y) :- once(to_ascii_space(Y, [], X, [])).
 2592
 2593to_ascii_space([0'\s|X], Y) --> " ", to_ascii_space(X, Y).  % '
 2594to_ascii_space([C|X], Y)--> [C], to_ascii_space(X, Y).
 2595to_ascii_space(X, X)--> []