1:- module(html, [quote/2, tag/3,tag_nl/3, html/4, html/5,
    2				 query_ans_html/2, query_ans_html/3, query_ans_html/4,
    3				 double_quote/2]).    4
    5:- use_module(util(misc)).    6:- use_module(pac(basic)).    7:- use_module(pac('expand-pac')).    8:- use_module(pac('expand-etc')).    9:- use_module(pac(op)).   10:- use_module(util(obj)).   11:- use_module(util(misc)).   12:- use_module(util('emacs-handler')).   13
   14term_expansion --> pac:expand_pac.
   15
   16:- encoding(utf8).
   17:- set_prolog_flag(allow_variable_name_as_functor, true).
Apply phrase A to X to get Y, and, by getting the buffer information, write the result Y to the buffer file F, and open F.
   23buffer_html(A, X, F) :- phrase(A, X, Y),
   24	get_buffer_info_codes(L),
   25 	obj_get([buffer(N), dir(D)], L, _),
   26	map_path_html(D, N, F),
   27  	html_write_me(F, Y),
   28  	html_open(F).
 get_buffer_info_codes(-X:obj) is det
Get the buffer info in codes, and unify X with it.
   33% ?- html:get_buffer_info_codes(X).
   34
   35get_buffer_info_codes([buffer(N), dir(D), whoami(U), hostname(H)]):-
   36	elisp:current_buffer_name(N),
   37 	elisp:default_directory(D),
   38 	getinfo_codes(whoami, U),
   39 	getinfo_codes(hostname, H).
 get_buffer_info(-X:obj) is det
