1:- module(latex,[latexit/2, latexit/3, latex_math/2, latex_math/3]).    2
    3:- meta_predicate letex_math(2,?,?).    4
    5:- set_prolog_flag(allow_variable_name_as_functor, true).    6:- use_module(util(prooftree)).    7:- use_module(pac(op)).    8:- use_module(pac(basic)).    9:- use_module(util(file)).   10:- use_module(util(obj)).   11:- use_module(util('emacs-handler')).   12:- use_module(util(misc)).   13% :- use_module(configs(cgiconfig)).
   14
   15% "asy -f pdf  xxx.asy;  open xxx.pdf"
   16asy_current_buffer_file :- cur_dir(D),
   17	cur_buf(B),
   18	atom_trim_tail(B, '.asy', B0),
   19	boomerang(D,
   20		     (asy(-f(pdf), B0);
   21			 open(-a('Preview'), B0+'.pdf'))).
 pdflatex_current_buffer_file is det
With current buffer file, "platex; dvipdfm; open -a Preview".
   25pdflatex_current_buffer_file :- cur_dir(D),
   26	cur_buf(B),
   27	atom_trim_tail(B, '.tex', B0),
   28	boomerang([D], (platex(B0);
   29		    dvipdfmx(B0);
   30		    open(-a('Preview'), B0+ '.pdf'))).
 platex_buffer is det
platex; dvipdfmx; open.
   35platex_buffer :- cur_dir(D), cur_buf(B),
   36	atom_trim_tail(B, '.tex', B0),
   37	boomerang( D,
   38	  ( platex(B0);
   39	    dvipdfmx(B0);
   40	    open(-a('Preview'), B0+ '.pdf'))).
   41
   42%
   43% ?- atom_trim_tail(abcd, cd, X).
   44% ?- atom_trim_tail(abcd, xx, X).
   45atom_trim_tail(Atom, Tail, Head):-
   46	(  sub_atom(Atom, P, _, 0, Tail)
   47	-> sub_atom(Atom, 0,  P, _, Head)
   48	;  Head = Atom ).
   49
   50
   51		/***************
   52		*     latex    *
   53		***************/
 latex_math(+Ext:text, +X:obj, -Y:obj) is det
Open the file whose directory, base, and extention are given in X.
   59latex_open_file(Ext) --> obj_get([directory(D), base(B)]),
   60	{ pshell(open(D+ (/)+ B+ (.)+ Ext)) }.
 latexit(M:atom, +X:obj, -Y:obj) is det
