1% enctex.ch: implementation of enc\TeX, to be applied on top of tex.ch.
2% Used by TeX, e-TeX, pdfTeX, but not by pTeX or XeTeX.
3
4@x [2.20] l.579 - encTeX: global declarations
5xprn: array [ASCII_code] of ASCII_code;
6   { non zero iff character is printable }
7@y
8xprn: array [ASCII_code] of ASCII_code;
9   { non zero iff character is printable }
10mubyte_read: array [ASCII_code] of pointer;
11   { non zero iff character begins the multi byte code }
12mubyte_write: array [ASCII_code] of str_number;
13   { non zero iff character expands to multi bytes in log and write files }
14mubyte_cswrite: array [0..127] of pointer;
15   { non null iff cs mod 128 expands to multi bytes in log and write files }
16mubyte_skip: integer;  { the number of bytes to skip in |buffer| }
17mubyte_keep: integer; { the number of chars we need to keep unchanged }
18mubyte_skeep: integer; { saved |mubyte_keep| }
19mubyte_prefix: integer; { the type of mubyte prefix }
20mubyte_tablein: boolean; { the input side of table will be updated }
21mubyte_tableout: boolean; { the output side of table will be updated }
22mubyte_relax: boolean; { the relax prefix is used }
23mubyte_start: boolean; { we are making the token at the start of the line }
24mubyte_sstart: boolean; { saved |mubyte_start| }
25mubyte_token: pointer; { the token returned by |read_buffer| }
26mubyte_stoken: pointer; { saved first token in mubyte primitive }
27mubyte_sout: integer; { saved value of |mubyte_out| }
28mubyte_slog: integer; { saved value of |mubyte_log| }
29spec_sout: integer; { saved value of |spec_out| }
30no_convert: boolean; { conversion supressed by noconvert primitive }
31active_noconvert: boolean; { true if noconvert primitive is active }
32write_noexpanding: boolean; { true only if we need not write expansion }
33cs_converting: boolean; { true only if we need csname converting }
34special_printing: boolean; { true only if we need converting in special }
35message_printing: boolean; { true if message or errmessage prints to string }
36@z
37
38@x [2.23] l.723 - encTeX
39for i:=@'177 to @'377 do xchr[i]:=i;
40@y
41for i:=@'177 to @'377 do xchr[i]:=i;
42{Initialize enc\TeX\ data.}
43for i:=0 to 255 do mubyte_read[i]:=null;
44for i:=0 to 255 do mubyte_write[i]:=0;
45for i:=0 to 127 do mubyte_cswrite[i]:=null;
46mubyte_keep := 0; mubyte_start := false;
47write_noexpanding := false; cs_converting := false;
48special_printing := false; message_printing := false;
49no_convert := false; active_noconvert := false;
50@z
51
52@x [5.59] l.1508 FIXME -- enc\TeX\ modifications of |print|.
53  else begin if selector>pseudo then
54      begin print_char(s); return; {internal strings are not expanded}
55      end;
56    if (@<Character |s| is the current new-line character@>) then
57      if selector<pseudo then
58        begin print_ln; return;
59        end;
60@y
61  else begin if (selector>pseudo) and (not special_printing)
62                 and (not message_printing) then
63      begin print_char(s); return; {internal strings are not expanded}
64      end;
65    if (@<Character |s| is the current new-line character@>) then
66      if selector<pseudo then
67        begin print_ln; no_convert := false; return;
68        end
69      else if message_printing then
70        begin print_char(s); no_convert := false; return;
71        end;
72    if (mubyte_log>0) and (not no_convert) and (mubyte_write[s]>0) then
73      s := mubyte_write[s]
74    else if xprn[s] or special_printing then
75      begin print_char(s); no_convert := false; return; end;
76    no_convert := false;
77@z
78
79@x [5.71] encTeX - native buffer printing
80if last<>first then for k:=first to last-1 do print(buffer[k]);
81@y
82k:=first; while k < last do begin print_buffer(k) end;
83@z
84
85@x [17.230] l.4725 - encTeX: xord_code_base, xchr_code_base, prn_code_base,
86@d math_font_base=cur_font_loc+1 {table of 48 math font numbers}
87@y
88@d xord_code_base=cur_font_loc+1
89@d xchr_code_base=xord_code_base+1
90@d xprn_code_base=xchr_code_base+1
91@d math_font_base=xprn_code_base+1
92@z
93
94% encTeX: \mubytein \mubyteout \mubytelog and \specialout
95@x [17.236] l.4954
96@d web2c_int_pars=web2c_int_base+3 {total number of web2c's integer parameters}
97@y
98@d mubyte_in_code=web2c_int_base+3 {if positive then reading mubytes is active}
99@d mubyte_out_code=web2c_int_base+4 {if positive then printing mubytes is active}
100@d mubyte_log_code=web2c_int_base+5 {if positive then print mubytes to log and terminal}
101@d spec_out_code=web2c_int_base+6 {if positive then print specials by mubytes}
102@d web2c_int_pars=web2c_int_base+7 {total number of web2c's integer parameters}
103@z
104
105% encTeX: \mubytein \mubyteout \mubytelog and \specialout
106@x [17.236] l.5016
107@d tracing_char_sub_def==int_par(tracing_char_sub_def_code)
108@y
109@d tracing_char_sub_def==int_par(tracing_char_sub_def_code)
110@d mubyte_in==int_par(mubyte_in_code)
111@d mubyte_out==int_par(mubyte_out_code)
112@d mubyte_log==int_par(mubyte_log_code)
113@d spec_out==int_par(spec_out_code)
114@z
115
116% encTeX: \mubytein \mubyteout \mubytelog and \specialout
117@x [17.237] l.5080
118tracing_char_sub_def_code:print_esc("tracingcharsubdef");
119@y
120tracing_char_sub_def_code:print_esc("tracingcharsubdef");
121mubyte_in_code:print_esc("mubytein");
122mubyte_out_code:print_esc("mubyteout");
123mubyte_log_code:print_esc("mubytelog");
124spec_out_code:print_esc("specialout");
125@z
126
127% encTeX: \mubytein \mubyteout \mubytelog and \specialout
128@x [17.238] l.5200
129@!@:tracing_char_sub_def_}{\.{\\tracingcharsubdef} primitive@>
130  end;
131@y
132@!@:tracing_char_sub_def_}{\.{\\tracingcharsubdef} primitive@>
133  end;
134if enctex_p then
135  begin enctex_enabled_p:=true;
136  primitive("mubytein",assign_int,int_base+mubyte_in_code);@/
137@!@:mubyte_in_}{\.{\\mubytein} primitive@>
138  primitive("mubyteout",assign_int,int_base+mubyte_out_code);@/
139@!@:mubyte_out_}{\.{\\mubyteout} primitive@>
140  primitive("mubytelog",assign_int,int_base+mubyte_log_code);@/
141@!@:mubyte_log_}{\.{\\mubytelog} primitive@>
142  primitive("specialout",assign_int,int_base+spec_out_code);@/
143@!@:spec_out_}{\.{\\specialout} primitive@>
144end;
145@z
146
147@x [18.262] - encTeX: control sequence to byte sequence
148they may be unprintable.
149
150@<Basic printing...@>=
151procedure print_cs(@!p:integer); {prints a purported control sequence}
152begin if p<hash_base then {single character}
153@y
154they may be unprintable.
155
156The conversion from control sequence to byte sequence for enc\TeX is
157implemented here. Of course, the simplest way is to implement an array
158of string pointers with |hash_size| length, but we assume that only a
159few control sequences will need to be converted. So |mubyte_cswrite|,
160an array with only 128 items, is used. The items point to the token
161lists. First token includes a csname number and the second points the
162string to be output. The third token includes the number of another
163csname and fourth token its pointer to the string etc. We need to do
164the sequential searching in one of the 128 token lists.
165
166@<Basic printing...@>=
167procedure print_cs(@!p:integer); {prints a purported control sequence}
168var q: pointer;
169    s: str_number;
170begin
171  if active_noconvert and (not no_convert) and
172     (eq_type(p) = let) and (equiv(p) = normal+11) then { noconvert }
173  begin
174     no_convert := true;
175     return;
176  end;
177  s := 0;
178  if cs_converting and (not no_convert) then
179  begin
180    q := mubyte_cswrite [p mod 128] ;
181    while q <> null do
182    if info (q) = p then
183    begin
184      s := info (link(q)); q := null;
185    end else  q := link (link (q));
186  end;
187  no_convert := false;
188  if s > 0 then print (s)
189  else if p<hash_base then {single character}
190@z
191
192@x [18.262] - encTeX: exit label for print_cs
193  print_char(" ");
194  end;
195end;
196@y
197  print_char(" ");
198  end;
199exit: end;
200@z
201
202@x [18.265] - encTeX: \endmubyte primitive
203primitive("endcsname",end_cs_name,0);@/
204@!@:end_cs_name_}{\.{\\endcsname} primitive@>
205@y
206primitive("endcsname",end_cs_name,0);@/
207@!@:end_cs_name_}{\.{\\endcsname} primitive@>
208if enctex_p then
209begin
210  primitive("endmubyte",end_cs_name,10);@/
211@!@:end_mubyte_}{\.{\\endmubyte} primitive@>
212end;
213@z
214
215@x [18.266] - encTeX: \endmubyte primitive
216end_cs_name: print_esc("endcsname");
217@y
218end_cs_name: if chr_code = 10 then print_esc("endmubyte")
219             else print_esc("endcsname");
220@z
221
222@x [22.318] encTeX - native buffer printing
223if j>0 then for i:=start to j-1 do
224  begin if i=loc then set_trick_count;
225  print(buffer[i]);
226  end
227@y
228i := start; mubyte_skeep := mubyte_keep;
229mubyte_sstart := mubyte_start; mubyte_start := false;
230if j>0 then while i < j do
231begin
232  if i=loc then set_trick_count;
233  print_buffer(i);
234end;
235mubyte_keep := mubyte_skeep; mubyte_start := mubyte_sstart
236@z
237
238@x [24.332] encTeX: insert the added functions
239appear on that line. (There might not be any tokens at all, if the
240|end_line_char| has |ignore| as its catcode.)
241@y
242appear on that line. (There might not be any tokens at all, if the
243|end_line_char| has |ignore| as its catcode.)
244
245Some additional routines used by the enc\TeX extension have to be
246declared at this point.
247
248@p @t\4@>@<Declare additional routines for enc\TeX@>@/
249@z
250
251@x [24.341] - encTeX: more declarations in expand processor
252var k:0..buf_size; {an index into |buffer|}
253@!t:halfword; {a token}
254@y
255var k:0..buf_size; {an index into |buffer|}
256@!t:halfword; {a token}
257@!i,@!j: 0..buf_size; {more indexes for encTeX}
258@!mubyte_incs: boolean; {control sequence is converted by mubyte}
259@!p:pointer;  {for encTeX test if noexpanding}
260@z
261
262@x [24.343] - encTeX: access the buffer via read_buffer
263  begin cur_chr:=buffer[loc]; incr(loc);
264@y
265  begin
266    { Use |k| instead of |loc| for type correctness. }
267    k := loc;
268    cur_chr := read_buffer (k);
269    loc := k; incr (loc);
270    if (mubyte_token > 0) then
271    begin
272      state := mid_line;
273      cur_cs := mubyte_token - cs_token_flag;
274      goto found;
275    end;
276@z
277
278@x [24.354] - encTeX: access the buffer via read_buffer
279else  begin start_cs: k:=loc; cur_chr:=buffer[k]; cat:=cat_code(cur_chr);
280  incr(k);
281@y
282else  begin start_cs:
283   mubyte_incs := false; k := loc; mubyte_skeep := mubyte_keep;
284   cur_chr := read_buffer (k); cat := cat_code (cur_chr);
285   if (mubyte_in>0) and (not mubyte_incs) and
286     ((mubyte_skip>0) or (cur_chr<>buffer[k])) then mubyte_incs := true;
287   incr (k);
288   if mubyte_token > 0 then
289   begin
290     state := mid_line;
291     cur_cs := mubyte_token - cs_token_flag;
292     goto found;
293   end;
294@z
295
296@x [24.354] - encTeX: noexpanding the marked control sequence
297  cur_cs:=single_base+buffer[loc]; incr(loc);
298  end;
299found: cur_cmd:=eq_type(cur_cs); cur_chr:=equiv(cur_cs);
300if cur_cmd>=outer_call then check_outer_validity;
301@y
302  mubyte_keep := mubyte_skeep;
303  cur_cs:=single_base + read_buffer(loc); incr(loc);
304  end;
305found: cur_cmd:=eq_type(cur_cs); cur_chr:=equiv(cur_cs);
306if cur_cmd>=outer_call then check_outer_validity;
307if write_noexpanding then
308begin
309  p := mubyte_cswrite [cur_cs mod 128];
310  while p <> null do
311    if info (p) = cur_cs then
312    begin
313      cur_cmd := relax; cur_chr := 256; p := null;
314    end else p := link (link (p));
315end;
316@z
317
318@x [24.355] - encTeX: deactivated when reading such \^^ab control sequences
319    limit:=limit-d; first:=first-d;
320@y
321    limit:=limit-d; first:=first-d;
322    if mubyte_in>0 then mubyte_keep := k-loc;
323@z
324
325@x [24.356] - encTeX: access the buffer via read_buffer
326begin repeat cur_chr:=buffer[k]; cat:=cat_code(cur_chr); incr(k);
327until (cat<>letter)or(k>limit);
328@<If an expanded...@>;
329if cat<>letter then decr(k);
330  {now |k| points to first nonletter}
331if k>loc+1 then {multiletter control sequence has been scanned}
332  begin cur_cs:=id_lookup(loc,k-loc); loc:=k; goto found;
333  end;
334end
335@y
336begin
337  repeat cur_chr := read_buffer (k); cat := cat_code (cur_chr);
338    if mubyte_token>0 then cat := escape;
339    if (mubyte_in>0) and (not mubyte_incs) and (cat=letter) and
340      ((mubyte_skip>0) or (cur_chr<>buffer[k])) then mubyte_incs := true;
341    incr (k);
342  until (cat <> letter) or (k > limit);
343  @<If an expanded...@>;
344  if cat <> letter then
345  begin
346    decr (k); k := k - mubyte_skip;
347  end;
348  if k > loc + 1 then { multiletter control sequence has been scanned }
349  begin
350    if mubyte_incs then { multibyte in csname occurrs }
351    begin
352      i := loc; j := first; mubyte_keep := mubyte_skeep;
353      if j - loc + k > max_buf_stack then
354      begin
355        max_buf_stack := j - loc + k;
356        if max_buf_stack >= buf_size then
357        begin
358          max_buf_stack := buf_size;
359          overflow ("buffer size", buf_size);
360        end;
361      end;
362      while i < k do
363      begin
364        buffer [j] := read_buffer (i);
365        incr (i); incr (j);
366      end;
367      if j = first+1 then
368        cur_cs := single_base + buffer [first]
369      else
370        cur_cs := id_lookup (first, j-first);
371    end else cur_cs := id_lookup (loc, k-loc) ;
372    loc := k;
373    goto found;
374  end;
375end
376@z
377
378@x [24.357] - encTeX: noexpanding the marked control sequence
379      else check_outer_validity;
380@y
381      else check_outer_validity;
382    if write_noexpanding then
383    begin
384      p := mubyte_cswrite [cur_cs mod 128];
385      while p <> null do
386        if info (p) = cur_cs then
387        begin
388          cur_cmd := relax; cur_chr := 256; p := null;
389        end else p := link (link (p));
390    end;
391@z
392
393@x [24.363] encTeX - native buffer printing
394  if start<limit then for k:=start to limit-1 do print(buffer[k]);
395@y
396  k := start;
397  while k < limit do begin print_buffer(k) end;
398@z
399
400@x [25.372] - encTeX: we need to distinguish \endcsname and \endmubyte
401if cur_cmd<>end_cs_name then @<Complain about missing \.{\\endcsname}@>;
402@y
403if (cur_cmd<>end_cs_name) or (cur_chr<>0) then @<Complain about missing \.{\\endcsname}@>;
404@z
405
406@x [26.414] l.8358 - encTeX: accessing xord/xchr/xprn
407if m=math_code_base then scanned_result(ho(math_code(cur_val)))(int_val)
408@y
409if m=xord_code_base then scanned_result(xord[cur_val])(int_val)
410else if m=xchr_code_base then scanned_result(xchr[cur_val])(int_val)
411else if m=xprn_code_base then scanned_result(xprn[cur_val])(int_val)
412else if m=math_code_base then scanned_result(ho(math_code(cur_val)))(int_val)
413@z
414
415@x [29.534] l.10293 - enc\TeX: add enc\TeX banner after loading fmt file
416  begin wlog_cr; wlog('MLTeX v2.2 enabled');
417  end;
418@y
419  begin wlog_cr; wlog('MLTeX v2.2 enabled');
420  end;
421if enctex_enabled_p then
422  begin wlog_cr; wlog(encTeX_banner); wlog(', reencoding enabled');
423    if translate_filename then
424      begin wlog_cr;
425        wlog(' (\xordcode, \xchrcode, \xprncode overridden by TCX)');
426    end;
427  end;
428@z
429
430@x [48.1138] l.21648 - encTeX: \endmubyte primitive
431begin print_err("Extra "); print_esc("endcsname");
432@.Extra \\endcsname@>
433help1("I'm ignoring this, since I wasn't doing a \csname.");
434@y
435begin
436if cur_chr = 10 then
437begin
438  print_err("Extra "); print_esc("endmubyte");
439@.Extra \\endmubyte@>
440  help1("I'm ignoring this, since I wasn't doing a \mubyte.");
441end else begin
442  print_err("Extra "); print_esc("endcsname");
443@.Extra \\endcsname@>
444  help1("I'm ignoring this, since I wasn't doing a \csname.");
445end;
446@z
447
448@x [49.1211] - encTeX: extra variables for \mubyte primitive
449@!p,@!q:pointer; {for temporary short-term use}
450@y
451@!p,@!q,@!r:pointer; {for temporary short-term use}
452@z
453
454@x [49.1219] - encTeX: \mubyte and \noconvert primitives
455primitive("futurelet",let,normal+1);@/
456@!@:future_let_}{\.{\\futurelet} primitive@>
457@y
458primitive("futurelet",let,normal+1);@/
459@!@:future_let_}{\.{\\futurelet} primitive@>
460if enctex_p then
461begin
462  primitive("mubyte",let,normal+10);@/
463@!@:mubyte_}{\.{\\mubyte} primitive@>
464  primitive("noconvert",let,normal+11);@/
465@!@:noconvert_}{\.{\\noconvert} primitive@>
466end;
467@z
468
469@x [49.1220] - encTeX: \mubyte primitive
470let: if chr_code<>normal then print_esc("futurelet")@+else print_esc("let");
471@y
472let: if chr_code<>normal then
473      if chr_code = normal+10 then print_esc("mubyte")
474      else if chr_code = normal+11 then print_esc("noconvert")
475      else print_esc("futurelet")
476  else print_esc("let");
477@z
478
479@x [49.1221] - encTeX: \mubyte primitive
480let:  begin n:=cur_chr;
481@y
482let:  if cur_chr = normal+11 then do_nothing  { noconvert primitive }
483      else if cur_chr = normal+10 then        { mubyte primitive }
484      begin
485        selector:=term_and_log;
486        get_token;
487        mubyte_stoken := cur_tok;
488        if cur_tok <= cs_token_flag then mubyte_stoken := cur_tok mod 256;
489        mubyte_prefix := 60;  mubyte_relax := false;
490        mubyte_tablein := true; mubyte_tableout := true;
491        get_x_token;
492        if cur_cmd = spacer then get_x_token;
493        if cur_cmd = sub_mark then
494        begin
495          mubyte_tableout := false; get_x_token;
496          if cur_cmd = sub_mark then
497          begin
498            mubyte_tableout := true; mubyte_tablein := false;
499            get_x_token;
500          end;
501        end else if (mubyte_stoken > cs_token_flag) and
502                    (cur_cmd = mac_param) then
503                 begin
504                   mubyte_tableout := false;
505                   scan_int; mubyte_prefix := cur_val; get_x_token;
506                   if mubyte_prefix > 50 then mubyte_prefix := 52;
507                   if mubyte_prefix <= 0 then mubyte_prefix := 51;
508                 end
509        else if (mubyte_stoken > cs_token_flag) and (cur_cmd = relax) then
510             begin
511               mubyte_tableout := true; mubyte_tablein := false;
512               mubyte_relax := true; get_x_token;
513             end;
514        r := get_avail; p := r;
515        while cur_cs = 0 do begin store_new_token (cur_tok); get_x_token; end;
516        if (cur_cmd <> end_cs_name) or (cur_chr <> 10) then
517        begin
518          print_err("Missing "); print_esc("endmubyte"); print(" inserted");
519          help2("The control sequence marked <to be read again> should")@/
520("not appear in <byte sequence> between \mubyte and \endmubyte.");
521          back_error;
522        end;
523        p := link(r);
524        if (p = null) and mubyte_tablein then
525        begin
526          print_err("The empty <byte sequence>, ");
527          print_esc("mubyte"); print(" ignored");
528          help2("The <byte sequence> in")@/
529("\mubyte <token> <byte sequence>\endmubyte should not be empty.");
530          error;
531        end else begin
532          while p <> null do
533          begin
534            append_char (info(p) mod 256);
535            p := link (p);
536          end;
537          flush_list (r);
538          if (str_start [str_ptr] + 1 = pool_ptr) and
539            (str_pool [pool_ptr-1] = mubyte_stoken) then
540          begin
541            if mubyte_read [mubyte_stoken] <> null
542               and mubyte_tablein then  { clearing data }
543                  dispose_munode (mubyte_read [mubyte_stoken]);
544            if mubyte_tablein then mubyte_read [mubyte_stoken] := null;
545            if mubyte_tableout then mubyte_write [mubyte_stoken] := 0;
546            pool_ptr := str_start [str_ptr];
547          end else begin
548            if mubyte_tablein then mubyte_update;    { updating input side }
549            if mubyte_tableout then  { updating output side }
550            begin
551              if mubyte_stoken > cs_token_flag then { control sequence }
552              begin
553                dispose_mutableout (mubyte_stoken-cs_token_flag);
554                if (str_start [str_ptr] < pool_ptr) or mubyte_relax then
555                begin       { store data }
556                  r := mubyte_cswrite[(mubyte_stoken-cs_token_flag) mod 128];
557                  p := get_avail;
558                  mubyte_cswrite[(mubyte_stoken-cs_token_flag) mod 128] := p;
559                  info (p) := mubyte_stoken-cs_token_flag;
560                  link (p) := get_avail;
561                  p := link (p);
562                  if mubyte_relax then begin
563                    info (p) := 0; pool_ptr := str_start [str_ptr];
564                  end else info (p) := slow_make_string;
565                  link (p) := r;
566                end;
567              end else begin                       { single character  }
568                if str_start [str_ptr] = pool_ptr then
569                  mubyte_write [mubyte_stoken] := 0
570                else
571                  mubyte_write [mubyte_stoken] := slow_make_string;
572              end;
573            end else pool_ptr := str_start [str_ptr];
574          end;
575        end;
576      end else begin   { let primitive }
577        n:=cur_chr;
578@z
579
580@x [49.1230] l.22936 - encTeX: \xordcode, \xchrcode, \xprncode primitives
581primitive("catcode",def_code,cat_code_base);
582@!@:cat_code_}{\.{\\catcode} primitive@>
583@y
584primitive("catcode",def_code,cat_code_base);
585@!@:cat_code_}{\.{\\catcode} primitive@>
586if enctex_p then
587begin
588  primitive("xordcode",def_code,xord_code_base);
589@!@:xord_code_}{\.{\\xordcode} primitive@>
590  primitive("xchrcode",def_code,xchr_code_base);
591@!@:xchr_code_}{\.{\\xchrcode} primitive@>
592  primitive("xprncode",def_code,xprn_code_base);
593@!@:xprn_code_}{\.{\\xprncode} primitive@>
594end;
595@z
596
597@x [49.1231] l.22956 - encTeX: \xordcode, \xchrcode, \xprncode primitives
598def_code: if chr_code=cat_code_base then print_esc("catcode")
599@y
600def_code: if chr_code=xord_code_base then print_esc("xordcode")
601  else if chr_code=xchr_code_base then print_esc("xchrcode")
602  else if chr_code=xprn_code_base then print_esc("xprncode")
603  else if chr_code=cat_code_base then print_esc("catcode")
604@z
605
606@x [49.1232] l.22969 - encTeX: setting a new value to xchr/xord/xprn
607  p:=cur_chr; scan_char_num; p:=p+cur_val; scan_optional_equals;
608  scan_int;
609@y
610  p:=cur_chr; scan_char_num;
611  if p=xord_code_base then p:=cur_val
612  else if p=xchr_code_base then p:=cur_val+256
613  else if p=xprn_code_base then p:=cur_val+512
614  else p:=p+cur_val;
615  scan_optional_equals;
616  scan_int;
617@z
618
619@x [49.1232] l.22980 - encTeX: setting a new value to xchr/xord/xprn
620  if p<math_code_base then define(p,data,cur_val)
621@y
622  if p<256 then xord[p]:=cur_val
623  else if p<512 then xchr[p-256]:=cur_val
624  else if p<768 then xprn[p-512]:=cur_val
625  else if p<math_code_base then define(p,data,cur_val)
626@z
627
628@x [49.1279] - encTeX: implement \noconvert
629old_setting:=selector; selector:=new_string;
630token_show(def_ref); selector:=old_setting;
631@y
632old_setting:=selector; selector:=new_string;
633message_printing := true; active_noconvert := true;
634token_show(def_ref);
635message_printing := false; active_noconvert := false;
636selector:=old_setting;
637@z
638
639% encTeX: |slow_print| is too eager to expand printed strings.  To
640% selectively suppress or enable expansion (needed to \noconvert)
641% |print| will look at |message_printing|.  So we bypass |slow_print|
642% and go directly to |print| instead.
643@x [49.1279] - encTeX: to handle \noconvert in messages go directly to |print|
644slow_print(s); update_terminal;
645@y
646print(s); update_terminal;
647@z
648
649@x [49.1279] - encTeX: to handle \noconvert in messages go directly to |print|
650begin print_err(""); slow_print(s);
651@y
652begin print_err(""); print(s);
653@z
654
655% encTeX: dump encTeX-specific data to fmt file.
656@x [50.1302] l.23694
657@<Dump ML\TeX-specific data@>;
658@y
659@<Dump ML\TeX-specific data@>;
660@<Dump enc\TeX-specific data@>;
661@z
662
663% encTeX: undump encTeX-specific data from fmt file.
664@x [50.1303] l.23694
665@<Undump ML\TeX-specific data@>;
666@y
667@<Undump ML\TeX-specific data@>;
668@<Undump enc\TeX-specific data@>;
669@z
670
671@x [51.1337] l.24371 - enc\TeX: add. enc\TeX banner after loading fmt file
672  begin wterm_ln('MLTeX v2.2 enabled');
673  end;
674@y
675  begin wterm_ln('MLTeX v2.2 enabled');
676  end;
677if enctex_enabled_p then
678  begin wterm(encTeX_banner); wterm_ln(', reencoding enabled.');
679    if translate_filename then begin
680      wterm_ln(' (\xordcode, \xchrcode, \xprncode overridden by TCX)');
681    end;
682  end;
683@z
684
685@x [53.1341] - encTeX: keep track of mubyte value for \write
686@d write_stream(#) == info(#+1) {stream number (0 to 17)}
687@y
688@d write_stream(#) == type(#+1) {stream number (0 to 17)}
689@d mubyte_zero == 64
690@d write_mubyte(#) == subtype(#+1) {mubyte value + |mubyte_zero|}
691@z
692
693@x [53.1350] - encTeX: \write stores mubyte_out value
694write_stream(tail):=cur_val;
695@y
696write_stream(tail):=cur_val;
697if mubyte_out + mubyte_zero < 0 then write_mubyte(tail) := 0
698else if mubyte_out + mubyte_zero >= 2*mubyte_zero then
699       write_mubyte(tail) := 2*mubyte_zero - 1
700     else write_mubyte(tail) := mubyte_out + mubyte_zero;
701@z
702
703@x [53.1353] - encTeX: \special stores specialout and mubyteout values
704begin new_whatsit(special_node,write_node_size); write_stream(tail):=null;
705p:=scan_toks(false,true); write_tokens(tail):=def_ref;
706@y
707begin new_whatsit(special_node,write_node_size);
708if spec_out + mubyte_zero < 0 then write_stream(tail) := 0
709else if spec_out + mubyte_zero >= 2*mubyte_zero then
710       write_stream(tail) := 2*mubyte_zero - 1
711     else write_stream(tail) := spec_out + mubyte_zero;
712if mubyte_out + mubyte_zero < 0 then write_mubyte(tail) := 0
713else if mubyte_out + mubyte_zero >= 2*mubyte_zero then
714       write_mubyte(tail) := 2*mubyte_zero - 1
715     else write_mubyte(tail) := mubyte_out + mubyte_zero;
716if (spec_out = 2) or (spec_out = 3) then
717  if (mubyte_out > 2) or (mubyte_out = -1) or (mubyte_out = -2) then
718    write_noexpanding := true;
719p:=scan_toks(false,true); write_tokens(tail):=def_ref;
720write_noexpanding := false;
721@z
722
723@x [53.1355] - encTeX: \write prints \mubyteout value
724else print_char("-");
725@y
726else print_char("-");
727if (s = "write") and (write_mubyte (p) <> mubyte_zero) then
728begin
729  print_char ("<"); print_int (write_mubyte(p)-mubyte_zero); print_char (">");
730end;
731@z
732
733@x [53.1356] - encTeX: \special prints \specialout and \mubyteout values
734special_node:begin print_esc("special");
735@y
736special_node:begin print_esc("special");
737if write_stream(p) <> mubyte_zero then
738begin
739  print_char ("<"); print_int (write_stream(p)-mubyte_zero);
740  if (write_stream(p)-mubyte_zero = 2) or
741     (write_stream(p)-mubyte_zero = 3) then
742  begin
743    print_char (":"); print_int (write_mubyte(p)-mubyte_zero);
744  end;
745  print_char (">");
746end;
747@z
748
749@x [53.1368] - encTeX: conversions in \special
750old_setting:=selector; selector:=new_string;
751@y
752old_setting:=selector; selector:=new_string;
753spec_sout := spec_out;  spec_out := write_stream(p) - mubyte_zero;
754mubyte_sout := mubyte_out;  mubyte_out := write_mubyte(p) - mubyte_zero;
755active_noconvert := true;
756mubyte_slog := mubyte_log;
757mubyte_log := 0;
758if (mubyte_out > 0) or (mubyte_out = -1) then mubyte_log := 1;
759if (spec_out = 2) or (spec_out = 3) then
760begin
761  if (mubyte_out > 0) or (mubyte_out = -1) then
762  begin
763    special_printing := true; mubyte_log := 1;
764  end;
765  if mubyte_out > 1 then cs_converting := true;
766end;
767@z
768
769@x [53.1368] - encTeX: conversions in \special
770for k:=str_start[str_ptr] to pool_ptr-1 do dvi_out(so(str_pool[k]));
771@y
772if (spec_out = 1) or (spec_out = 3) then
773  for k:=str_start[str_ptr] to pool_ptr-1 do
774    str_pool[k] := si(xchr[so(str_pool[k])]);
775for k:=str_start[str_ptr] to pool_ptr-1 do dvi_out(so(str_pool[k]));
776spec_out := spec_sout; mubyte_out := mubyte_sout; mubyte_log := mubyte_slog;
777special_printing := false; cs_converting := false;
778active_noconvert := false;
779@z
780
781@x [53.1370] l.24770 - encTeX
782begin @<Expand macros in the token list
783@y
784begin
785mubyte_sout := mubyte_out;  mubyte_out := write_mubyte(p) - mubyte_zero;
786if (mubyte_out > 2) or (mubyte_out = -1) or (mubyte_out = -2) then
787  write_noexpanding := true;
788@<Expand macros in the token list
789@z
790
791@x [53.1370] - encTeX: conversion in parameter of \write
792token_show(def_ref); print_ln;
793@y
794active_noconvert := true;
795if mubyte_out > 1 then cs_converting := true;
796mubyte_slog := mubyte_log;
797if (mubyte_out > 0) or (mubyte_out = -1) then mubyte_log := 1
798else mubyte_log := 0;
799token_show(def_ref); print_ln;
800cs_converting := false; write_noexpanding := false;
801active_noconvert := false;
802mubyte_out := mubyte_sout; mubyte_log := mubyte_slog;
803@z
804
805@x[54.1376] l.24903 - enc\TeX
806@* \[54] System-dependent changes.
807@y
808@* \[54/enc\TeX] System-dependent changes for enc\TeX.
809
810@d encTeX_banner == ' encTeX v. Jun. 2004'
811
812@ The boolean variable |enctex_p| is set by web2c according to the given
813command line option (or an entry in the configuration file) before any
814\TeX{} function is called.
815
816@<Global...@> =
817@!enctex_p: boolean;
818
819
820@ The boolean variable |enctex_enabled_p| is used to enable enc\TeX's
821primitives.  It is initialised to |false|.  When loading a \.{FMT} it
822is set to the value of the boolean |enctex_p| saved in the \.{FMT} file.
823Additionally it is set to the value of |enctex_p| in Ini\TeX.
824
825@<Glob...@>=
826@!enctex_enabled_p:boolean;  {enable encTeX}
827
828
829@ @<Set init...@>=
830enctex_enabled_p:=false;
831
832
833@ Auxiliary functions/procedures for enc\TeX{} (by Petr Olsak) follow.
834These functions implement the \.{\\mubyte} code to convert
835the multibytes in |buffer| to one byte or to one control
836sequence. These functions manipulate a mubyte tree: each node of
837this tree is token list with n+1 tokens (first token consist the byte
838from the byte sequence itself and the other tokens point to the
839branches). If you travel from root of the tree to a leaf then you
840find exactly one byte sequence which we have to convert to one byte or
841control sequence. There are two variants of the leaf: the ``definitive
842end'' or the ``middle leaf'' if a longer byte sequence exists and the mubyte
843tree continues under this leaf. First variant is implemented as one
844memory word where the link part includes the token to
845which we have to convert and type part includes the number 60 (normal
846conversion) or 1..52 (insert the control sequence).
847The second variant of ``middle leaf'' is implemented as two memory words:
848first one has a type advanced by 64 and link points to the second
849word where info part includes the token to which we have to convert
850and link points to the next token list with the branches of
851the subtree.
852
853The inverse: one byte to multi byte (for log printing and \.{\\write}
854printing) is implemented via a pool. Each multibyte sequence is stored
855in a pool as a string and |mubyte_write|[{\it printed char\/}] points
856to this string.
857
858@d new_mubyte_node ==
859  link (p) := get_avail; p := link (p); info (p) := get_avail; p := info (p)
860@d subinfo (#) == subtype (#)
861
862@<Basic printing...@>=
863{ read |buffer|[|i|] and convert multibyte.  |i| should have been
864  of type 0..|buf_size|, but web2c doesn't like that construct in
865  argument lists. }
866function read_buffer(var i:integer):ASCII_code;
867var p: pointer;
868    last_found: integer;
869    last_type: integer;
870begin
871  mubyte_skip := 0; mubyte_token := 0;
872  read_buffer := buffer[i];
873  if mubyte_in = 0 then
874  begin
875    if mubyte_keep > 0 then mubyte_keep := 0;
876    return ;
877  end;
878  last_found := -2;
879  if (i = start) and (not mubyte_start) then
880  begin
881    mubyte_keep := 0;
882    if (end_line_char >= 0) and (end_line_char < 256) then
883      if mubyte_read [end_line_char] <> null then
884      begin
885        mubyte_start := true; mubyte_skip := -1;
886        p := mubyte_read [end_line_char];
887        goto continue;
888      end;
889  end;
890restart:
891  mubyte_start := false;
892  if (mubyte_read [buffer[i]] = null) or (mubyte_keep > 0) then
893  begin
894    if mubyte_keep > 0 then decr (mubyte_keep);
895    return ;
896  end;
897  p := mubyte_read [buffer[i]];
898continue:
899  if type (p) >= 64 then
900  begin
901    last_type := type (p) - 64;
902    p := link (p);
903    mubyte_token := info (p); last_found := mubyte_skip;
904  end else if type (p) > 0 then
905  begin
906    last_type := type (p);
907    mubyte_token := link (p);
908    goto found;
909  end;
910  incr (mubyte_skip);
911  if i + mubyte_skip > limit then
912  begin
913    mubyte_skip := 0;
914    if mubyte_start then goto restart;
915    return;
916  end;
917  repeat
918    p := link (p);
919    if subinfo (info(p)) = buffer [i+mubyte_skip] then
920    begin
921      p := info (p); goto continue;
922    end;
923  until link (p) = null;
924  mubyte_skip := 0;
925  if mubyte_start then goto restart;
926  if last_found = -2 then return;  { no found }
927  mubyte_skip := last_found;
928found:
929  if mubyte_token < 256 then  { multibyte to one byte }
930  begin
931    read_buffer := mubyte_token;  mubyte_token := 0;
932    i := i + mubyte_skip;
933    if mubyte_start and (i >= start) then mubyte_start := false;
934    return;
935  end else begin     { multibyte to control sequence }
936    read_buffer := 0;
937    if last_type = 60 then { normal conversion }
938      i := i + mubyte_skip
939    else begin            { insert control sequence }
940      decr (i); mubyte_keep := last_type;
941      if i < start then mubyte_start := true;
942      if last_type = 52 then mubyte_keep := 10000;
943      if last_type = 51 then mubyte_keep := mubyte_skip + 1;
944      mubyte_skip := -1;
945    end;
946    if mubyte_start and (i >= start) then mubyte_start := false;
947    return;
948  end;
949exit: end;
950
951@ @<Declare additional routines for enc\TeX@>=
952procedure mubyte_update; { saves new string to mubyte tree }
953var j: pool_pointer;
954    p: pointer;
955    q: pointer;
956    in_mutree: integer;
957begin
958  j := str_start [str_ptr];
959  if mubyte_read [so(str_pool[j])] = null then
960  begin
961    in_mutree := 0;
962    p := get_avail;
963    mubyte_read [so(str_pool[j])] := p;
964    subinfo (p) := so(str_pool[j]); type (p) := 0;
965  end else begin
966    in_mutree := 1;
967    p := mubyte_read [so(str_pool[j])];
968  end;
969  incr (j);
970  while j < pool_ptr do
971  begin
972    if in_mutree = 0 then
973    begin
974      new_mubyte_node; subinfo (p) := so(str_pool[j]); type (p) := 0;
975    end else { |in_mutree| = 1 }
976      if (type (p) > 0) and (type (p) < 64) then
977      begin
978        type (p) := type (p) + 64;
979        q := link (p); link (p) := get_avail; p := link (p);
980        info (p) := q;
981        new_mubyte_node; subinfo (p) := so(str_pool[j]); type (p) := 0;
982        in_mutree := 0;
983      end else begin
984        if type (p) >= 64 then p := link (p);
985        repeat
986          p := link (p);
987          if subinfo (info(p)) = so(str_pool[j]) then
988          begin
989            p := info (p);
990            goto continue;
991          end;
992        until link (p) = null;
993        new_mubyte_node; subinfo (p) := so(str_pool[j]); type (p) := 0;
994        in_mutree := 0;
995      end;
996continue:
997    incr (j);
998  end;
999  if in_mutree = 1 then
1000  begin
1001    if type (p) = 0 then
1002    begin
1003       type (p) := mubyte_prefix + 64;
1004       q := link (p);  link (p) := get_avail; p := link (p);
1005       link (p) := q; info (p) := mubyte_stoken;
1006       return;
1007    end;
1008    if type (p) >= 64 then
1009    begin
1010      type (p) := mubyte_prefix + 64;
1011      p := link (p); info (p) := mubyte_stoken;
1012      return;
1013    end;
1014  end;
1015  type (p) := mubyte_prefix;
1016  link (p) := mubyte_stoken;
1017exit: end;
1018@#
1019procedure dispose_munode (p: pointer); { frees a mu subtree recursivelly }
1020var q: pointer;
1021begin
1022  if (type (p) > 0) and (type (p) < 64) then free_avail (p)
1023  else begin
1024    if type (p) >= 64 then
1025    begin
1026      q := link (p); free_avail (p); p := q;
1027    end;
1028    q := link (p); free_avail (p); p := q;
1029    while p <> null do
1030    begin
1031      dispose_munode (info (p));
1032      q := link (p);
1033      free_avail (p);
1034      p := q;
1035    end;
1036  end;
1037end;
1038@#
1039procedure dispose_mutableout (cs: pointer); { frees record from out table }
1040var p, q, r: pointer;
1041begin
1042  p := mubyte_cswrite [cs mod 128];
1043  r := null;
1044  while p <> null do
1045    if info (p) = cs then
1046    begin
1047      if r <> null then link (r) := link (link (p))
1048      else mubyte_cswrite[cs mod 128] := link (link (p));
1049      q := link (link(p));
1050      free_avail (link(p)); free_avail (p);
1051      p := q;
1052    end else begin
1053      r := link (p); p := link (r);
1054    end;
1055end;
1056
1057@ The |print_buffer| procedure prints one character from |buffer|[|i|].
1058It also increases |i| to the next character in the buffer.
1059
1060@<Basic printing...@>=
1061{ print one char from |buffer|[|i|]. |i| should have been of type
1062  0..|buf_size|, but web2c doesn't like that construct in argument lists. }
1063procedure print_buffer(var i:integer);
1064var c: ASCII_code;
1065begin
1066  if mubyte_in = 0 then print (buffer[i]) { normal TeX }
1067  else if mubyte_log > 0 then print_char (buffer[i])
1068       else begin
1069         c := read_buffer (i);
1070         if mubyte_token > 0 then print_cs (mubyte_token-cs_token_flag)
1071         else print (c);
1072       end;
1073  incr (i);
1074end;
1075
1076@ Additional material to dump for enc\TeX.  This includes whether
1077enc\TeX is enabled, and if it is we also have to dump the \.{\\mubyte}
1078arrays.
1079
1080@<Dump enc\TeX-specific data@>=
1081dump_int(@"45435458);  {enc\TeX's magic constant: "ECTX"}
1082if not enctex_p then dump_int(0)
1083else begin
1084  dump_int(1);
1085  dump_things(mubyte_read[0], 256);
1086  dump_things(mubyte_write[0], 256);
1087  dump_things(mubyte_cswrite[0], 128);
1088end;
1089
1090@ Undumping the additional material we dumped for enc\TeX.  This includes
1091conditionally undumping the \.{\\mubyte} arrays.
1092
1093@<Undump enc\TeX-specific data@>=
1094undump_int(x);   {check magic constant of enc\TeX}
1095if x<>@"45435458 then goto bad_fmt;
1096undump_int(x);   {undump |enctex_p| flag into |enctex_enabled_p|}
1097if x=0 then enctex_enabled_p:=false
1098else if x<>1 then goto bad_fmt
1099else begin
1100  enctex_enabled_p:=true;
1101  undump_things(mubyte_read[0], 256);
1102  undump_things(mubyte_write[0], 256);
1103  undump_things(mubyte_cswrite[0], 128);
1104end;
1105
1106
1107@* \[54] System-dependent changes.
1108@z
1109