Get the buffer info, and unify X with it.
   44% ?- html:get_buffer_info(X).
   45
   46get_buffer_info([buffer(N), dir(D), whoami(U), hostname(H)]):-
   47	elisp:cur_buf(N),
   48 	elisp:cur_dir(D),
   49 	getinfo(whoami, U),
   50 	getinfo(hostname, H).
   51
   52%
   53html(F, Top) --> region, html_export(F, Top).
   54
   55html_export(F, Top) --> paragraph,
   56	remove([]),
   57	phrase(Top),
   58	html_write_me(F),
   59	html_open(F),
   60	clear.
   61
   62html(F, Top, Sub) --> region,
   63	paragraph,
   64	maplist(phrase(Sub)),
   65	act(Top),
   66	html_write_me(F),
   67	html_open(F),
   68	clear.
   69
   70tex2html(env(N, Body),
   71	["<", N, ">" , Body1, "</", N, ">"],
   72	[Body],  [Body1], true).
   73tex2html(X, X, [], [], true).
   74
   75% [2009/10/18]
   76% # question_button_list([list_type(ul), label(`ここを押せ`)]), browse, clear
   77% $a+b+c+d$の値は
   78% $a+b+c$と$d$の和である.
   79question_button_list(L) --> obj_init(L), question_button_list.
   80
   81question_button_list -->
   82	obj_merge([label("==&gt;"),
   83		   list_type(ol),
   84		   mid_symbol_codes("==>"),
   85		   file_name(test('deldel.html'))
   86		  ]),
   87	obj_get([list_type(O)]),
   88	current(Env),
   89	obj_act((split,
   90		maplist(remove(0'\n)),   %'
   91		remove([]),
   92		sed(question_button_list_item(Env)),
   93		tag(O))).
   94
   95question_button_list_item(E, QA) --> [Line],
   96	{
   97	 obj_get([label(L),  mid_symbol_codes(M)], E),
   98	 append([X, M, Y], Line),
   99	 mimetex_question_button([question(X), button(Y), label(L)], Z),
  100	 obj_get([acc(Z0)], Z),
  101	 tag(li, Z0, QA)
  102	}.
  103
  104prolog_answer_button(E, ["\n", QA]) --> [Line],
  105	{ text_parse_solve(Line, Y),
  106	  quote(Y, Y0),
  107	  obj_get([label(Label)], E),
  108	  quote(Label, Label0),
  109	  LI = ["?- ", Line, ".  ",
  110		     "<script>ans(",
  111		      Y0,
  112		      "," ,
  113		      Label0,
  114		      ");</script>"],
  115	 obj_put([acc(LI)], E, _E),
  116	 tag(li, LI, QA)
  117	}.
  118
  119% all solved forms html.
  120text_parse_solve(X, Y):-
  121	( catch(herbrand(V, X, G), _, fail) ->  findall(V, call(G), Y0)
  122	; Y0= "Syntax Error"
  123	),
  124	solved_form_html(Y0, Y).
  125
  126solved_form_html([], "false"):-!.
  127solved_form_html([[]|_], "true"):-!.
  128solved_form_html(X, [X]):- atom(X), !.
  129solved_form_html(X, Y):-  % do not add `\n` after <br>
  130        maplist(maplist(herbrand_opp), X, S1),
  131	maplist(insert("<br>"), S1, S2),
  132	insert(" ;<br><br>", S2, S3),
  133	flatten(["<br>", S3], Y).
  134
  135% ?- html:parse_mimetex((`$a$`, [mimetex_name(fff)]), (Y, _)),  smash(Y).
  136%@ <script>fff(`a`);</script>
  137
  138parse_mimetex((X,E),(Y,E)):- parse_mimetex(E, X, Y).
  139
  140% ?- html:parse_mimetex_qa([], `$a$ ==> $b$`, R), smash(R).
  141% ?- html:parse_mimetex_qa([], `$a$ ==> $\\b$`, R), basic:smash(R).
  142
  143parse_mimetex(E, X, Y) :- obj_put([acc(X)], E, E0),
  144	mimetex(E0, E1),
  145	obj_get([acc(Y)], E1).
  146
  147% ?- html:at_or_qa([], `$a$ ==> $b$`, R), smash(R).
  148%@ <li>$a$<script>ans("$b$","==&gt;");</script></li>
  149
  150at_or_qa(_, [0'@ |X], [X, "\n"]):- !.	%'
  151at_or_qa(E, X, Y):-   parse_mimetex_qa(E, X, Y0),
  152	tag_nl(li, Y0, Y).
  153
  154
  155parse_mimetex_qa(E, X, Y) :- once(parse_qa_line(Q, A, X, [])),
  156	obj_put([question(Q), button(A)], E, E0),
  157	mimetex_question_button(E0, E1),
  158	!,
  159	obj_get([acc(Y)], E1).
  160
  161% ?- html:parse_qa_line(Q, A, `  a  ==>  b  `, []).
  162parse_qa_line(Q, A) --> wl("[ \t]*"),
  163	w(".*", Q),
  164	wl("[ \t]*==>[ \t]*"),
  165	w(".*", A),
  166	w("[ \t]*$").
  167
  168%
  169boole_qa(E, [Q, A], Y) :-
  170	atom_codes(A, A0),
  171	atomic_list_concat([$, Q, $], Q0),
  172	atom_codes(Q0, Q1),
  173 	obj_put([question(Q1), button(A0)], E, E0),
  174	mimetex_question_button(E0, E1),
  175	!,
  176	obj_get([acc(Y)], E1).
  177
  178%
  179dummy_qa(_, [_, _], "Hello world").
  180
  181
  182% ?- html:mimetex_question_button([question(`a$\\pi$`), button(`x$\\sigma$`)], X), obj_get([acc(V)], X), smash(V).
  183
  184mimetex_question_button -->
  185	obj_get([question(X)]),
  186	obj_put([acc(X)]),
  187	mimetex_question,
  188	obj_get([acc(X0)]),
  189	obj_get([button(Y)]),
  190	obj_put([acc(Y)]),
  191	mimetex_button,
  192	obj_get([acc(Y0)]),
  193	obj_put([acc([X0, Y0])]).
  194
  195% ?- html:mimetex([acc(`a $b+c$ `)], X), smash(X).
  196mimetex_question(X, X).
  197
  198%
  199mimetex --> obj_merge([mimetex_name(mimetex), insert([])]),
  200	obj_get([mimetex_name(N), insert(Insert)]),
  201	obj_act(html:mimetex(N, Insert)).
  202
  203%
  204mimetex(N, Insert) --> mime_parse_me,
  205	flatten,
  206	maplist(mimetex_(N, Insert)).
  207
  208%
  209mimetex_(N, Insert)--> peek(dol(X), [Insert, X]), !,
  210	tex_quote,
  211	peek(Y, ["<script>", N, "(", Y, ");</script>"]).
  212mimetex_(N, Insert)--> peek(ddol(X), [Insert, X]), !,
  213	tex_quote,
  214	peek(Y, ["<center><script>", N, "(", Y, "); </script></center>"]).
  215mimetex_(_, _) --> [].
  216
  217%
  218tex_quote --> tex_codes, flatten, quote.
  219
  220% ?- html:mimetex_button([acc(`a`)], R), obj_get([acc(V)], R), smash(V).
  221mimetex_button --> obj_merge([label("==&gt;"),
  222      			      parse(html:parse_mimetex_quote),
  223			      ans(ans)]),
  224	obj_get([label(Label),  ans(A),  parse(P)]),
  225	obj_act(P),
  226	obj_get([acc(X)]),
  227	{quote(X, X0)},
  228	{quote(Label, Label0)},
  229	obj_put([acc(["<script>", A, "(", X0, "," , Label0,  ");</script>"])]).
  230
  231% ?- html:parse_mimetex_quote(f, `$a$ and b`, X), smash(X).
  232% ?- html:parse_mimetex_quote(f, `$a+\\emptyset$`, X), smash(X).
  233parse_mimetex_quote --> parse_mimetex_quote(mimetexcode).
  234
  235%
  236parse_mimetex_quote(_,X,X).
  237
  238%
  239join_neighbor_codes([], []).
  240join_neighbor_codes([X|Y], R):- join_neighbor_codes(Y, R0),
  241	join_neighbor_codes(X, R0, R).
  242
  243join_neighbor_codes(dol(X), Y, [dol(X)|Y]):- !.
  244join_neighbor_codes(ddol(X), Y, [ddol(X)|Y]):- !.
  245join_neighbor_codes(X, [], [[X]]):- !.
  246join_neighbor_codes(X, [L|R], [[X|L]|R]):- listp(L), !.
  247join_neighbor_codes(X, Y, [[X]|Y]).
  248
  249% [2010/11/03]
  250% ?- html:mimetex_onclick(`a$\\sigma$b`, X), smash(X).
  251% ?- html:mimetex_onclick(`a$\\sigma$b`, X), quote(X, Y), smash(Y).
  252mimetex_onclick --> mime_js, js_plus, quote.
  253
  254mime_js --> texparse, flatten, split_mime, maplist(js_func_call).
  255
  256%
  257split_mime([], [[]]):- !.
  258split_mime([X|R], [[X|Y]|M]):-  integer(X), !, split_mime(R, [Y|M]).
  259split_mime([X|R], [[],X|S]):- split_mime(R, S).
  260
  261%
  262js_func_call(dol(X), dol(Y)):- !, tex_js(X, Y).
  263js_func_call(ddol(X), ddol(Y)):- !, tex_js(X, Y).
  264js_func_call(X, just(Y)):- flatten(X, X0), quote(X0, Y).
  265
  266% tex_js --> tex_codes, flatten, quote.
  267
  268% js_plus(X, Y):- maplist(smash_functor, X, X0),
  269% 	insert("+", X0, X1),
  270% 	flatten(X1, Y).
  271
  272% smash_functor(X, [F,"(", A, ")"]):- X=..[F|A].
  273
  274% % ?- html:quote_math(f, dol(`abc`), X), smash(X).
  275% %@ f("abc")
  276% quote_math(N, dol(X), Y):- !, tex_codes(X, X0), flatten(X0, X1),
  277% 	quote(X1, X2),
  278% 	Y = [N, "(", X2, ")"].
  279% quote_math(N, ddol(X), Y):- !, tex_codes(X, X0), flatten(X0, X1),
  280% 	quote(X1, X2),
  281% 	Y=["\"<center>\"+", N, "(", X2, ")+\"</center>\""].
  282% quote_math(_, X, Y):- flatten(X, X0), quote(X0, Y).
  283
  284% %%%% Simple quoting
  285% % ?- quote(`\\\`abc`, X), smash(X).
  286% % ?- html:single_quote(`\\\`abc`, X), smash(X).
  287
  288% quote --> double_quote.
  289
  290% % ?- html:double_quote(`abc`, X), smash(X).
  291% % ?- html:double_quote(`abc`, X), atom_codes(X0, X).
  292% double_quote(X, [0'\"|X0]):- escape(0'\", X, X0, [0'\"]).
  293
  294% single_quote(X, [0'\'|X0]):- escape(0'\', X, X0, [0'\']).
  295
  296% % ?- html:back_quote(`a\`bc`, R), smash(R).
  297% %@ `a\`bc`
  298% back_quote(X, [0'\`|X0]):- escape(0'\`, X, X0, [0'\`]).
  299
  300% % ?- html:escape(0'", `"ab"`, X, []), smash(X).
  301% %@ \"ab\"
  302% %@ X = [92, 34, 97, 98, 92, 34].
  303
  304% escape(X, Y) --> escape_quasi_string(Y, X), !.
  305
  306
  307% escape_quasi_string([], _)	--> [].
  308% escape_quasi_string([A|B], M)	-->
  309% 	escape_quasi_string(A, M),
  310% 	escape_quasi_string(B, M).
  311% escape_quasi_string(S,    M) --> { string(S), string_codes(S, S0)}, !,
  312% 	escape_quasi_string(S0, M).
  313% escape_quasi_string(S,    M) --> { atom(S), atom_codes(S, S0)}, !,
  314% 	escape_quasi_string(S0, M).
  315% escape_quasi_string(M,    M, [0'\\ , M    | X],	X).
  316% escape_quasi_string(0'\\, _, [0'\\ , 0'\\ | X],	X).
  317% escape_quasi_string(0'\n, _, [0'\\ , 0'n  | X],	X).
  318% escape_quasi_string(0'\t, _, [0'\\ , 0't  | X],	X).
  319% escape_quasi_string(C,    _, [C           | X], X).
  320
  321
  322
  323			/****************************
  324			*	simple escape       *
  325			****************************/
  326
  327% ?- html:escape(`abc`, X, []), atom_codes(X0, X).
  328% ?- html:escape(``, X, []), atom_codes(X0, X).
  329% ?- html:escape(`\n`, X, []), atom_codes(X0, X).
  330% ?- html:escape(`\\\n`, X, []), atom_codes(X0, X), writeln(X0).
  331% ?- html:escape(`\\\s`, X, []), atom_codes(X0, X), writeln(X0).
  332
  333% escape([], X, X) :- !.
  334% escape([0'\\ |R], [0'\\ , 0'\\ |X], Y):- !, escape(R, X, Y).
  335% escape([[A|B]|R])	--> !, escape(A), escape(B), escape(R).
  336% escape([C|R], [C|X], Y) :- escape(R, X, Y).
  337
  338% ?- html:mime_parse_me(`$a$+$b$`, R).
  339% R = [dol([97]),43,dol([98])].
  340
  341mime_parse_me(X,Y):- mime_parse_me(Y,X,[]), !.
  342
  343mime_parse_me([]) --> [].
  344mime_parse_me([Y|Z]) --> tex:tex_math(X,[]), {tex_env(X,[Y])}, mime_parse_me(Z).
  345mime_parse_me([A|X]) --> [A], mime_parse_me(X).
  346
  347		/************************
  348		*     open HTML page    *
  349		************************/
  350
  351oh --> region, {open_current_html}, clear.
  352
  353open_current_html :-
  354	get_html_buffer_info(L),
  355	open_current_html(L).
  356
  357open_current_html(L) :-
  358	obj_get([buffer(N), path_html(P), whoami(U), hostname(H)], L, _),
  359	sh(open("http://"+ H+ "/~"+ U+ "/"+ P+ N)).
  360
  361get_html_buffer_info(L):- get_buffer_info_codes(L0),
  362	obj_get([dir(D)], L0, _),
  363	once(local_apache_path(D, P)),
  364	obj_push([path_html(P)], L0, L).
  365%
  366local_apache_path -->
  367	{	getenv(home, H),
  368		atomics_to_string([H, public_html], /, P),
  369		atom_codes(P, PCodes)
  370	},
  371	residue(PCodes),
  372	!.
  373local_apache_path -->
  374    {	elisp:message(
  375		[	"fDCG: Current directory",
  376			"is not under 'Sites' directory."
  377		])
  378    }.
  379
  380%
  381tex_js --> tex_codes, flatten, quote.
  382
  383%
  384js_plus(X, Y):- maplist(smash_functor, X, X0),
  385	insert("+", X0, X1),
  386	flatten(X1, Y).
  387
  388smash_functor(X, [F,"(", A, ")"]):- X=..[F|A].
  389
  390% ?- html:quote_math(f, dol(`abc`), X), smash(X).
  391
  392quote_math(N, dol(X), Y):- !, tex_codes(X, X0), flatten(X0, X1),
  393	quote(X1, X2),
  394	Y = [N, "(", X2, ")"].
  395quote_math(N, ddol(X), Y):- !, tex_codes(X, X0), flatten(X0, X1),
  396	quote(X1, X2),
  397	Y=["\"<center>\"+", N, "(", X2, ")+\"</center>\""].
  398quote_math(_, X, Y):- flatten(X, X0), quote(X0, Y).
  399
  400%%%% Simple quoting
  401% ?- quote(`\\\`abc`, X), smash(X).
  402%@ "\\`abc"
  403%@ X = [34, 92, 92, 96, 97, 98, 99, 34].
  404% ?- quote(`\\\`abc`, X), smash(X).
  405%@ `\\\`abc`
  406%@ X = [34,92,92,92,34,97,98,99,34].
  407% ?- html:single_quote(`\\\`abc`, X), smash(X).
  408%@ '\\`abc'
  409%@ X = [39,92,92,34,97,98,99,39].
  410
  411quote --> double_quote.
  412
  413% ?- html:double_quote(`abc`, X), smash(X).
  414% ?- html:double_quote(`abc`, X), atom_codes(X0, X).
  415
  416double_quote(X, [0'\"|X0]):- escape(0'\", X, X0, [0'\"]). %'
  417
  418single_quote(X, [0'\'|X0]):- escape(0'\', X, X0, [0'\']).
  419
  420% ?- html:back_quote(`a\`bc`, R), smash(R). %'
  421%@ `a\`bc`
  422back_quote(X, [0'\`|X0]):- escape(0'\`, X, X0, [0'\`]).  %'
  423
  424% ?- html:escape(0'", `"ab"`, X, []), smash(X).
  425%@ \"ab\"
  426
  427escape(X, Y) --> escape_quasi_string(Y, X), !.
  428
  429%
  430escape_quasi_string([A|B], M)	-->
  431	escape_quasi_string(A, M),
  432	escape_quasi_string(B, M).
  433escape_quasi_string([], _)	--> [].
  434escape_quasi_string(S,    M) --> { string(S), string_codes(S, S0)},
  435	escape_quasi_string(S0, M).
  436escape_quasi_string(S,    M) --> { atom(S), atom_codes(S, S0)},
  437	escape_quasi_string(S0, M).
  438escape_quasi_string(M,    M, [0'\\ , M    | X],	X).		%'
  439escape_quasi_string(0'\\, _, [0'\\ , 0'\\ | X],	X).		%'
  440escape_quasi_string(0'\n, _, [0'\\ , 0'n  | X],	X).		%'
  441escape_quasi_string(0'\t, _, [0'\\ , 0't  | X],	X).		%'
  442escape_quasi_string(0'\s, _, [0'\\ , 0'\s | X],X).		%'
  443escape_quasi_string(C,    _, [C           | X], X).		%'
  444
  445
  446			/****************************
  447			*	simple escape       *
  448			****************************/
  449
  450% ?- html:escape(`abc`, X, []), atom_codes(X0, X).
  451% ?- html:escape(``, X, []), atom_codes(X0, X).
  452% ?- html:escape(`\n`, X, []), atom_codes(X0, X).
  453% ?- html:escape(`\\\n`, X, []), atom_codes(X0, X), writeln(X0).
  454% ?- html:escape(`\\\s`, X, []), atom_codes(X0, X), writeln(X0).
  455
  456escape([], X, X) :- !.
  457escape([0'\\ |R], [0'\\ , 0'\\ |X], Y):- !, escape(R, X, Y).
  458escape([[A|B]|R])	--> !, escape(A), escape(B), escape(R).  %'
  459escape([C|R], [C|X], Y) :- escape(R, X, Y).
  460
  461
  462%?- html:drop_angle_suffix(`abc`, X).
  463%?- html:drop_angle_suffix(`abc<2>`, X).
  464
  465drop_angle_suffix([], []):-!.
  466drop_angle_suffix([0'<|_], []):-!.  % ' drop <...>
  467drop_angle_suffix([X|Y], [X|Z]):- drop_angle_suffix(Y,Z).
  468
  469%
  470html_list(F) --> region, paragraph, remove([]), maplist(F), overwrite.
  471
  472		/************************************************
  473		*     create query & answers table html page    *
  474		************************************************/
  475
  476html_qa(M) --> query_ans_html(M).
  477html_qa(M, Tag) --> query_ans_html(M, Tag).
  478
  479mimetex_qa(Label) --> drill(Label).
  480%
  481query_ans_html	-->	query_ans_html(pac:eval).
  482%
  483query_ans_html(S) -->
  484	{	getenv(home_html_root, H0),
  485		concat_atom([H0, '/sample'], Dir0),
  486		getenv(host_html_root, H1),
  487		concat_atom([H1, '/sample'], Dir1)
  488	},
  489	query_ans_html(S, ol),
  490	current(SOL),
  491	obj_put([directory(Dir0),
  492		 counter_name(sample_counter)]),
  493	phrase((eh:counter(update), obj_get([count(C)]))),
  494	initLoad_must_exist,
  495	{ atomics_to_string([Dir0, /, sample, C, '.html'], F0),
  496	  html_write_me(F0, SOL),
  497	  atomics_to_string([Dir1, /, sample, C, '.html'], F1)
  498	},
  499	peek([	"<a href=\"", F1, "\">",
  500			"Click this to display the generated page</a>"]),
  501	term_smash0.
  502%
  503query_ans_html(M, Tag) -->  query_ans_html_body(M), tag(Tag).
  504%
  505query_ans_html(File, M, Tag)--> region,
  506				query_ans_html_export(File, M, Tag).
  507%
  508query_ans_html_export(File, M, Tag) -->
  509	query_ans_html(M, Tag),
  510	html_write_me(File),
  511	html_open(File),
  512	clear.
  513
  514initLoad_must_exist --> obj_get([directory(D)]),
  515	{ working_directory(Old, D),
  516		(	exists_file('initLoad.js') -> true
  517		; 	getenv(exercise_js_name, P),
  518			atomics_to_string(['../../cgi-bin', P], /, P0),
  519			pshell(ln(-fs, P0, 'initLoad.js'))
  520    	),
  521   	  working_directory(_, Old)
  522	}.
  523
  524% ?- html:query_ans_html(pac:eval, ol, `(:id)@(3)`, X), basic:smash(X).
  525%@ <ol><li>(:id)@(3)<script>ans("3");</script></li>
  526%@ </ol>
  527%@ X = ["<", ol, ">", [["<li>", [40, 58|...], "<script>", [...|...]|...]],
  528% "</", ol, ">"] .
  529
  530query_ans_html_body(M) --> split, remove([]),
  531		maplist(html_li(M)).
  532
  533html_li(M, X, Y):- catch(html_li_(M, X, Y),  _,
  534			 (Y = [" <li> ", X, " ==> Error !  </li>"])).
  535
  536%
  537html_li_(M) --> current(X), parse_run(M), html_li(X, ans).
  538
  539html_li(X, J) --> { atom_codes(J, J0) },
  540	smash_codes,
  541	qstring,
  542    peek(Y, ["<li>", X, "<script>", J0, "(", Y, ");</script></li>\n"]).
  543
  544% ?- listing(qstring).
  545
  546% ?- html:parse_run(pac:eval, `:(=(a))`, R).
  547% ?- html:parse_run(pac:eval, `(X\\X)@ quote(a)`, R).
  548% ?- herbrand_in_context(`:(=(a))`, H), nopac(pac:eval(H, R)).
  549
  550% (setq module-query  "qcompile(util(html)), module(html).")
  551% ?- qcompile(util(html)), module(html).
  552% ?- parse_run(pac:eval, `:(=(a))`, R), smash(R).
  553
  554% ?- qcompile(util(html)), module(html).
  555% ?- eval_string(":(=(a))").
  556% ?- eval_string("append@[a,b]@[c,d]").
  557% ?- eval_string(":append@[a,b]@[c,d]").
  558% ?- eval_string("pred([X,Y,Z]:-append(Y,X,Z))@[1,2,3]@[a,b,c]").
  559% ?- eval_string(":pred([X,Y,Z]:-append(Y,X,Z))@[1,2,3]@[a,b,c]").
  560% ?- eval_string("(#([X,Y]\\ append(Y,X)))@[1,2,3]@[a,b,c]").
  561% ?- eval_string(":fun([X,Y] >> append(Y,X))@[1,2,3]@[a,b,c]").
  562% ?- eval_string("append @ append([1,2],[3,4])@ append([a,b], [c,d])").
  563% ?- eval_string(":append @ :append([1,2],[3,4])@ :append([a,b], [c,d])").
  564% ?- eval_string("pred([X, X])@5").
  565% ?- eval_string(":pred([X, X])@5").
  566% ?- eval_string("maplist @ fun([X]>>(append(X)@ append([a],[b]))) @ [[1,2],[3,4]]").
  567% ?- eval_string(":maplist @ fun([X]>>(:append(X)@ :append([a],[b]))) @ [[1,2],[3,4]]").
  568%@ [[1,2,a,b],[3,4,a,b]]
  569
  570eval_string(X):- string_codes(X, S),
  571	parse_run(pac:eval, S, U),
  572	smash(U).
  573
  574parse_run(M) --> herbrand_in_context,
  575	call(M),
  576	herbrand_opp.
  577
  578html_result(value(X), Y) :- !, numbervars(X, 0, _),
  579	with_output_to(codes(Y), print(X)).
  580html_result(L, Y) :- solutions_codes(L, Y).
  581
  582%
  583solutions_codes([], "false"):-!.
  584solutions_codes([[]|_], "true"):-!.
  585solutions_codes --> maplist(herbrand_opp), insert("<br>\n").
  586
  587%
  588html_table  --> region, matrix:html_table.
  589
  590html_table_th  --> region, matrix:html_table_th.
  591
  592html_table_var --> region, matrix:html_table_.
  593
  594%%%%  handling html files
 browse(+P:obj, -Q:obj) is det
The object P is supposed to contain [file_name(FN), acc(X)] then write the html data X to the file FN, and open it with the local web server. Q extends P so as to contain [anchor_tag_codes(A)], where A is the codes of html anchor-tag to the written html file for X.
  604browse --> obj_get([file_name(FN), acc(X)]),
  605	{ expand_file_search_path(html(FN), Posix) },
  606	obj_act(file_name, anchor_tag_codes, html:anchor_tag),
  607	{ html_write_me(Posix, X), html_open(FN) }.
  608
  609%	html_write_me(+F, +X) is det.
  610%	write a html text data given in X to the file F.
  611html_write_me(F, X):-
  612	A = [ file(other('html-begin-end'/htmlbegin0)),
  613	      file(other('html-begin-end'/htmlbegin1)),
  614	      file(other('html-begin-end'/htmlbegin2)),
  615	      text(X),
  616	      file(other('html-begin-end'/htmlend))  ],
  617	 assemble(A, F).
  618
  619%
  620html_write_me(F, X, X):- html_write_me(F, X).
  621
  622%	html_open(+F) is dete.
  623%	Open the html file F on a local web server
  624%	with a default browser.
  625
  626html_open(F):-  atom_codes(F, F0),
  627	 local_apache_path(F0, P),
  628	 getinfo_codes(hostname, H),
  629	 getinfo_codes(whoami, U),
  630	 sh(open("http://" + H + "/~"+ U + "/"+ P)).
  631
  632%	base_of_path(+X:string, -Y:string) is det.
  633% 	Y is the base of the posix path X.
  634
  635base_of_path(X, Y) :-  split_string(X, "/", "", L),
  636		       last(L, Y).
  637
  638
  639%
  640anchor_tag --> base_of_path,  peek(X, ["<a href=\"", X, "\"> </a>"]).
  641
  642% ?- qa(f, `abc\n\nxyz`, X).
  643
  644qa(X) --> region, paragraph, sed(qa(X)), flatten, overwrite.
  645
  646%
  647qa(N, ["<li>", X, "<script>", N1, "(", Y1, "); </script></li>\n"]) --> [X, Y],
  648    {atom_codes(N, N1), webstring(Y,Y1)}.
  649
  650button(A, T, ["<script>", A0, "(", T0, ");</script>\n"]):-
  651	atom_codes(A, A0),
  652	webstring(T, T0).
  653
  654wqa(N) --> w(".*", X), wl("\n\n(\n)*"),
  655	peek(Y, [X,Y]),
  656	sed(wqa(N)),
  657	flatten.
  658
  659wqa(N, ["<li> ",  X,
  660		"<script>",
  661			N1, "(`<pre>", Y1, "</pre>`); ",
  662		"</script>", "
  663	</li>\n"])	-->  [X, Y],
  664			     {	atom_codes(N,N1),
  665				webencode(Y, Y1)}.
  666
  667webencode --> sed(js_char),	% sed/3 is a pac macro (see pac-etc.pl)
  668	flatten,						% So the prefix html is necessary:
  669	sed(js_char2),				% meta_predicate for sed does not help.
  670	flatten.
  671
  672erase(L) --> dsed(erase(L)).
  673erase(L,X,X)--> phrase(L).
  674
  675%
  676webstring --> qstring,
  677	flatten,
  678	sed(js_char2).
  679
  680% ?- html:qstring(`abc`, R).
  681qstring --> sed(js_char),
  682	peek(A,  ["\"", A, "\""]),
  683	flatten.
  684
  685%
  686esc --> sed(js_char), flatten.
  687
  688atomic_list_prolog_lisp(L, P):-
  689	maplist(atom_codes, L, C0),
  690	maplist(qstring, C0, C1),
  691	insert(` `, C1, P).
  692
  693% copy a buffer into the mirror directory.
  694map_mirror(['Cabinet', lecture, class2009b] - [public_html]).
  695map_mirror(['infomath2009', _] - ['2009-infomath']).
  696map_mirror(['infomath2009'] - ['2009-infomath']).
  697map_mirror(['semi-proof'] - ['2009-seminar-proof']).
  700copy_mirror_pdf(M) :- get_buffer_info(Buffer_info),
  701	obj_get([buffer(F), dir(D)], Buffer_info, _),
  702	atom_concat(D, '_region_.pdf', P),
  703	map_path_pdf(M, D, F, Q),
  704	sh(cp(P, Q)).
  705
  706%
  707map_path_pdf(M, D, F, P):- file_path_map(M, '.tex', '.pdf', D, F, P).
  708
  709% ?- html:file_path_map(map_mirror, '.tex', '.pdf', '/x/a/y/', 'cd', X).
  710% X = '/x/b/y/cd.pdf'.
  711
  712file_path_map(M, Ext, Ext0, D, F, P):- file_path_map(M, D, X),
  713	change_extension(Ext, Ext0, F, F0),
  714	atomic_list_concat(['', X, F0], /, P).
  715
  716file_path_map(M, D, P):- atomic_list_concat(D0, / , D),
  717	remove('', D0, X0),
  718	path_map(M, X0, X1),
  719	atomic_list_concat(X1, /,  P).
  720
  721%  rewriting path in a context-free way (i.e. ad hoc)
  722path_map(M, X, Y):- path_map_one(M, X, Z), !, path_map(M, Z, Y).
  723path_map(_, X, X).
  724
  725%
  726path_map_one(M, X, Y):- call(M, A-B), append(A, C, X), append(B, C, Y).
  727path_map_one(M, [X|Y], [X|Z]):- path_map_one(M, Y, Z).
  728
  729% ?- change_extension('.tex', '.pdf', 'abc.tex', X).
  730% X = 'abc.pdf'.
  731
  732change_extension(E, E0, X, Y):- atom_concat(H, E, X), !, atom_concat(H, E0, Y).
  733change_extension(_, E0, X, Y):- atom_concat(X, E0, Y).
 copy_mirror_buffer(-M) is det
copy the current buffer to a file the path of which is computed from the buffer info, and a mapping table to get the target path.
  741copy_mirror_buffer(M) :- get_buffer_info(Buffer_info),
  742	obj_get([buffer(F), dir(D)], Buffer_info, _),
  743	atom_concat(D, F, P),
  744	file_path_map(M, D, Q0),
  745	atomic_list_concat(['', Q0, F], /, Q),
  746	sh(cp(P, Q)).
  747
  748%
  749set_target(X):- atom_codes(T, X), nb_setval(target_file, T).
  750get_target(X):- nb_getval(target_file, X).
  751
  752%	Wrap with a tag mark
  753tag(Tag) --> peek(Body, ["<", Tag, ">", Body, "</", Tag, ">"]).
  754
  755tag_nl(Tag) --> peek(Body, ["<", Tag, ">", Body, "</", Tag, ">\n"]).
  756
  757tag_front(Tag) -->peek(Body, ["<", Tag, ">", Body]).
  758
  759tag_back(Tag) --> peek(Body, [Body, "<", Tag, ">"]).
 set_tex(+X, -Y) is det
Convert a term X consisting of set operations into a Latex text Y.
  767set_tex([],cs(emptyset)):-! .
  768set_tex(X,A1):-listp(X),!,(maplist(set_tex,X,A2),insert(',',A2,A3)),'pac#435'(A3,A1) .
  769set_tex(X,A1):-integer(X),!,number_codes(X,A1) .
  770set_tex(p(X,Y),['(',A1,',',A2,')']):-!,set_tex(X,A1),set_tex(Y,A2) .
  771set_tex(X+Y,[A1,cs(cup),A2]):-!,set_tex(X,A1),set_tex(Y,A2) .
  772set_tex(X&Y,[A1,cs(cap),A2]):-!,set_tex(X,A1),set_tex(Y,A2) .
  773set_tex((X\Y),[A1,cs(setminus),A2]):-!,set_tex(X,A1),set_tex(Y,A2) .
  774set_tex(X*Y,[A1,cs(times),A2]):-!,set_tex(X,A1),set_tex(Y,A2) .
  775set_tex(pow(X),[cs(mathrm),group(pow),'(',A1,')']):-!,set_tex(X,A1) .
  776
  777'pac#435'(A,[cs('{'),A,cs('}')]):-true .
 subset_tex(+X, -Y) is det
Convert a tex term X consisting of subset relations into a latex codes Y.
  784subset_tex(X=Y,[A1,=,A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  785subset_tex(X=<Y,[A1,cs(subseteq),A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  786subset_tex(X>=Y,[A1,cs(supseteq),A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  787subset_tex(X<Y,[A1,cs(subset),A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  788subset_tex(X>Y,[A1,cs(supset),A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  789subset_tex(true,group([cs(mathtt),' true'])):-! .
  790subset_tex(false,group([cs(mathtt),' false'])):-! .
  791subset_tex(in(X,Y),[A1,cs(in),A2]):-!,subset_tex(X,A1),subset_tex(Y,A2) .
  792
  793%
  794% js code conversion
  795
  796js_char("\\\\") --> "\\".
  797js_char("\\`") --> "`".
  798js_char("\\n")	--> "\n".
  799js_char("\\/")	--> "/".
  800
  801js_char2("&amp;amp;")	--> "&".
  802js_char2("&amp;prime;") --> "'".
  803js_char2("&amp;lt;")	--> "<".
  804js_char2("&amp;gt;")	--> ">".
  805
  806tex_codes(cs(N),["\\",N]):-! .
  807tex_codes(comment(X),["%",X,"\n"]):-! .
  808tex_codes(env(N,X),["\\begin{",A1,"}",A2,"\\end{",A1,"}"]):-!,tex_codes(N,A1),tex_codes(X,A2) .
  809tex_codes(group(G),A1):-!,tex_codes(@@(["{",G,"}"],:maplist@(::)),A1) .
  810tex_codes(math(X),A1):-!,tex_codes(@@(["$",X,"$"],:maplist@(::)),A1) .
  811tex_codes(dmath(X),A1):-!,tex_codes(@@(["$$",X,"$$"],:maplist@(::)),A1) .
  812tex_codes([A1|A2],A3):-!,maplist(tex_codes,[A1|A2],A3) .
  813tex_codes(X,X):-atomic(X),!