1:- module(switex, [ switex/0, switex_main/0 ]).

LaTeX/Prolog server module

*/

    5:- use_module(latex).    6
    7:- meta_predicate write_phrase(//).    8
    9switex_main :-
   10   on_signal(int,_,exit), % allows direct exit in case of deadlock
   11   switex,
   12   halt.
   13
   14exit(Sig) :- log('CTL | Terminating due to sig~w.\n',[Sig]), halt(1).
   15
   16switex :-
   17   log('Starting SWITeX server...\n',[]),
   18   current_prolog_flag(tty_control,TTY),
   19   set_stream(current_input,buffer(line)),
   20   setup_call_cleanup(
   21      (set_prolog_flag(tty_control, false), prompt(Pr1,'')), start,
   22      (set_prolog_flag(tty_control, TTY), prompt(_,Pr1))).
   23
   24
   25start :- get_code(C), first_char(C).
   26
   27% process first character of a new line read from TeX
   28first_char(-1)   :- log('SWITeX ending normally.\n',[]).
   29first_char(0'\\) :- !, get_code(C1), pre_query(C1).
   30first_char(C)    :- is_prompt(C), !, nl, 
   31   read_line_to_codes(current_input,Rest),
   32   tex_prompt(Rest,[C|T]-T).
   33first_char(C)    :- tex_output([C|T]-T). 
   34
   35is_prompt(0'?).
   36is_prompt(0'*).
   37
   38% Process rest of line after detecting TeX prompt character (? or *)
   39% Second argument is a difference list representing input so far this line.
   40tex_prompt(end_of_file,Prefix-[]) :- !,
   41   log('CTL | Possible incomplete TeX prompt: ~s\n',[Prefix]).
   42tex_prompt(Rest,Prefix-Rest) :- log('TPR | ~s\n',[Prefix]), start.
   43
   44% Process lines which start with \ as potential Prolog queries.
   45pre_query(-1) :- !, log('CTL | Possible incomplete Prolog query "\\"\n',[]).
   46pre_query(0'Q) :- !, get_code(C2), pre_query2(C2).
   47pre_query(C1) :- tex_output([0'\\,C1|T]-T).
   48
   49pre_query2(-1) :- !, log('CTL | Possible incomplete Prolog query "\\Q"\n',[]).
   50pre_query2(0'=) :- !, 
   51   with_output_to(codes(C),query), 
   52   log('SWI | <- {~s}\n',[C]),
   53   format('{~s}\n',[C]), start.
   54pre_query2(C2) :- tex_output([0'\\,0'Q,C2|T]-T).
   55
   56query :- 
   57   catch((read_term(Q,[]), log('SWI | -> ~q.\n',[Q]), user:once(Q)), Ex, handle(Ex)).
   58
   59% Process rest of line as normal TeX output given prefix as difference list
   60tex_output(Head-Tail) :-
   61   read_line_to_codes(current_input,Rest),
   62   tex_output1(Rest,Head-Tail).
   63tex_output1(end_of_file,Head-[]) :- !, log('TeX output ended mid-line: ~s\n',[Head]).
   64tex_output1(Rest,Head-Rest) :- log('TeX | ~s\n',[Head]), start.
   65
   66% If an exception occurs in the Prolog query, we output ERROR
   67handle(Ex) :- 
   68   print_message(error,Ex),
   69   write_phrase(cmd(swierror,"ERROR")).
   70
   71write_phrase(Phrase) :-
   72	phrase(Phrase,Codes,[]),
   73	format('~s',[Codes]).
   74
   75log(Msg,Args) :- format(user_error,Msg,Args).
   76
   77% Not used at the moment
   78% module_tex_preamble --> def(swiphr, #(1), cmd(swi,(wr(switex),":",wr(write_phrase),paren(#(1))))).