Latex it with mode M. Necessary information is in X.
   65latexit(prooftree) --> !, prooftree,
   66	current([X|_]),
   67	peek(X),
   68	latex_math.
   69latexit(math) --> latex_math.
   70
   71%;; (setq module-query  "qcompile(util(latex)), module(latex).")
   72% ?- qcompile(util(latex)), module(latex).
   73% ?- minimal_math_pdf(`$$\\sqrt{a+b}$$`, A).
   74% ?- minimal_math_pdf(`$$\\sqrt{a_b}$$`, A).
   75
   76minimal_math_pdf -->
   77	latex_math(
   78	(	generate_tex,
   79    	platex,
   80%    	get_size,
   81    	dvipdfmx,
   82		cleaning_tmp_file
   83	)),
   84	obj_get([base(B)]),
   85	{  pshell(open(-a('Skim'), '~/local/cgi-bin/images/' + B +'.pdf'))}.
   86
   87%
   88latex_math -->
   89	latex_math(
   90	(	generate_tex,
   91	   	platex,
   92%	   	get_size,
   93	   	dvipdfmx,
   94		cleaning_tmp_file,
   95		pdf2svg,
   96		loc(svg),
   97		img_src_tag,
   98		www_form_encode
   99	) ).
  100
  101%
  102:-meta_predicate latex_math(2, ?, ?).  103
  104latex_math(Ph) -->
  105	{	getenv(home_html_root, HR),
  106		atomics_to_string([HR, images], /, D),
  107		xsh(mkdir(-p, D)),
  108		getenv(host_html_root, UR),
  109		atomics_to_string([UR, images], /, E)
  110	},
  111	peek(X, []),
  112	obj_put([text(X)]),
  113	obj_put([directory(D)]),
  114	obj_put([url_directory(E)]),
  115	obj_put([counter_name(pdfcounter), stem(math)]),
  116	{ working_directory(OldD, D) },
  117	new_file,
  118 	det_phrase(Ph),
  119    { working_directory(_, OldD) }.
  120
  121det_phrase(M:G, X, Y):- det_phrase(G, X, Y, M).
  122%
  123det_phrase(true, X, X, _):-!.
  124det_phrase(M:G, X, Y, _):-!, det_phrase(G, X, Y, M).
  125det_phrase((G, H), X, Y, M):-!, det_phrase(G, X, Z, M),
  126	det_phrase(H, Z, Y, M).
  127det_phrase(G, X, Y, M):- once(call(M:G, X, Y)).
  128
  129
  130% ?- phrase(((=), {write(a)}, (=), {write(b)}), 1, X).
  131
  132loc(Ext) --> obj_get([base(B)]),
  133			 { atomics_to_string([images, (/), B, (.), Ext], Loc)},
  134			 obj_put([loc(Loc)]).
  135
  136img_src_tag --> obj_get([loc(Loc)]),
  137	peek(["<img width=300 height=300 src='", Loc, "'/>"]),
  138	atomics_to_string.
 trim_expr(+B:expr, +E:expr, +X:text, -Y:text) is det
Trim X by patterns B and E, and unify Y with the result.
  143trim_expr(B, E) --> expr(B), expr(X), expr(E), peek([], X).
 tex_pdf(+X:obj, -Y:url) is det
PDFLatex a given text, whose information is in X, and write the html that has a link to the pdf, and unify Y with the url of the html file.
  150tex_pdf -->
  151    generate_tex,
  152	!,
  153    platex,
  154%    get_size,
  155    dvipdfmx,
  156    generate_html,
  157    cleaning_tmp_file.
  158
  159%
  160cleaning_tmp_file --> obj_get([base(B)]),
  161   { maplist(delete_file(B), [dvi,out,log,aux]) }.
  162
  163%
  164delete_file(B, Ext):-
  165	concat_atom([B, (.) ,Ext], F),
  166	(	exists_file(F)  ->	delete_file(F)
  167	;	true
  168	).
 generate_tex(+X:obj, -Y:obj) is det
Generate a latex text in X supplying preamble, and unify Y with updated X.
  175% generate_tex --> obj_get([base(B), text(X)]),
  176%       { getenv(home, H),
  177% 		concat_atom([H, '/texmf/tex/latex/ptex/preambles/jsarticle-minimal.tex'], C),
  178% 		concat_atom([H, '/texmf/tex/latex/ptex/preambles/minimalmath.tex'], M),
  179% 		S = ["\\def\\boxfilename{", B, ".size}\n"],
  180% 		D = "\\begin{document}\\minimalpdf{",
  181% 		E = "}\\end{document}",
  182% 		concat_atom([B, '.', tex], Ftex),
  183% 		combine_file([eh:include_text(C), S, eh:include_text(M), D, X, E], Ftex)
  184% 	}.
  185
  186generate_tex --> obj_get([base(B), text(TexCode)]),
  187      {
  188		concat_atom([B, '.', tex], Ftex),
  189		file:cat_text([
  190				"\\documentclass{jsarticle}\n",
  191				"\\usepackage{amssymb}\n",
  192				"\\usepackage{amsmath}\n",
  193				"\\usepackage{fmtcount}\n",
  194				"\\usepackage{amsfonts}\n",
  195				"\\usepackage[all,graph,frame,tips,2cell]{xy}\n",
  196				"\\input{minimalmath}\n",
  197				"\\input{prooftree}\n",
  198				"\\def\\boxfilename{", B, ".size}\n",
  199				"\\begin{document}\n",
  200				"\\minimalpdf{",
  201				TexCode,
  202				  "}\n",
  203				"\\end{document}\n"
  204				 ],  Ftex)
  205	}.
 platex(+X:obj, -Y:obj) is det
