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.
  775
  776%! 	handle([help]) is det.
  777%   Show all handle commands.
  778%!  handle([help]) --> {setof(H, P^Q^R^clause(handle(H,P,Q), R), S),
  779% 		 sort(S, S1),
  780% 		 maplist(pred(([X, Y]:-
  781% 				numbervars(X,0,_),
  782% 				write_to_chars(X, Z, []),
  783% 				string_codes(Z, Y))),
  784% 			S1, S2),
  785% 		 insert_tab_nl(4, 4, S2, R)
  786% 		},
  787% 		peek(R).
  788
  789%! 	handle([handle, list]) is det.
  790%   Set Lisp variables  handle-list to the list of all handles.
  791
  792handle([handle, list]) --> region,
  793    {findall(H, clause(handle(H,_,_), _), S),
  794	 sort(S, S1),
  795	 maplist(pred(([H, H0] :-
  796			   foldl(pred([H, H0],
  797							  ( [X, ['VAR'|L], L]:- var(X) )
  798							& [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.
  815handle([reload, buffer, file]) -->
  816	{ call_lisp('buffer-file-name'(), term(File)),
  817  	  string_codes(S, File),
  818	  unload_file(S),
  819	  load_files(S, [silent(true)]) }.
Generate edit commnad ?- edit(X) from the symbol at the current point.
  823handle([edit])--> { prolog_symbol_at_point(X) },
  824			  peek(["\n\n% ?- edit(", X, ").\n"]).
Take a time-stamped memo, and display it in the emacs window.
  829handle([take, memo]) --> region,
  830 	{   lisp('time-stamp', Dir),
  831		getinfo_string("date +%Y-%m-%d", Today),
  832		atomics_to_string([Dir, Today], File0),
  833		expand_file_name(File0, [File|_]),   % File is of type atom.
  834		pshell(touch(File))
  835	},
  836	pred([Today, File],
  837		 ( [ Note, []]
  838		   :- file:push_to_file(
  839					 basic:smash(["[", Today, "]\n",
  840								  Note,
  841								  "\n"]),
  842							File))),
  843	{	atom_string(File, File0),
  844		lisp('find-file'(File0))
  845	}.
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.
  857handle([choose, working, directory]) -->
  858	{	choose_folder(X),
  859		set_string(working_directory, X)
  860	},
  861	peek(X).
Choose a folder.
  865handle([choose, folder]) --> {choose_folder(X)}, peek(X).
Choose a file.
  870handle([choose, files]) -->
  871	{	choose_folder(X),
  872		X = [D],
  873		directory_files(D, Files)
  874	},
  875	peek(Files),
  876	insert("\n").
directory_files.
  880handle([directory, files]) -->
  881	{	choose_folder(X),
  882		X = [ D ],
  883		directory_files(D, Files)
  884	},
  885	peek(Files),
  886	insert("\n").
  887%
  888handle([rename, files]) --> region,
  889	split,
  890	remove([]),
  891	maplist(flip(string_codes)),
  892	rename_files_base,
  893	overwrite.
  894%
  895handle([display, renamed]) --> region,
  896	split,
  897	remove([]),
  898	maplist(flip(string_codes)),
  899	rename_files_base_display,
  900	overwrite.
  901
  902
  903% short for handle([open, pdf]).
  904handle([o]) --> handle([open, pdf]).
  905handle([m]) --> handle([jisui, archives]).
  906%
  907handle([jisui, archives])--> trim_line_string,
  908	current(A),
  909	{ jisui_archives(B),
  910	  expand_file_name(B, [B0|_]),
  911	  run_shell(mkdir, ['-p', B0]),
  912%	  pshell(mv(A, B0))
  913%  	  process_create(path(mv), [A, B0], [])
  914	  run_shell(mv, [A, B0])
  915	},
  916	clear,
  917	overwrite.
  918
  919%
  920rename_files_base([], []).
  921rename_files_base([X,Y|Z], [U, "\n"|V]):-
  922	subst_file_base(X, Y, U),
  923	rename_file(X, U),
  924	rename_files_base(Z, V).
  925
  926% ?- subst_file_base("/a/ b/b", c, Z).
  927subst_file_base(X, Y, Z):-
  928	atomic_list_concat(X0, /, X),
  929	append(U, [_], X0),
  930	append(U, [Y], V),
  931	atomic_list_concat(V, /, Z).
Choose files.
  935handle([choose, files]) -->
  936	{	choose_files(X)
  937	},
  938	peek(X),
  939	insert("\n").
Choose a folder, and open it.
  944handle([choose, folder, open]) -->
  945	{	choose_folder(X),
  946		term_string(X, Y),
  947		pshell(open(Y))
  948	},
  949	peek(X).
  950
  951
  952		/********************
  953		*     sort lines    *
  954		********************/
Sort lines.
  958handle([sort, lines]) --> region,
  959						  split,
  960						  sort,
  961						  insert("\n"),
  962						  overwrite.
Trim leading white codes and sort the trimed lines.
  967handle([trim, sort, lines]) --> region,
  968						  split,
  969						  remove([]),
  970						  maplist(phrase(wl("[\s\t]*"))),
  971						  sort,
  972						  maplist(pred([L, [L,"\n"]])),
  973						  overwrite.
  974end_of_codes([], []).
  975%
  976trim_line --> line, phrase(wl("[\s\t]*")).
  977%
  978trim_line_string --> line, trim_line, flip(string_codes).
open a file with a full path in the current line as pdf.
  982handle([open, pdf]) --> trim_line,
  983				current(X),
  984				{	string_codes(Y, X),
  985					run_shell(open, ['-a', "Preview", Y])
  986				},
  987				clear.
  988
  989
  990		/************************
  991		*     shell in buffer   *
  992		************************/
Run shell commands in the region.
  997handle([shell]) --> set_mark_region,
  998	region,
  999	split,
 1000	remove([]),
 1001	insert(" ; "),
 1002        {
 1003	    tmp_file_stream(utf8, File, Stream),
 1004	    close(Stream)
 1005	},
 1006	peek(X, ["( ", X, " ) > ", File]),
 1007	smash,
 1008	pred(File, ([Shell_in_string, Codes]:-
 1009			shell(Shell_in_string),
 1010			read_file_to_codes(File, Codes, [tail([]), encoding(utf8)])
 1011		   )
 1012	    ),
 1013        {
 1014	    delete_file(File)
 1015	}.
Run shell commnad in the region, and convert the Japanese ligature to the normal form.
 1020handle([shell, dakuten]) --> handle([shell]), dakuten_convert.
Run message command of Lisp.
 1025handle([message]) --> region, pred([M, []]:- message(M)).
 1026
 1027		/*********************
 1028		*     prolog/lisp    *
 1029		*********************/
 1030
 1031solve_once -->
 1032	remove_leading_comment_chars,
 1033	current(X),
 1034	{	string_codes(Str, X),
 1035		term_string(G, Str, [variable_names(Es)]),
 1036		(	once(G)		->
 1037			numbervars(Es),
 1038			maplist(pred([Eq, Sol]:- term_string(Eq, Sol,
 1039									 [	numbervars(true),
 1040										quoted(false)])),
 1041					Es, Sols0),
 1042			(	Sols0 = [] -> R =  "\n%@ true.\n"
 1043			;	insert(",\n%@ ", Sols0, Sols),
 1044				R = ["\n%@ ", Sols,  "\n%@ true."]
 1045			)
 1046		;	R = "\n%@ false.\n"
 1047		)},
 1048	peek(R).
run the current region by once as prolog query.
 1054%@ ?- append([a,c],[c,d], []).
 1055%@ false.
 1056
 1057
 1058%@ ?- append([a,b],[c,d], [a,b,c,d]).
 1059%@ ?- append([a,c],[c,d], X), append(X, X, Z),
 1060%@ append(Z, Z, U).
 1061
 1062handle([once])--> region, solve_once.
Run a Prolog goal in the paragraph between \n\n and \n\n Emacs short cut: s-M-<return>
 1068% ?- 1 = 1,
 1069%	2 = 2,
 1070%   3 = 3.
 1071
 1072% ?- X = 1,
 1073%	Y = 2,
 1074%   Z = 3.
 1075
 1076handle([prolog, paragraph]) --> set_mark_region, region, solve_once.
Run a prolog goal on the current line. emacs short cut: C-<return>
 1082%   ?- X = 1.
 1083handle([prolog, line])  --> line, solve_once.
 1084
 1085
 1086
 1087%	Put the comment symbol to each line of the region.
 1088handle([comment, region])  --> region,
 1089	split,
 1090	maplist(comment),
 1091	insert("\n"),
 1092	overwrite.
Remove the comment symbol of each line of the region.
 1096handle([uncomment, region])  --> region,
 1097	split,
 1098	maplist(uncomment),
 1099	insert("\n"),
 1100	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.
 1119handle([enum]) --> region, snippets:environment(enumerate), overwrite.
Make a LaTeX eitemize environment from the items in the region.
 1124handle([eit])  --> region, snippets:environment(itemize), overwrite.
Put "<code>" and "</code>" around the region.
 1128handle([html,tag,code])  --> region,
 1129			 peek(X, ["<code> ", X, " </code>"]),
 1130			 overwrite.
Run the region as a goal igonoring errors.
 1134handle([ignore, goal|R]) --> region_or_line(R),
 1135	herbrand(_),
 1136	pred([X, []]:- ignore(X)).
Run the region as a goal catching errors.
 1140handle([solve,  goal|R]) -->  region_or_line(R),
 1141	herbrand(_),
 1142	pred(B, [X, ["\n", R, "\n"]]:- catch_once(X, B, R)).
Insert tab before the each line of the region.
 1147handle([shift, region]) -->  region,
 1148	split,
 1149	maplist(pred([X, ['\t'|X]])),
 1150	insert('\n'),
 1151	overwrite.
Insert A before the each line of the region.
 1155handle([insert, before, A]) -->  region,
 1156	split,
 1157	maplist(pred(A, [X, [A|X]])),
 1158	insert('\n'),
 1159	overwrite.
 1160
 1161		/****************
 1162		*     indent    *
 1163		****************/
insert tab. ! handle([indent, region]) is det. ! handle([indent, region, N]) is det. Indent the region.
 1171handle([tab, region])	-->  indent_region(0'\t, 1). %'
 1172handle([tab, region, N])-->  { atom_number(N, N0) },
 1173	indent_region(0'\t, N0).		%'
 1174handle([indent, region])--> indent_region(0'\s, 4).		%'
 1175handle([indent, region, N]) -->  { atom_number(N, N0) },
 1176	indent_region(0'\s, N0).					%'
Put framed header without centering.
 1181handle([header]) -->  region,
 1182	split,
 1183	maplist(remove_trailing_white),
 1184	maplist(detab),
 1185	remove_enveloping_nulls,
 1186	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1187	{ Width is Max + 7,
 1188	  length(Hr, Width),
 1189	  maplist(=("*"), Hr)
 1190	},
 1191	maplist(fill_trailing_spaces(Width)),
 1192	maplist(pred([X, ["\t*", X, "*\n"]])),
 1193	peek(Body,	["\t/", Hr, "*\n",
 1194				Body,
 1195				"\t*", Hr, "/\n"]),
 1196	overwrite.
 1197
 1198%
 1199fill_trailing_spaces(Width, X, [X, Y]):-
 1200	length(X, L),
 1201	J is Width - L,
 1202	length(Y, J),
 1203	maplist(=("\s"), Y).
 1204
 1205% ?- ejockey:remove_enveloping_nulls([[], a, [], b,[]], R).
 1206%@ R = [a, [], b] .
 1207remove_enveloping_nulls -->[[]], remove_enveloping_nulls.
 1208remove_enveloping_nulls -->[], remove_trailing_nulls.
 1209%
 1210remove_trailing_nulls(X, []):- nulls(X), !.
 1211remove_trailing_nulls([X|R], [X|S]):-
 1212	remove_trailing_nulls(R, S).
 1213
 1214%
 1215nulls([[]|R]):- nulls(R).
 1216nulls([]).
 1217
 1218% ?- ejockey:remove_trailing_white(X, `abc   `, Y).
 1219% ?- trace, ejockey:remove_trailing_white(`abc   `, Y).
 1220% ?- trace, ejockey:remove_trailing_white(`a`, Y).
 1221
 1222handle([trim, trailing, white]) --> region, remove_trailing_white(X), peek(X).
 1223
 1224remove_trailing_white(X) --> w(".*", X), wl("[\s\t]*$").
 1225
 1226remove_trailing_white --> w(".*", X), wl("[\s\t]*$"), peek(X).
Removing tab from each line of the region.
 1231handle([detab]) --> region, detab, overwrite.
 1232%
 1233detab_spaces(`\s\s\s\s`).
 1234%
 1235detab(X, Y):- detab(X, Y, []).
 1236
 1237% ?- ejockey:detab(`\ta\t\b`, X, []).
 1238detab([0'\t|R], X, Y):- !, detab_spaces(S),   %'
 1239	append(S, X0, X),
 1240	detab(R, X0, Y).
 1241detab([A|R], [A|X], Y):-detab(R, X, Y).
 1242detab([], X, X).
Make a framed header wiht centering.
 1247handle([shift, frame|Optional]) --> region_or_line(Optional),
 1248	split,
 1249	maplist(trim_white),
 1250	remove_enveloping_nulls,
 1251	pred(Max, ([X, X]:- maplist(length,X, L), poly:list_max(L, Max))),
 1252	{ Width is Max + 11 },
 1253	maplist(pred([Width, Max], ( [A, B]:-
 1254				length(B, Width),
 1255				N is (Width - Max) div 2,
 1256				length(L, N),
 1257			       	append([ ['*'], L, A, R, ['*']], B),
 1258				maplist(=('\s'), L),
 1259			        maplist(=('\s'), R)))),
 1260	{	length(Top, Width),
 1261		length(Bottom, Width) ,
 1262		Top = ['/'|L0],
 1263		append(L1, ['/'], Bottom),
 1264		maplist(=('*'), L0),
 1265		maplist(=('*'), L1)
 1266	},
 1267	maplist(pred([X, ['\t\t', X, '\n']])),
 1268	peek(Body, ['\t\t', Top, '\n',
 1269				Body,
 1270				'\t\t', Bottom, '\n']),
 1271	overwrite.
 1272
 1273/*--------------------------------------------
 1274	long comment /* ... */
 1275--------------------------------------------*/
 1276
 1277handle([long, comment]) --> region,
 1278	peek(Block, [
 1279			"/*--------------------------------------------\n",
 1280			Block,
 1281			"--------------------------------------------*/\n"
 1282			]),
 1283	overwrite.
Convert the region to a comma list of lines in the region added with single quotation marks.
 1290handle([single, quote]) --> region,
 1291	split,
 1292	remove([]),
 1293	maplist(html:single_quote),
 1294	insert(',\n'),
 1295	overwrite.
Convert the region to a comma list of lines in the region added with double quotation marks.
 1300handle([double, quote]) --> region,
 1301	split,
 1302	remove([]),
 1303	maplist(html:double_quote),
 1304	insert(',\n'),
 1305	overwrite.
Copy region to copyboad; lualatex it with standalone class.
 1309handle([region, standalone])  -->
 1310	{ call_lisp(pbcopy()),
 1311	  shell(standalone, 0)
 1312	}.
lualatex pasteboard text with standalone class.
 1316handle([pasteboard, standalone])  --> { shell(standalone, 0)}.
Show a LaTeX description environment.
 1322handle([description]) -->  peek([
 1323	"\\begin{description}[style=multiline, labelwidth=1.5cm]",
 1324	"\\item[\\namedlabel{itm:rule1}{Rule 1}] Everything is easy with \\LaTeX",
 1325	"\\item[\\namedlabel{itm:rule2}{Rule 2}] Sometimes it is not that easy\\\\",
 1326	"$\\to$ \\ref{itm:rule1} applies",
 1327	"\\end{description}\n"	]),
 1328	insert("\n"),
 1329	overwrite.
Generate a LaTeX listlisting environment.
 1334handle([list, listing]) --> region,
 1335	pred([	X, [	"\\begin{lstlisting}[caption={},label=src:]\n",
 1336			X,
 1337			"\\end{lstlisting}\n"	]]),
 1338	overwrite.
Generate a LaTeX align* environment.
 1341handle([begin, align]) --> region,
 1342	pred([	X, [	"\\begin{align*}\n",
 1343			X,
 1344			"\\end{align*}\n"	]]),
 1345	overwrite.
Generate TeX \vbox template.
 1348handle([vbox]) --> peek([
 1349	"$$\\vbox{\\offinterlineskip",
 1350        "\\halign{\\strut",
 1351        "\\vrule\\vrule\\quad\\textbf{#}\\hfill\\quad & \\vrule\\quad\\hfill #cm \\quad ",
 1352         "& \\vrule\\quad\\hfill #kg \\quad\\vrule\\vrule\\cr",
 1353        "\\noalign{\\hrule\\hrule}",
 1354        "鈴木 一太郎 & 168 & 74 \\cr",
 1355        "\\noalign{\\hrule} ",
 1356        "山田 太郎   & 170 & 72 \\cr",
 1357        "\\noalign{\\hrule} ",
 1358        "渡辺 次郎   & 192 & 103 \\cr",
 1359        "\\noalign{\\hrule\\hrule} ",
 1360        "}}$$"		]),
 1361	insert("\n").
Generate TeX halign
 1365handle([halign]) --> peek([
 1366	"\\halign{",
 1367%	"\\hfill$#$\\hfill\\qquad&\\hfill$#$\\hfill&\\quad\\text{#}\\cr\n",
 1368	"\\hfill$#=\\>$ & $#$ \\hfill & \\qquad \\mbox{#} \\cr\n",
 1369	" &  &   \\cr\n",
 1370      	" &  &   \\cr\n",
 1371	" &  &   \\cr\n",
 1372	"}"	]).
Generate a LaTeX cases environment.
 1376handle([case, equation]) --> region,
 1377	pred([	Left, [		"$", Left, "= \n",
 1378				"\\begin{cases}\n",
 1379				"     &  \\mbox{} \\\\\n",
 1380				"     &  \\mbox{} \\\\\n",
 1381				"     &  \\mbox{} \n",
 1382				"\\end{cases}$\n"	]]),
 1383	overwrite.
Generate a LaTex eqnarray* environment.
 1388handle([eqn, array]) --> region,
 1389	pred([	_, [	"\\begin{eqnarray*}\n",
 1390			"     &=&          \\\\\n",
 1391			"     &=&          \\\\\n",
 1392			"     &=&          \\\\\n",
 1393			"\\end{eqnarray*}\n"	]]),
 1394	overwrite.
Parse and Generate a LaTeX eqnarray* environment.
 1399handle([parse, eqn, array]) --> region, split, remove([]),
 1400	maplist(split(`=`)),
 1401	maplist(pred([[X|Y],	[X, " &=& ", Y]])),
 1402	insert("\\\\\n"),
 1403	pred([Body, [	"\\begin{eqnarray*}\n",
 1404			Body,
 1405			"\n\\end{eqnarray*}\n"	]]),
 1406	overwrite.
! handle([q, F,X, N]) is det.
 1414handle([q, F,X, N]) -->
 1415	peek([F, "(", X, "_1, ", X, "_2, ", "\\ldots ,", X, "_", N, ")"]).
 1419handle([q, F, X, N0, N]) -->
 1420	peek([F, "(", X, "_", N0, ", ", X, "_1, ", "\\ldots ,", X, "_", N, ")"]).
 1421%! 	handle([q]) is det.
 1422%
 1423%
 1424handle([q]) --> region, split(` `), remove([]),
 1425	pred(	([[F, X, N], E]:- handle([q, F, X, N], _, E))
 1426		&		([[F, X, N0|N], E]:- handle([q, F, X, N0, N], _, E))),	overwrite.
 1432handle([ref])	--> region, pred([X, ["\\ref{", X, "}"]]), overwrite.
 1436handle([cite])	--> region, pred([X, ["\\cite{", X, "}"]]), overwrite.
 1440handle([cs, N]) --> region,
 1441	pred([N],[X, ["\\", N, "{", X, "}"]]),
 1442	overwrite.
 1443%
 1444%! 	handle([parse, bind, context]) is det.
 1445%
 1446%
 1447handle([parse, bind, context])	--> region,	parse_bind_context, overwrite.
 1451handle([parse, bind, context, append])	--> region, parse_bind_context.
 1455handle([eval, markup, text])		--> region, eval_markup_text, overwrite.
 1459handle([eval, markup, text, append])	--> region, eval_markup_text.
 1460%
 1461%! 	handle([tag, l]) is det.
 1462%
 1463%
 1464handle([tag, l])	--> {nb_getval(phrase_tag, G), herbrand_opp(G, G0)},  % to list the saved tag
 1465	peek(G0).
 1469handle([tag, s|P])	--> region_or_line(P),		% to save the tag
 1470	peek(Q),
 1471	{parse_phrase_save(Q)},
 1472	peek("\n the tag saved.\n").
 1476handle([tag, a])  --> region,
 1477	{ nb_getval(phrase_tag, G) },
 1478	act(G),
 1479	overwrite.
 1484region_debug(X, Y):- var(X), !, region(X, Y).
 1485region_debug(X, X).
 1486
 1487
 1488handle([t, a])  --> handle([tag,a]).
Generate bibliography commands.
 1491handle([bib]) --> peek(["\\bibliographystyle{plain}\n",
 1492	"\\bibliography{jmukai,mukai}\n"]).
 1493
 1494% Convert  delicious 3 data in book/1 to bibtex form.
 1495handle([book, bibtex]) --> region,
 1496		paragraph,
 1497		remove([]),
 1498		maplist(herbrand),
 1499		maplist(book_bibitem),
 1500		insert("\n"),
 1501	    overwrite.
 1502
 1503% Convert  csv data to a dict  with keywords.
 1504handle([csv, bibtex])	--> region,
 1505						csv_to_dict,
 1506						peek(key_dict(_, L), L),
 1507						maplist(dict_bibtex).
 1508
 1509% Convert  csv data to a dict  with keywords.
 1510% ?- ejockey:csv_to_dict(`a\tb\tc\n1\t2\t3\n4\t5\t6`, R).
 1511%@ R = key_dict([a, b, c], [[a="1", b="2", c="3"], [a="4", b="5", c="6"]]) .
 1512
 1513csv_to_dict --> split,
 1514		remove([]),
 1515		maplist(split("\t")),
 1516		peek([H|R], R),
 1517		{	maplist(atom_codes, Keys0, H),
 1518			map_key_tbl(M),
 1519			map_key(Keys0, M, Keys)
 1520		},
 1521		maplist(pred(Keys,
 1522					 ([A, B]:-
 1523						 maplist(pred([K, A0, K=A1]:-
 1524									 string_codes(A1, A0)),
 1525								 Keys, A, B)))),
 1526		peek(D, key_dict(Keys, D)).
 1527
 1528%
 1529dict_bibtex(L, BB):-
 1530	maplist(pred([K=V, [K, " = ", "{", V, "}"]]), L, Items),
 1531	insert(",\n", Items, Items0),
 1532	smash(["@book{", "to be filled", ",\n", Items0, "\n}\n"], BB).
 1533%
 1534map_key_tbl([creator-author, 'ISBN'-isbn]).
 1535
 1536%
 1537map_key([],_,[]).
 1538map_key([K|R],M,[K0|R0]):- memberchk(K-K0, M), !,
 1539						   map_key(R, M, R0).
 1540map_key([K|R],M,[K|R0]):-  map_key(R, M, R0).
Generate a LaTeX thm environment.
 1545handle([thm|X])--> region_or_line(X),
 1546	peek(Y, ["\\begin{thm}\\label{thm:}\n", Y, "\\end{thm}\n"]),
 1547	overwrite.
Generate a LaTeX prop environment.
 1553handle([prop|X])--> region_or_line(X),
 1554	peek(Y, ["\\begin{prop}\\label{prop:}\n", Y, "\\end{prop}\n"]),
 1555	overwrite.
Generate a LaTeX lemma environment.
 1560handle([lem|X])--> !, region_or_line(X),
 1561	peek(Y, ["\\begin{lemma}\\label{lem:}\n", Y, "\\end{lemma}\n"]),
 1562	overwrite.
Generate a LaTeX cor environment.
 1566handle([cor|X])-->region_or_line(X),
 1567	peek(Y, ["\\begin{cor}\\label{cor:}\n", Y,"\\end{cor}\n"]),
 1568	overwrite.
Generate a LaTeX ex environment.
 1572handle([ex|X])--> region_or_line(X),
 1573	peek(Y, ["\\begin{ex}\n", Y, "\\end{ex}\n"]),
 1574	overwrite.
Generate a LaTeX df environment.
 1578handle([df|X])--> region_or_line(X),
 1579	peek(Y, ["\\begin{df}\\label{df:}\n", Y, "\\end{df}\n"]),
 1580	overwrite.
Generate a LaTeX cases environment template. For example try for f(x)
 1585handle([cases|X])--> region_or_line(X),
 1586	peek(Y, ["\\[", Y, " =\n",
 1587			 "\t\\begin{cases}\n",
 1588				 "\t\t  & (\t\t\t  ) \\\\\n",
 1589				 "\t\t  & (\t\t\t  ) \\\\\n",
 1590				 "\t\t  & (\t\t\t  ) \n",
 1591			  "\t\\end{cases}\n",
 1592			"\\]\n"
 1593			]),
 1594	overwrite.
 1595%
 1596handle([emph|X])--> region_or_line(X),
 1597	peek(Y, ["\\emph{", Y, "}"]),
 1598	overwrite.
 1599
 1600handle([mbox|X])--> region_or_line(X),
 1601	peek(Y, ["\\mbox{", Y, "}"]),
 1602	overwrite.
Generate a LaTeX rem environment.
 1606handle([rem|X])--> region_or_line(X),
 1607	peek(Y, ["\\begin{remark}\\label{rem:}\n",Y,"\\end{remark}\n"]),
 1608	overwrite.
Generate a LaTeX proof environment.
 1612handle([proof|X])-->region_or_line(X),
 1613	peek(Y, ["\\begin{Proof}\n",Y,"\\end{Proof}\n"]),
 1614	overwrite.
Insert red color macro.
 1618handle([red|X])	--> region_or_line(X),
 1619					peek(Y, ["\\Red{", Y, "}"]), overwrite.
Insert blue color macro.
 1622handle([blue|X])	--> region_or_line(X),
 1623						peek(Y, ["\\Blue{", Y, "}"]), overwrite.
Insert green color macro.
 1627handle([green|X]) --> region_or_line(X),
 1628					  peek(Y, ["\\Green{", Y, "}"]),
 1629					  overwrite.
 1630
 1631% I don't remember what is the purpose of the following handle.
 1632%!  handle([mkh])	--> region,
 1633% 	split,
 1634% 	maplist(pred( ( [X, Y]:-
 1635% 						html:single_quote(X, X0),
 1636% 						atom_codes(Y, X0)))),
 1637% 	pred([L, ( handle([names]
 1638% 					 ) --> peek(L), insert_nl, ".")]).
Put font macro \mathscr
 1642handle([ms|X])	--> region_or_line(X),
 1643					peek(Y, ["\\mathscr{", Y, "}"]), overwrite.
Generate a LaTeX euation environment with a label command.
 1647handle([eq|X])	--> region_or_line(X),
 1648	peek(Y, ["\\begin{equation}\\label{eq:}\n",
 1649				Y, "\n",
 1650			"\\end{equation}\n"]),
 1651	overwrite.
get the module name from the source in the current buffer defined by ":- module(<name>, ...)."
 1656handle([get, module, name]) -->
 1657 {
 1658	wait(progn(
 1659		setq(point_saved, point()),
 1660		'goto-char'('point-min'()))),
 1661	line_get(Obj),
 1662	obj_get([line(Line)], Obj),
 1663	string_codes(Line, Codes),
 1664	module_name(Codes, Name),
 1665	wait('goto-char'(point_saved))
 1666    },
 1667    peek(Name).
Set query context.
 1670handle([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.
 1677handle([set, query, context]) -->
 1678		handle([get, module, name]),
 1679		peek(C, ["% ?- module(", C, ")."]),
 1680		current(X),
 1681		{	smash(X) },
 1682		peek([]),
 1683		{	wait('keyboard-quit'()) }.
 1684
 1685		/*******************
 1686		*     directory    *
 1687		*******************/
Run the shell command pwd.
 1691handle([pwd])	-->
 1692	{
 1693		get_string(working_directory, Path)
 1694	},
 1695	peek(Path).
Set target directory.
 1699handle([set, target, directory])	-->
 1700	{	line_get(Obj),
 1701		obj_get([line(Line)], Obj),
 1702		trim_white(Line, DirPath),
 1703		string_codes(S, DirPath),
 1704		expand_file_name(S, [S0|_]),
 1705		set_string(target_directory, S0)
 1706	}.
Choose working directory, and set the working_directory to it.
 1712handle([cwd]) -->
 1713	{	choose_folder(X),
 1714		set_string(working_directory, X),
 1715		working_directory(_, X)
 1716	},
 1717	peek(X).
Change director to the HOME.
 1722handle([cd]) -->
 1723	{	expand_file_name("~/", [D]),
 1724		set_string(working_directory, D),
 1725		working_directory(_, D)
 1726	},
 1727	peek(D).
Change directory like "../"
 1732handle([cd, up]) -->
 1733	{
 1734		get_string(working_directory, Path),
 1735		change_unix_path(up, Path, New_Path),
 1736		set_string(working_directory, New_Path),
 1737		working_directory(_, New_Path)
 1738	},
 1739	peek(New_Path).
Call Finder open.
 1746handle([open])	-->
 1747	{
 1748		line_get(Obj),
 1749		obj_get([line(Line)], Obj),
 1750		trim_white(Line, Line0),
 1751		double_quote(Line0, X),
 1752		(	Line0 = [0'/|_]						% '
 1753		-> 	pshell(open(X))
 1754		;	string_codes(XStr, X),
 1755			handle_open_relative(XStr)
 1756		)
 1757	}.
Call Finder open all files in the region.
 1763handle([open, *]) -->
 1764	{	get_string(working_directory, S),
 1765		S\== ""
 1766	},
 1767	region,
 1768	split,
 1769	remove([]),
 1770	reverse,
 1771	current(L),
 1772	{
 1773	maplist(pred(S, ([X] :-
 1774			double_quote([S, X], SX),
 1775			pshell(open(SX)))),
 1776		L)
 1777	},
 1778	clear
 1779	;
 1780	peek("**** directory not found. ****\n").
 1781
 1782 		/*****************************
 1783		*     Accessing Directory    *
 1784		*****************************/
Call Finder open for directory.
 1787handle([finder, open, directory])	-->
 1788	{
 1789		line_get(Obj),
 1790		obj_get([line(Line)], Obj),
 1791		first_token_codes(Line, Directory),
 1792		sh(open(-a('Finder'), Directory))
 1793	}.
 1794
 1795append_slash_code([], [0'/]):-!.	%'
 1796append_slash_code(Line, Line0):- last(Line, C),
 1797	(	C == 0'/ -> Line0 = Line		%'
 1798	;   append(Line, [0'/], Line0)		%'
 1799	).
Set working directory to working_directory.
 1802handle([swd])	-->
 1803	{	line_get(Obj),
 1804		obj_get([line(Line)], Obj),
 1805		trim_white(Line, Line0),
 1806		append_slash_code(Line0, Line1),
 1807		first_token_codes(Line1, Directory),
 1808		string_codes(Dir_string, Directory),
 1809		expand_file_name(Dir_string, [Full_path|_]),
 1810		nb_setval(working_directory, Full_path),
 1811		atom_string(Full_path, S),
 1812		set_string(working_directory, S)
 1813	},
 1814	peek(Full_path).
Set working directory to the default directory.
 1820handle([swd, (.)])-->
 1821	{	call_lisp_value('default-directory', D),
 1822		string_codes(X, D),
 1823		expand_file_name(X, [Full_path|_]),
 1824		nb_setval(working_directory, Full_path),
 1825		atom_string(Full_path, S),
 1826		set_string(working_directory, S)
 1827	},
 1828	peek([]).
Open the default directory.
 1833handle([finder, default, directory])	-->
 1834	{	call_lisp_value('default-directory', D),
 1835		string_codes(X, D),
 1836		sh(open(X))
 1837	}.
 1838
 1839%
 1840handle([directory, path])	-->
 1841	{	call_lisp_value('default-directory', D)
 1842	},
 1843	peek(D).
 1844%
 1845handle([file, path]) -->
 1846	{ lisp(list('default-directory', 'buffer-name'()), List)
 1847	},
 1848	peek(List).
List all files in the working directory.
 1853handle([list, files])		--> % ls
 1854	{	get_string(working_directory, S),
 1855		S \== "",
 1856		directory_files(S, Files)
 1857	},
 1858	peek(Files),
 1859	insert("\n")
 1860	;
 1861	peek("**** directory not found. ****\n").
Convert the text possibly with ligatures to the normal normal sequences of chars.
 1867handle([dakuten])--> region,
 1868					flip(string_codes),
 1869					dakuten_convert,
 1870					overwrite.
Inverse of handle([dakuten]).
 1874handle([dakuten, flip]) --> region,
 1875					flip(string_codes),
 1876					flip(dakuten_convert),
 1877					overwrite.
List files with the ligatures resolved as in handle([dakuten]).
 1881handle([list, files, dakuten])	--> % ls
 1882	{	get_string(working_directory, S),
 1883		S \== "",
 1884		directory_files(S, Files)
 1885	},
 1886	peek(Files),
 1887	maplist(string_codes),
 1888	maplist(dakuten_convert),
 1889	insert("\n")
 1890	;
 1891	peek("**** directory not found. ****\n").
List files with a regex filter.
 1896handle([list, regex])	--> region_term,
 1897	current(Regex),
 1898	{	let(Parser, pred(Regex, [X]:- phrase(w(Regex), X, []))),
 1899		get_string(working_directory, S),
 1900		S \== "",
 1901		directory_files(S, Files)
 1902	},
 1903	peek(Files),
 1904	maplist(dakuten_convert),
 1905	maplist(string_codes),
 1906	collect(Parser),
 1907	insert("\n")
 1908	;
 1909	peek("**** directory not found. ****\n").
List all of time-stamped pdf files.
 1914handle([list, timed, pdf])	--> % ls
 1915	{	get_string(working_directory, S),
 1916		S \== "",
 1917		directory_files(S, Files),
 1918		maplist(atom_codes, Files, Codes_list),
 1919		collect(time_stamped_pdf, Codes_list, Pdf_files)
 1920	},
 1921	peek(Pdf_files),
 1922	insert("\n")
 1923	;
 1924	peek("**** directory not found. ****\n").
 1925%
 1926time_stamped_pdf(Codes):- phrase(w("[0-9]+\\.pdf"), Codes, []).
Move files.
 1931handle([mv])	--> % move a file over directories
 1932	{	get_string(working_directory, S),
 1933		S\== "" ,
 1934		get_string(target_directory, T),
 1935		T\== ""
 1936	},
 1937	rename(S, T)
 1938	;
 1939	peek("**** directory not found. ****\n").
Rename a file.
 1943handle([mv, (.)]) --> % rename a file at a directory
 1944	{	get_string(working_directory, S),
 1945		S \== ""
 1946	},
 1947	rename(S, S)
 1948	;
 1949	peek("**** directory not found. ****\n").
Move files at the source directory to the target directory with renaming.
 1955handle([mv, *])	-->
 1956	{	get_string(working_directory, S),
 1957		S\== "",
 1958		get_string(target_directory, T),
 1959		T\== ""
 1960	},
 1961	region,
 1962	paragraph,
 1963	remove([]),
 1964	maplist(trim_nl_mv(S,T)),
 1965	insert("\n"),
 1966	overwrite
 1967	;
 1968	peek("**** directory not found. ****\n").
 1969
 1970% c handle([rename]) is det.
 1971%   Rename a file.
 1972
 1973handle([rename]) --> handle([mv, (.)]).
Rename multi files.
 1977handle([rename, *]) -->
 1978	{	get_string(working_directory, S),
 1979		S\==""
 1980	},
 1981	region,
 1982	paragraph,
 1983	remove([]),
 1984	maplist(trim_nl_mv(S,S)),
 1985	insert("\n"),
 1986	overwrite
 1987	;
 1988	peek("**** directory not found. ****\n").
Get working directory.
 1993handle([wd])	--> {working_directory(X, X)}, peek(X).
Change working directory.
 1997handle([wd, change])	--> { line_get(Obj),
 1998		      obj_get([line(D0)], Obj),
 1999		      atom_codes(D, D0),
 2000		      working_directory(_, D)
 2001		    }.
 2002
 2003% !! Experimental !!
 2004%	handle([doc, latex]) is det.
 2005%   under debugging.
 2006%
 2007%!  handle([doc, latex]) --> region,   % @see => C-c-ee
 2008% 	paragraph,
 2009% 	remove([]),
 2010% 	maplist(split),
 2011% 	maplist(remove([])),
 2012% 	pred(([[X, [Y|_]],[X0, Y0]]:-
 2013% 	     maplist(flip(atom_codes), X, X1),
 2014% 	     maplist(expand_file_name, X1, X2),
 2015% 	     append(X2, X0),
 2016% 	     atom_codes(Y1, Y),
 2017% 	     expand_file_name(Y1, [Y0|_]))),
 2018% 	pred(([[X, Y], Y]:-
 2019% 	    doc_latex(X, Y, [public_only(false)]))).
 2020
 2021% % 	handle([global,set,key]) is det.
 2022% %   Run global-set-key lisp command.
 2023%!  handle([global,set,key]) --> region, paragraph, maplist(split),
 2024% 	maplist(remove_comment_line),
 2025% 	remove([]),
 2026% 	maplist([[X,Y], done]
 2027% 		:- (herbrand(Y, H),
 2028% 		    elisp:global_set_key(X, H))
 2029% 	       ),
 2030% 	herbrand_opp.
Run global-unset-key Lisp command.
 2034handle([global, unset, key])	-->
 2035	region_or_line(K),
 2036	{global_unset_key(K)},
 2037	peek(`unset.`).
View the source in the current buffer as an html file generated by the pldoc library.
 2043handle([pldoc]) -->
 2044	{ Doc_html = 'TMPPLDOC.html',
 2045	  atomics_to_string(['~/public_html/', Doc_html], Local_html),
 2046	  expand_file_name(Local_html,[HTML|_]),
 2047	  lisp(list('default-directory', 'buffer-name'()), List),
 2048	  atomics_to_string(List, File_source_name),
 2049	  open(HTML, write, Out_stream),
 2050	  set_output(Out_stream),
 2051	  pldoc_html:doc_for_file(File_source_name,
 2052							  [edit(false),
 2053							  public_only(false)]),
 2054	  close(Out_stream),
 2055  	  getenv(user, User_name),
 2056	  sh(open(-a('Safari'),
 2057				"http://localhost/"
 2058				+ "~"
 2059				+ User_name
 2060			    + "/"
 2061				+ Doc_html))
 2062	}.
 2063
 2064		/***************************
 2065		*     make-reftex-label    *
 2066		***************************/
 2067
 2068tex_command(Comm, Arg)--> w(".*\\"),
 2069						  w(".*", Comm0),
 2070						  "{",
 2071						  w(".*", Arg0),
 2072						  "}",
 2073						 {	string_codes(Comm, Comm0),
 2074							string_codes(Arg, Arg0)
 2075						  }.
 2076%
 2077reftex_label_prefix("subsection", "sec").
 2078reftex_label_prefix(S, Pref):- string_length(S, L),
 2079							   (	L =< 3
 2080							   ->	Pref = S
 2081							   ;	sub_string(S, 0, 3, _, Pref)
 2082							   ).
 2083
 2084%
 2085make_reftex_label("begin", Beg, Rem,
 2086				  ["\n\\label{", Pref, ":", Rem0, "}"]):- !,
 2087		reftex_label_prefix(Beg, Pref),
 2088		trim_white(Rem0, Rem, []).
 2089make_reftex_label(Comm, Arg, _,
 2090				  ["\n\\label{", Pref, ":", Arg, "}"]):-
 2091		reftex_label_prefix(Comm, Pref).
 2092
 2093%
 2094handle([reftex, label])--> line,
 2095						tex_command(Comm, Arg),
 2096						make_reftex_label(Comm, Arg).
 2097
 2098		/*****************************************
 2099		*     helper predicates for handle/4.    *
 2100		*****************************************/
 2101
 2102%  \C-l  help  (for help)
 2103
 2104%  trim_white(+X:codes, -Y:codes) is det.
 2105%	Trim white codes from both ends of X as long as possible,
 2106%	and unify Y with the remainder of X.
 2107% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P),
 2108% ?- ejockey:trim_white(` \t/a\tb c/ \t`, P), basic:smash(P).
 2109% ?- ejockey:trim_white(`\n \t/a\tb c/ \t`, P), basic:smash(P).
 2110% ?- ejockey:trim_white(`\n \t/a\tb c/ \t\n\n`, P), basic:smash(P).
 2111% ?- ejockey:trim_white(`\n ab\n cd \nef \n\n\n`, P), basic:smash(P).
 2112trim_white --> wl("[\s\t\n]*"),
 2113			   w(".*", A),
 2114			   wl("[\s\t\n]*"),
 2115			   end_of_codes,
 2116			   peek(A).
 2117
 2118%  Qcompile: /Users/cantor/devel/zdd/prolog/util/emacs-jockey.pl
 2119%  trim_white_prefix(+X:codes, -Y:codes) is det.
 2120%	Trim white codes of the prefix of X,
 2121%	and unify Y with the remainder of X.
 2122trim_white_prefix --> wl("[\s\t]*").
 2123
 2124%  catch_once(+G:goal, +A:term, -R:term) is det.
 2125%	Unify R with A if G is true, with E if exception E is thrown
 2126%	from a child process of G, and fail if G fails.
 2127
 2128catch_once(X, A, R):- catch((once(X), R=A), E, (R = E)), !.
 2129catch_once(_, _, fail).
 2130
 2131%  line(_, -L:codes) is det.
 2132%	Get the codes of the current line with  the cursor on.
 2133line(_, Line) :- line_get(I), obj_get([line(Line)], I, _).
 2134
 2135%  partial_match(As:list, B:atom) is det.
 2136%	True if some atom in As is a prefix atom of B.
 2137
 2138% ?- ejockey:partial_match([reg, a], region).
 2139partial_match(Atoms, Fullname):-
 2140	once((
 2141	member(Shortname, Atoms),
 2142	atom(Shortname),
 2143	sub_atom(Fullname, 0, N, _, Shortname),
 2144	N>0)).
 2145
 2146% %c select_phrase(+C:cond, +P:phrase, +Q:phrase) is det.
 2147% %	Conditional phrase depending on arguments abbreviation;
 2148% %	Use default unless otherwise being specified.
 2149% select_phrase(Cond, P, _) --> {call(Cond)}, !, phrase(P).
 2150% select_phrase( _, _, Q)	  -->  phrase(Q).
 2151
 2152%  region_or_line(As:list, ?X, ?Y) is det.
 2153%	Apply region/2 or line/2 to  X, Y depending on X.
 2154
 2155region_or_line([]) --> !, region.   % region is default.
 2156region_or_line([X|_]) --> {partial_match([X], line)}, !, line.
 2157region_or_line([X|_]) --> {partial_match([X], region)}, region.
 2158
 2159%  trim_nl_mv(+S, +T, +X, -Y) is det.
 2160%	Move a file over directories.
 2161trim_nl_mv(S, T) --> trim_nl(L, R),
 2162	handle_mv(S, T),
 2163	peek(X, [L, X, R]).
 2164
 2165%  rename(S:directory, T:directory, +X:codes, -Y:codes) is det.
 2166%	Move a file over directories with specified new name.
 2167rename(S, T)-->  set_mark_region,
 2168	region,
 2169	trim_nl_mv(S, T),
 2170	overwrite.
 2171
 2172%  indent_region(+C:code, +N:int, +X, -Y) is det.
 2173%	Indent the region by padding the code C  N times.
 2174
 2175indent_region(CharCode, N) -->  region,
 2176	split,
 2177	{ 	length(Indent, N),
 2178		maplist(=(CharCode), Indent)
 2179	},
 2180	maplist(pred(Indent,
 2181		     [[], []]
 2182		    &		     [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.
 2191handle_open_relative(Line) :-
 2192		get_string(working_directory, Path),
 2193		(	Path \== ""
 2194		->	PathStr = Path
 2195		;	PathStr = ""
 2196		),
 2197		atomics_to_string([PathStr, /, Line], X),
 2198		pshell(open(X)).
 2199
 2200%  remove_comment_line(X:codes, Y:codes) is det.
 2201%	Remove the comment lines from X, and Unify Y with the
 2202%	remaining.
 2203
 2204% ?- ejockey:remove_comment_line([`%abc`, `%xyz`, `%hello`], R).
 2205remove_comment_line([],[]).
 2206remove_comment_line([[0'%|_]|R], R0):- !, remove_comment_line(R, R0). %'
 2207remove_comment_line([X|R], [X|R0]):- remove_comment_line(R, R0).
 2208
 2209%!  handle_mv(+S, +T, +X, -Y) is det.
 2210%	Move a file from directory S to T, whose source and target names
 2211%	are coded in X.
 2212
 2213handle_mv(S_dir, T_dir) -->
 2214	trim_nl(Left, Right),
 2215	pred([X, Y]:- foldr(  % : ===>  @
 2216		pred(   [0':,  U, [0'@  | U]]
 2217			&
 2218				[0'/,  U, [0'-  | U]]
 2219			&
 2220				[A,    U, [A|U]] ) ,
 2221		X, [], Y)),
 2222	mv_over_directory(S_dir, T_dir),
 2223	peek(A, [Left, A, Right]).
 2224
 2225
 2226%  A -->>  B   is a genral form of rules, tentatively called a `DCGX' (DCG extended) rule.
 2227%	Syntactically, A and B must be prolog terms such that A --> B forms a DCG rule.
 2228%	This rule is translated like a DCG rule, but into a predicate H that acts on contextual
 2229%	object of the form (X, E), which is called here a `state'.
 2230%	Procedually, H acts on states as a state transition action, so that we write
 2231%
 2232%	                H
 2233%		(X, E) ~~> (X', E')
 2234%
 2235%	for H((X, E), (X', E')).
 2236%
 2237%	Let H1, ..., Hn be actions for instances of the lefthand side of rules defined
 2238%	by '-->>' rules and (X0, E0) given an initial contextual objects. Then,  a sequence (H1,...,Hn)
 2239%	acts on a state (X0, E0) as an intial state, and then  produce a next state (X1, E1),
 2240%	and does successively so on  like this with a final state (Xn, En).
 2241%
 2242%	                 H1           H2      Hn
 2243%		(X0, E0) ~~> (X1, E1) ~~> ... ~~> (Xn, En).
 2244%
 2245
 2246%  mv_at_directory(+L:directory, +S:state, -S0:state) is det.
 2247%	Rename a file under L, whose  source and target names are
 2248%	coded in the state S.
 2249
 2250mv_at_directory(L) -->> dcl([dir(L)]),
 2251	paragraph,
 2252	remove([]),
 2253	maplist(split),
 2254	maplist(remove([])),
 2255	remove([]),
 2256	obj(obj_get([dir(F)])),
 2257	maplist(pred(F, ([[X|Y], "renamed."]:-
 2258		maplist(split(` `), Y, Y0),
 2259		maplist(remove([]), Y0, Y1),
 2260		maplist(insert("\\ "), Y1, Y2),
 2261		insert("@", Y2, Y3),
 2262		file_extension(Ext, X, _),
 2263		sh(mv(-i, F + X, F + Y3 + Ext)))
 2264		&
 2265		([P,Q]:- insert("\n", P, Q)))),
 2266	insert("\n").
 2267
 2268%   mv_over_directory(+L:directory, +M:directory, +S:state, -S0:state) is det.
 2269%   Move files over from L to M. The source and target name of a file
 2270%   are in the given state S.
 2271
 2272mv_over_directory(L, M) -->> dcl([dir(L), dir_target(M)]),
 2273	paragraph,
 2274	maplist(split),
 2275	maplist(remove([])),
 2276	remove([]),
 2277	obj(obj_get([dir(F), dir_target(G)])),
 2278	maplist(pred([F,G],
 2279			([[X|Y], "Renamed and moved."]:-
 2280				file_name(Y, Y0),
 2281				atomics_to_string([G,/, Y0], Y1),
 2282		 		file_extension(Ext, X, _),
 2283				modify_file_name(Y1, 0, Ext, Y2),
 2284				atom_codes(X0, X),
 2285				atomics_to_string([F,/, X0], X1),
 2286				rename_file(X1, Y2))
 2287			&
 2288			([P,Q]:- insert("\n", P, Q))
 2289		    )
 2290	       ),
 2291	insert("\n").
 2292
 2293%  file_name(+X:text, -Y:atom) is det.
 2294%	Concatenate a list X of blocks of codes into an atom Y
 2295%	with '@' as a block separator character.
 2296
 2297file_name --> insert(`@`), flatten, flip(string_codes).
 2298
 2299%  modify_file_name(+F:file_name, +I:integer, +E:extension, -G:File_name) is det.
 2300%	Modify the file name F to G by adding a minimum integer suffix J >= I
 2301%	to F when F conflicts with an existing one so that G does not so, otherwise,
 2302%	unify G with F.
 2303
 2304% ?- ejockey:modify_file_name('emacs-jockey', 0, '.pl', G).
 2305% ?- ejockey:modify_file_name('~/Desktop/test', 0, '.bib', G).
 2306% ?- ejockey:modify_file_name('~/Desktop/test', 1, '.bib', G).
 2307
 2308modify_file_name(F, 0, Ext, G):- !,
 2309	atomic_list_concat([F, Ext], F0),
 2310	(	exists_file(F0)
 2311	->	modify_file_name(F, 1, Ext, G)
 2312	;	G = F0
 2313	).
 2314modify_file_name(F, I, Ext, G):- atom_number(A, I),
 2315	atomic_list_concat([F, @, A, Ext], F0),
 2316	(	exists_file(F0)
 2317	->	J is I+1,
 2318		modify_file_name(F, J, Ext, G)
 2319	;	G = F0
 2320	).
 2321
 2322%  file_extension(-Ext:atom, +P:codes, -Q:codes) is det.
 2323%	Unify Ext with a file extension codes (including the '.' character) of
 2324%	P, and Q with the remainder prefix of P.  If no extension of P is found,
 2325%	unify Ext and Q with the empty atom '' and P, respective.
 2326
 2327% ?- ejockey:file_extension(X, `abc/.efg/a.b.c`, R).
 2328% ?- ejockey:file_extension(X, `abc/.efg/a.b.c/x`, R).
 2329
 2330file_extension(Ext) --> w(*(.)),  ".",  wl("[^\\./]*", X), end_of_list, !,
 2331	{ atom_codes(Ext, [0'. | X]) }.		%'
 2332file_extension('') --> [].
 2333
 2334%  insert_tab_nl(+N:int, +I:int, +T:list, -T0:list) is det.
 2335%	Insert tab codes or newline codes between each successive elements
 2336%	of T, and unify T0 with it, so that  writing all elements of the list T0
 2337%	in order shows up an array of raws of  N-elements, provided that I = N.
 2338
 2339% ?- ejockey:insert_tab_nl(3, 3, [a,b,c,d,e], R).
 2340insert_tab_nl(_, _, [], []).
 2341insert_tab_nl(N, 0, [X|Y], [[X,'\n']|Y0]):- !, insert_tab_nl(N, N, Y, Y0).
 2342insert_tab_nl(N, J, [X|Y], [[X,'\t']|Y0]):- J0 is J-1, insert_tab_nl(N, J0, Y, Y0).
 2343
 2344%  insert_nl(+X:list, -Y:list) is det.
 2345%	Shorthand for insert(`\n`, X, Y).
 2346
 2347insert_nl --> insert(`\n`).
 2348
 2349			/****************************************
 2350			*     listing tex command sequences.    *
 2351			****************************************/
 2352
 2353%  	handle([list, tex, cs]) is det.
 2354%   Listing tex command sequeces.
 2355%
 2356handle([list, tex, cs]) --> region,
 2357	texparse,
 2358	list_texcs,
 2359	sort,
 2360	insert("\n").
 2361
 2362%
 2363list_texcs_file(File, R):- read_file_to_codes(File, R0, []),
 2364	texparse(R0, R1),
 2365	list_texcs(R2, [], R1, []),
 2366	sort(R2, R).
 2367%
 2368list_texcs(X, Y):-  list_texcs(Y, [], X, []).
 2369
 2370%
 2371list_texcs([A|X], Y)	--> [cs(A)], !, list_texcs(X, Y).
 2372list_texcs([F|X], Y)	--> [env(F, B)], !,
 2373	{ list_texcs(X, X0, B, []) },
 2374	 list_texcs(X0, Y).
 2375list_texcs(X, Y)	--> [L], { listp(L) } , !,
 2376	{ list_texcs(X, X0, L, []) },
 2377	list_texcs(X0, Y).
 2378list_texcs(X, Y)	--> [_], !, list_texcs(X, Y).
 2379list_texcs(X, X)	--> [].
 2380
 2381
 2382		/************************************************
 2383		*     bi-directional converter for file name    *
 2384		%     with dakuten characters                   *
 2385		************************************************/
 2386
 2387%  dakuten_convert(?X:text, ?Y:text) is det and bi-directional.
 2388%	Replace each 'dakuten' and 'semi-dakuten' (voiced sound mark) ligature with
 2389%	the one character in utf8 encoding, and unify Y with the result so that Y is from
 2390%	from such ligatures; and vice versa. Note that copy-paste of Japanese file names
 2391%	of ligature free in Finder may yield codes that has (semi-)dakuten ligatures,
 2392%	which may cause troubles.
 2393
 2394% [2013/09, 2014/12]
 2395%  ex. "ば" <==> "ば”   (bi-directional)
 2396
 2397% ?- ejockey:dakuten_convert("プロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2398% ?- ejockey:dakuten_convert(`プロジェクト`, Y), ejockey:dakuten_convert(X, Y).
 2399% ?- ejockey:dakuten_convert('プロジェクト', Y), ejockey:dakuten_convert(X, Y).
 2400% ?- ejockey:dakuten_convert("プロジェクトプロジェクト", Y), ejockey:dakuten_convert(X, Y).
 2401% 濁点 '゙'	半濁点 '゚'
 2402
 2403dakuten_convert(X, Y):- var(Y), !,
 2404	string_chars(X, U),
 2405	once(convert_chars(U, V)),
 2406	string_chars(Y, V).
 2407dakuten_convert(X, Y):-
 2408	string_chars(Y, V),
 2409	once(convert_chars(U, V)),
 2410	string_chars(X, U).
 2411
 2412convert_chars([], []).
 2413convert_chars([X, Y|R], [Z|S]):- conversion_table(Y, D, E),
 2414	chars_table_check(X, D, E, Z),
 2415	convert_chars(R, S).
 2416convert_chars([X|R], [X|S]):- convert_chars(R, S).
 2417
 2418%
 2419chars_table_check(X, [X|_], [Z|_], Z).
 2420chars_table_check(X, [_|U], [_|V], Z):- chars_table_check(X, U, V, Z).
 2421
 2422% conversion_table(a, X, Y) means that  ba <==> c  for each b in X and c in Y.
 2423conversion_table('゙',
 2424		['か', 'き', 'く', 'け', 'こ',
 2425		 'さ', 'し', 'す', 'せ', 'そ',
 2426		 'た', 'ち', 'つ', 'て', 'と',
 2427		 'は', 'ひ', 'ふ', 'へ', 'ほ'],
 2428		['が', 'ぎ', 'ぐ', 'げ', 'ご',
 2429		 'ざ', 'じ', 'ず', 'ぜ', 'ぞ',
 2430		 'だ', 'ぢ', 'づ', 'で', 'ど',
 2431		 'ば', 'び', 'ぶ', 'べ', 'ぼ']).
 2432conversion_table('゙',
 2433		['ウ',
 2434		 'カ', 'キ', 'ク', 'ケ', 'コ',
 2435		 'サ', 'シ', 'ス', 'セ', 'ソ',
 2436		 'タ', 'チ', 'ツ', 'テ', 'ト',
 2437		 'ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2438		['ヴ',
 2439		 'ガ', 'ギ', 'グ', 'ゲ', 'ゴ',
 2440		 'ザ', 'ジ', 'ズ', 'ゼ', 'ゾ',
 2441		 'ダ', 'ヂ', 'ヅ', 'デ', 'ド',
 2442		 'バ', 'ビ', 'ブ', 'ベ', 'ボ']).
 2443conversion_table('゚',
 2444		['は', 'ひ', 'ふ', 'へ', 'ほ'],
 2445		['ぱ', 'ぴ', 'ぷ', 'ぺ', 'ぽ`']).
 2446conversion_table('゚',
 2447		['ハ', 'ヒ', 'フ', 'ヘ', 'ホ'],
 2448		['パ', 'ピ', 'プ', 'ペ', 'ポ']
 2449	      ).
 2450
 2451
 2452
 2453%  trim_nl(-L:codes, -R:codes, +X:codes, -Y:codes) is det.
 2454%	Trim successive new line codes from both ends of X  as long as possible,
 2455%	and unify Y with the remainder of X.
 2456
 2457% ?-ejockey:trim_nl(L, R, `abc`, Y).
 2458% ?-ejockey:trim_nl(L, R, `\n\n\n`, Y).
 2459% ?-ejockey:trim_nl(L, R, `\nabc\n`, Y).
 2460% ?-ejockey:trim_nl(L, R, `\n\nabc\n\n`, Y).
 2461% ?-ejockey:trim_nl(L, R, `\n\n向井\n国昭\nabc\n\n`, Y).
 2462
 2463%
 2464trim_nl(L, R) --> wl(*("\n"), L),
 2465	w(*(.), Y),
 2466	wl(*("\n"), R),
 2467	end_of_list,
 2468	peek(Y).
 2469
 2470%
 2471end_of_list([], []).
 2472
 2473%  meta_handle(?X, -Y) is det.
 2474%	Parse the first line of the region for a handle command,
 2475%	and apply the command to the rest of the region.
 2476
 2477meta_handle --> region,
 2478	w("[^\n]*$", L),
 2479	{ parse_line(X, L, []),
 2480	  maplist(atom_codes, A, X)
 2481	},
 2482	pred([A, L], [U, V]:-
 2483		once(find_handle_call(A, L, U, V))).
 2484
 2485%  parse_line(+X:list, +Y:codes, -Z:codes) is det.
 2486%	Unify X with a list of (S-expression) tokens that
 2487%	appears in the deference between Y and Z.
 2488
 2489% ?- ejockey:parse_line(X, `a b c`, []).
 2490% ?- ejockey:parse_line(X, `a "b c""d e"`, []).
 2491% ?- ejockey:parse_line(X, `a "b c"'d \\"e'`, []).
 2492% ?- ejockey:parse_line(X, `'d\\e'`, []).
 2493% ?- ejockey:parse_line(X, `'d\e'`, []).
 2494% ?- ejockey:parse_line(X, `'d\\\\e'`, []).
 2495% ?- ejockey:parse_line(X, `"d\\\\\e"`, []).
 2496% ?- ejockey:parse_line(X, `"a"`, []).
 2497
 2498parse_line(X) --> wl("[\s\t]*"), parse_line0(X).
 2499
 2500parse_line0([A|X]) --> token(A), !, parse_line(X).
 2501parse_line0([]) --> [].
 2502
 2503
 2504% ?-coalgebra:show_am("\"([^\"\\\\]|(\\\\.))*\"" | "'([^'\\\\]|(\\\\.))*'" | "[^ \t\"']+").
 2505
 2506
 2507%  token(-X:token, +Y:codes, -Z:codes) is det.
 2508%	Unify X with a token in S-expression for the difference betwee Y and Z.
 2509
 2510% ?- ejockey:token(X, `abcd  `, Y).
 2511% ?- ejockey:token(X, `"ab\\\"d"`, Y), smash(X).
 2512%@ "ab\"d"
 2513% ?- ejockey:token(X, `"ab\\\"c\\\"d"`, Y), smash(X).
 2514%@ "ab\"c\"d"
 2515
 2516token(X) --> wl( "\"([^\"\\\\]|(\\\\.))*\""
 2517	       | "'([^'\\\\]|(\\\\.))*'"
 2518	       | "[^\s\t\"']+",
 2519		X).
 2520
 2521%  prolog_identifier(N:, X:codes, Y:codes) is det.
 2522%	Unify N with a list of codes
 2523%	such that N is the longest prolog_identifier prefix of X,
 2524%	and Y with the remaining suffix of X.
 2525%
 2526
 2527prolog_identifier(N) --> wl("[a-z][a-zA-Z0-9_]*", N, []).
 2528
 2529%  keyword(N:, X:codes, Y:codes) is det.
 2530%	Unify N with a list of codes
 2531%	such that N is the longest keyword prefix of X,
 2532%	and Y with the remaining suffix of X.
 2533%
 2534
 2535keyword(N) --> wl("[a-zA-Z][a-zA-Z0-9_]*", N, []).
 2536
 2537%  collect_tokens(+W:type, +X:codes, -Y:tokens) is det.
 2538%	Collect tokens in X that satisfies W, and
 2539%	unify Y with it.
 2540
 2541collect_tokens(W, X, Y):- collect_tokens(W, Y, [], X, []).
 2542
 2543%
 2544collect_tokens(W, X, Y) --> [_], collect_tokens(W, X, Y).
 2545collect_tokens(_, X, X)-->[].
 2546
 2547% % [2013/10/07] To escape special characters of the file name
 2548% % in order to pass it to sh/1.
 2549% % ?- ejockey:escape_shell_char(`a : (b)`, R), atom_codes(A, R).
 2550% %@ A = 'a \\@ \\(b\\)' .
 2551
 2552escape_shell_char(X, Y):-
 2553  foldr(pred(	[0'(,  U, [0'\\,    0'(  | U]	] &		%'
 2554		[0'),  U, [0'\\,    0')  | U]	] &
 2555		[0'\', U, [0'\\,    0'\' | U]	] &
 2556		[0':,  U, [0'\\,    0'@  | U]	] &
 2557		[0'/,  U, [0'\\,    0'@  | U]	] &
 2558		[A,    U, [A|U]			]
 2559	    ),
 2560	X, [], Y).
 2561
 2562% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X).
 2563
 2564% ?- ejockey:remove_leading_comment_chars(`% %@ ?- a, \n %  b.\n`, X),
 2565%	basic:smash(X).
 2566
 2567remove_leading_comment_chars(X, Y) :-
 2568	remove_leading_comment_chars(Y, [], X, []).
 2569%
 2570remove_leading_comment_chars(X, Y) -->
 2571	wl("([% \t]|(%@*)|(\\?-))*"),
 2572	wl("[^\n]*", X, X0),
 2573	remove_leading_comment_chars_continue(X0, Y).
 2574%
 2575remove_leading_comment_chars_continue([0'\n|X], Y) --> "\n",  %' %
 2576	remove_leading_comment_chars(X, Y).
 2577remove_leading_comment_chars_continue(X, X) --> [].
 2578
 2579% ?- comment(X, [], `/* abc   \ndef */xyz`, R), smash(X), nl, smash(R).
 2580%@ /* abc   def */
 2581%@ xyz
 2582
 2583comment --> w(@comment).
 2584%
 2585comment(X, Y)-->w(@comment, X, Y).
 2586%
 2587uncomment --> wl("%+ ?"|[]).
 2588
 2589module_name(Codes, Name):- once(module_name(Name, Codes, _)).
 2590%
 2591module_name(Name) --> wl("[\s\t]*:-[\s\t]*"),
 2592		      "module(",
 2593		      wl("[^,\s\t]+", Name).
 2594module_name(????) --> [].
 2595
 2596%
 2597white_filler --> wl("[\s\t\n]*").
 2598%
 2599non_white_line(X):- \+ white_filler(X, []).
 2600
 2601% ?- C = `ab cd`, ejockey:to_ascii_space(`ab cd`, R).
 2602%@ C = [97, 98, 12288, 99, 100],
 2603%@ R = [97, 98, 32, 99, 100].
 2604
 2605to_ascii_space(X, Y) :- once(to_ascii_space(Y, [], X, [])).
 2606
 2607to_ascii_space([0'\s|X], Y) --> " ", to_ascii_space(X, Y).  % '
 2608to_ascii_space([C|X], Y)--> [C], to_ascii_space(X, Y).
 2609to_ascii_space(X, X)--> []