Latex X into Y.
  210platex --> obj_get([base(B)]),
  211	{	getenv(platex, Tex) ,
  212		xsh([Tex,
  213			 '-halt-on-error',
  214		     '-interaction=nonstopmode',
  215		     B])
  216	}.
 pdf2ps(+X:obj, -Y:obj) is det
Pdf2ps X into Y.
  222pdf2ps -->  { getenv(pdf2ps, PDF2PS)},
  223			obj_get([base(B)]),
  224			{ xsh([PDF2PS, B+ ".pdf ", B+ ".ps"]) }.
 ps2jpg(+X:obj, -Y:obj) is det
Ps2jpg X into Y.
  229ps2jpg --> obj_get([base(B)]), { xsh(convert(B + ".ps",  B + ".jpg")) }.
 get_size(+X:obj, -Y:obj) is det
Get the size of X into Y.
  234% get_size --> obj_get([base(F)]),
  235% 	  { atomic_list_concat([F, '.size'], Fsize),
  236% 		file(Fsize, read, getstring(S)),
  237% 	    split(S, [W, H|_]),
  238% 		string_codes(W0, W),
  239% 		string_codes(H0, H)
  240% 	  },
  241% 		obj_put([width(W0), height(H0)]).
  242
  243%
  244dvi2svg --> dvipdfmx, pdf2svg.
 dvipdfmx(+X:obj, -Y:obj) is det
Dvipdfmx X into Y.
  249dvipdfmx --> obj_get([base(B)]),
  250    {   P   =  '100%,100%',
  251		PDF =  B+ ".pdf",
  252		getenv(dvipdfmx, DVIPDFMX),
  253		xsh([DVIPDFMX, -o(PDF), -p(P), -x('0pt'),-y('0pt'), B])
  254    }.
  255
  256%
  257pdf2svg --> {	getenv(pdf2svg, PDF2SVG),
  258				getenv(home_html_root, HTML_ROOT)
  259			},
  260			obj_get([base(B)]),
  261			{	atomic_list_concat([HTML_ROOT, / , images], WD),
  262				working_directory(Old, WD),
  263				xsh([PDF2SVG, B + ".pdf ", B + ".svg"]),
  264				working_directory(_, Old)
  265			}.
 generate_html(+X:obj, -Y:obj) is det
Generate HTML file from X into Y.
  270generate_html --> obj_get([base(B)]),
  271    {   H = [ "<html><body>", "<img src=""", B, ".pdf""/>", "</body></html>" ],
  272		atomics_to_string([B, '.' , html],  HTML),
  273        file(HTML, write, smash(H))
  274    }.
 open_pdf(+X:obj, -Y:obj) is det
Open pdf file X in X, and unify Y with X.
  279open_pdf --> obj_get([directory(D), base(B)]),
  280	{ xsh(open(D + (/) + B+ '.pdf')) }.
 math_view(+X:obj, -Y:obj) is det
Latex X into Y, and preview it.
  284math_view --> latex_math(
  285			   (	generate_tex,
  286					platex,
  287%					get_size,
  288					dvipdfmx,
  289					cleaning_tmp_file,
  290					obj_put([target('~/public_html/cgi-bin/images')]),
  291					loc(pdf)
  292			   )),
  293			current(P),
  294			{	send_off([ "(find-file-existing \"", P, "\")"])	 }.
 latexit(X, X) is det
Latex the current buffer content, and preview it.
  299latexit --> {latexit}.
  300
  301latexit :-  send_off("(command-execute 'latex-it)"),
  302    lisp_atom("default-directory", D),
  303	dvipdfmx(D),
  304	send_off("(preview-it)")