Here are the remaining changes to the program that are necessary to make \TeX\ work on VMS. Note that especial care has been taken not to introduce any new sections; therefore, everything up to this point has had the same section numbers as the canonical versions in ``\TeX: The Program''. Firstly, putting the cart before the horse, this is how we can return the final status of \TeX\ to the operating system, in such a way that DCL command procedures and the like can determine whether the run of \TeX\ was successfull or not. We use the \.{\$EXIT} system service; the value of its parameter is @.{\$}EXIT@> given by an appropriate symbolic constant taken from the \.{starlet} library. We also take this opportunity to call the |symbol_jobname| routine (defined below). @d VAX_exit==@=$exit@> @d VAX_ss_normal==@= sts$k_success @> @d VAX_ss_ignore==@= sts$m_inhib_msg @> @d VAX_ss_warning==@= sts$k_warning+sts$m_inhib_msg @> @d VAX_ss_error==@= sts$k_error+sts$m_inhib_msg @> @d VAX_ss_fatal==@= sts$k_severe+sts$m_inhib_msg @> @= symbol_jobname; case history of { Issue an appropriate VAX exit status } spotless: VAX_exit(VAX_ss_normal); { Everything OK! } warning_issued: VAX_exit(VAX_ss_warning); error_message_issued: VAX_exit(VAX_ss_error); fatal_error_stop: VAX_exit(VAX_ss_fatal) endcases @ |symbol_jobname| is a routine which takes the |job_name| string and the numeric portion of the extension of the output file and writes that information to the DCL symbol given by \.{/JOBNAME\_SYMBOL}. @./JOBNAME_SYMBOL@> The code here is based on code donated by Jim Walker of South Carolina University. @d VAX_set_symbol == @= lib$set_symbol @> @= procedure@?VAX_set_symbol(VAX_immed symbol: descr_ptr; VAX_immed value_string: descr_ptr; tbl_ind: integer := VAX_immed 0); external; @t\2@> @# procedure symbol_jobname; var tmp_descr: descr_ptr; begin tmp_descr:=nil; if job_qual then begin str_to_descr(job_name,tmp_descr); VAX_set_symbol (VAX_stdescr l_jobname, tmp_descr, 2); end; end; @ Support is provided for the \.{REVIEW} mode of DEC's Language-sensitive editor, @^Language-sensitive editor@> @^LSE@> by generating a \.{.dia} file. Any output sent via this routine is also repeated to that file if the global |copy_err| is |print_it|: if the characters are being ``repeated'' to produce a \.{label} for a \.{region/text} directive, then characters will only be copied if no more than |label_max| have been output; this is controlled by |label_size|. Negative values for this variable always permit printing. Since \TeX\ produces its error messages by many separate calls to various printing routines, we accumulate the full text in the \PASCAL\ internal file |temp_file| when |copy_err| is set to |save_it|. This file can later be |reset| and ``played back'' by standard \PASCAL\ routines. @d label_max=14 @= case copy_err of print_it: begin if label_size<> 0 then diag_char(s); if label_size>0 then decr(label_size) end; ignore_it: do_nothing; save_it: temp_char(s) endcases @ We introduce here variables which control the action of error reporting routines. When error message display is commenced, the variable |copy_err| is set to |save_it|: this causes parts of the error message to be saved in the internal file |temp_file|, which is rewound at this point. Certain parts of the error message are not so saved (|copy_err=ignore_it|). This variable is also used to cause messages to be written (|copy_err=print_it|) to the diagnostics file |diag_file|. Since VAX-\PASCAL\ supports proper enumeration types, we don't bother with defining numeric constants for this. When information is being written to the |diag_file|, we restrict the ``label'' portion of a diagnostic message to |label_max| characters, to preserve on-screen alignment in LSEdit's \.{REVIEW} buffer. Characters are only output through to the |diag_file| if |label_size| is non-zero, and this variable is decremented after each character has been output if it is positive. Thus negative values of |label_size| do not impose any restriction on the amount of text that may be output to the |diag_file|. @= @!copy_err:(ignore_it,print_it,save_it); @!label_size:-1..label_max; {Restricts ``printing'' in the \.{.dia} file} @ After the terminating period has been written, |copy_err| is reset to prevent further output to |temp_file|, which is also reset, ready to be ``replayed'' into the diagnostics file itself. This code is also used during initialization, and also before prompting for a new file name when \TeX\ has been unable to find a users' file. @= copy_err:=ignore_it; reset(temp_file) {Full \TeX\ message in |temp_file|} @ Every error message that \TeX\ creates is ``wrapped'' into a \.{diagnostic} environment for use by LSE's \.{REVIEW} mode. This is the text generated for the start of such an environment. @= wdiag_ln('!'); wdiag_ln(' start diagnostic') @ And this finishes off the \.{diagnostic} environment: we copy into it the informational part of \TeX's own error message. @= wdiag(' message "%TEX-E-TEXERROR, '); while not eof(temp_file) do begin wdiag(temp_file^); get(temp_file) end; wdiag_ln('"'); wdiag_ln(' end diagnostic') @ If the error report arises within the expansion of a macro, \TeX\ will report the expansions of all macros and arguments involved: each such line of information is used in the diagnostics file as a \.{label} (in the terminology of LSE's \.{REVIEW} mode). This is how we start it off, and ensure that no more than |label_max| characters are printed, thus preserving alignment of the text within the \.{\$REVIEW} buffer. @= wdiag(' region/text/label="'); copy_err:=print_it; label_size:=label_max @ The rest of the context (display of macro expansions, or whatever) forms the remainder of the diagnostic region label. @= copy_err:=ignore_it; wdiag('" "') @ On the other hand, if \TeX's error report specifies a location within a source file, the diagnostic region generated in the diagnostics file reports that location thus: @= wdiag(' region/file/primary '); diag_print(name); wdiag_ln(' -'); {Continuation line follows} wdiag_ln(' /line=',line:1,'/column_range=(1,65535)') @ Whenever |show_context| involves printing out a token list, we arrange to capture the printed tokens for our diagnostic file. @= wdiag(' region/text/label="'); copy_err:=print_it; label_size:=label_max @ As we write out the second line of the original source, split at the point of error detection, we don't want to include within the diagnostic file the newline nor the leading spaces. This looks like horrible duplication of code, but remember that |copy_err=print_it| \&{only} if a diagnostic file is being generated. @= if copy_err=print_it then begin copy_err:=ignore_it; print_ln; for q:=1 to n do print_char(" "); {print |n| spaces to begin line~2} copy_err:=print_it end else begin print_ln; for q:=1 to n do print_char(" "); {print |n| spaces to begin line~2} end @ After we've completed the display of the error context, we are able to complete the diagnostic region within the diagnostics file. @= if copy_err=print_it then begin wdiag('"/line=1/column_range=('); n:=n-l; wdiag_ln(n+1:1,',65535)'); copy_err:=ignore_it; end else wdiag_ln(' region/nested/column=',loc-start+1:1) @ When we are writing the remainder of the context to the terminal and/or transcript file, we need to ensure that it is also \&{all} copied to the diagnostics file. The diagnostic is completed by ``playing back'' the contents of the |temp_file|, which contains \TeX's error message. @= begin copy_err:=print_it; label_size:=-1 end @ When the \.{\string\show} primitive is used, it will later involve the display of a token; the latter would cause output to be written to the |temp_file| used for accumulating error messages for the diagnostics file, so we ensure here that the file will not be overfilled. @= copy_err:=ignore_it; rewrite(temp_file); {Internal file will later be |reset|} @ The |open_diag_file| routine is used to open a file into which error diagnostics are written to support DEC's Language-sensitive Editor (LSEdit). @^Language-sensitive editor@> @^LSE@> These may be used by the latter to locate the editor at the position within the source file at which an error has been detected. @= procedure open_diag_file; begin pack_job_name(".dia"); if pack_default_name(diag_qual,diagf_name,diagf_len) then begin while not a_open_out(diag_file) do prompt_file_name("diagnostics file name",".dia"); diag_name:=a_make_name_string(diag_file); wdiag_ln('start module'); end else diag_name:="."; clear_default_name; end; @ Here are a number of variables used during the initial extraction of the command line and its qualifiers. Firstly, we require separate flags for each of the possible qualifiers. We also need to declare those variables associated with support for the diagnostics file, utilized by LSEdit. @^Language-sensitive editor@> @^LSE@> When \TeX\ is producing error messages, they are created in ``dribs and drabs''; we utilize a \PASCAL\ `internal' file |temp_file| to accumulate the whole message for transfer to the diagnostics file. This mechanism is also used to create a command line by means of which an editor can be invoked by the user answering `\.e' in response to \TeX's error prompt. Since such invocation of an editor will disrupt access to the values associated with any qualifiers on the \.{TEX} command, we have to provide storage space for any values provided with those qualifiers, so that they may be read during the initialization phase, in preparation for use later (in some cases, much later) in the program. For each such piece of text, we need somewhere to save it, and somewhere else to record its length, for use with |pack_default_name|. @= @!format_qual, @!dvi_qual, @!cmd_line_present, @!continue_qual, @!eight_qual, @!job_qual,@!batch_qual, @!log_qual, @!diag_qual, @!edit_qual : boolean; @# @!diag_file : alpha_file; @!diag_name : str_number; @!temp_file : alpha_file; @# @!logf_name, @!diagf_name, @!edit_name, @!l_jobname, @!dvif_name : packed array[1..file_name_size] of char; @!logf_len, @!diagf_len, @!edit_len, @!l_len_name, @!dvif_len : file_size; @ Since we provide a command-line qualifier which will ``preload'' a format file, it would be best to extract all the qualifiers before the |banner| gets printed, so that the correct preloaded format can be displayed (it will never {\it really\/} be preloaded, but a VAX doesn't take long to read a \.{.FMT} file!) In fact, it is {\it essential\/} that all command-line qualifiers be read at this stage; the reader might imagine that extraction of qualifiers and their values could be deferred until the point at which the qualifier is used, but any intervening activation of another image (for example, an editor) results in the information being wiped out. The |cmd_line_present| flag will later avoid clearing the |buffer| if a command-line has already been ``read'' into it. We can control \TeX's operation in |batch_mode| through the \.{/BATCH} qualifier. At this point, we also initialize |copy_err|, which controls the insertion into the diagnostics file of text being (pseudo)printed in traditional \TeX\ error message. @= diag_name := 0; get_command_line; if batch_qual then interaction:=batch_mode; copy_err:=ignore_it@; @ For interacting with a user-supplied command line, we need to call the VAX standard library routines \.{CLI\$PRESENT}, \.{CLI\$GET\_VALUE}, \.{CLI\$DCL\_PARSE} and \.{LIB\$GET\_FOREIGN}. @.CLI{\$}PRESENT@> @.CLI{\$}GET_VALUE@> @.CLI{\$}DCL_PARSE@> @.LIB{\$}GET_FOREIGN@> This is a definition of their external interfaces: note the application of the `external' attribute, and use of the |extern| directive. @d VAX_external==@= external@> @d VAX_asynchronous==@= asynchronous@> @d VAX_cli_dcl_parse==@= cli$dcl_parse@> @d VAX_lib_get_foreign==@= lib$get_foreign@> @d VAX_lib_sig_to_ret==@= lib$sig_to_ret@> @d VAX_establish==@= establish@> @= [VAX_external] function VAX_cli_present(@/ VAX_stdescr @!entity: [VAX_volatile,VAX_readonly] packed array [l1..u1:integer] of char := VAX_immed 0) : integer; @/ extern;@;@t\2@>@# [VAX_external] function VAX_cli_get_value(@/ VAX_stdescr @!entity: [VAX_volatile,VAX_readonly] packed array [l1..u1:integer] of char := VAX_immed 0; VAX_stdescr @!returns: [VAX_volatile] packed array [l2..u2:integer] of char := VAX_immed 0; var @!retlen: [VAX_volatile] sixteen_bits := VAX_immed 0):integer; @/ extern;@;@t\2@>@# [VAX_external] function VAX_cli_dcl_parse(@/ VAX_stdescr @!cmdline: [VAX_volatile,VAX_readonly] packed array [l1..u1:integer] of char := VAX_immed 0; VAX_immed @!cld_table: [VAX_volatile,VAX_readonly] VAX_unsigned := VAX_immed 0):integer; @/ extern;@;@t\2@>@# [VAX_external] function VAX_lib_get_foreign(@/ VAX_stdescr @!cmdlin: [VAX_volatile] packed array [l1..u1:integer] of char := VAX_immed 0; VAX_stdescr @!prompt: [VAX_volatile] packed array [l2..u2:integer] of char := VAX_immed 0; var @!len: [VAX_volatile] sixteen_bits := VAX_immed 0; var @!flag: [VAX_volatile] integer := VAX_immed 0) :integer; @/ extern;@;@t\2@>@# [VAX_external, VAX_asynchronous] function VAX_lib_sig_to_ret(@/ VAX_ref @!signal_args: [VAX_volatile,VAX_unsafe] array [l1..u1:integer] of [VAX_byte] eight_bits; VAX_ref @!mechan_args: [VAX_volatile,VAX_unsafe] array [l2..u2:integer] of [VAX_byte] eight_bits) :integer; @/ extern; @ The following global symbol is used to refer to the command definition table linked into the \TeX\ program @d eTeX_CLD_table == @=ETEX_CLI@> @= @!eTeX_CLD_table : [VAX_external, VAX_readonly] VAX_unsigned; @ The |init_cli| function is invoked right at the beginning of \TeX, only preceded by the terminal output initialization. Its purpose is to make sure that the DCL command interface is available. This function checks, if the program was invoked by the DCL command specified through |verb_name| and that a command qualifier specified by |qual_name| is present (or defaulted) in the command description. For the second test, a small subroutine |check_cli| is needed, because of the "caller--callee" dependence required by the user error handler facility. The |verb_name| string supplied to |init_cli| by the caller must not exceed a length of 4, otherwise the comparison with the "last DCL command" does never succeed, because the DCL parser truncates commands to a length of 4! The test item |qual_name| should be a specific, non-negatable command qualifier for the verb |verb_name|, which is set by default in the command description. If either of these two tests fail, it can be assumed that the program was invoked as a foreign command (or started by the RUN command). If this case, the command line tail is fetched with the \.{LIB\$GET\_FOREIGN} runtime functions and parsed internally, using the \.{CLI\$DCL\_PARSE} utility routine and the command table linked into the program executable, whose name is supplied by the |table| formal parameter. @.LIB{\$}GET_FOREIGN@> @.CLI{\$}DCL_PARSE@> @= function init_cli( var @!table:[VAX_readonly] VAX_unsigned; @!verb_name:[VAX_readonly] packed array[l1..u1:integer] of char; @!qual_name:[VAX_readonly] packed array[l2..u2:integer] of char ): integer; label exit; var command_line: packed array[1..256] of char; @!len: sixteen_bits; @!sts: integer; function check_cli( @!unique_def_qual:[VAX_readonly] packed array[l1..u1:integer] of char ): integer; begin VAX_establish(VAX_lib_sig_to_ret); check_cli := VAX_cli_present(unique_def_qual); end; begin sts := VAX_cli_get_value('$VERB',command_line,len); if (odd(sts) and (len > 0)) then if (VAX_substr(command_line,1,len) = verb_name) then if (odd(check_cli(qual_name))) then begin init_cli := 1; return; end; VAX_lib_get_foreign(command_line,,len); {prepend |verb_name| plus a blank to |command_line|} command_line := verb_name + ' ' + VAX_substr(command_line,1,len); init_cli := VAX_cli_dcl_parse(command_line, VAX_address_of(table)); exit:end; @ Logically, the following procedure belongs with |init_terminal|; however, we can't declare it there because it calls functions which don't get declared until later, so we'll stuff it in just before the main program starts. If an editor is invoked later, its use of the command-line interface parsing routines will ``disable communications'', so we'd better extract any values associated with qualifiers now. The various flags are set or cleared according as to whether the associated qualifier is or is not present. @= procedure get_command_line; var qual_argument: packed array[1..256] of char; @!len: sixteen_bits; @!i: integer; @!j: 0..buf_size; begin cmd_line_present := odd(VAX_cli_present('COMMAND_LINE')); edit_qual := odd(VAX_cli_present('EDITOR')); if edit_qual then VAX_cli_get_value('EDITOR',edit_name,edit_len); job_qual:=odd(VAX_cli_present('JOBNAME_SYMBOL')); if job_qual then VAX_cli_get_value('JOBNAME_SYMBOL',l_jobname,l_len_name); continue_qual := odd(VAX_cli_present('CONTINUE')); batch_qual := odd(VAX_cli_present('BATCH')); dvi_qual := odd(VAX_cli_present('OUTPUT')); if dvi_qual then VAX_cli_get_value('OUTPUT',dvif_name,dvif_len); log_qual := odd(VAX_cli_present('LOG_FILE')); if log_qual then VAX_cli_get_value('LOG_FILE',logf_name,logf_len); diag_qual := odd(VAX_cli_present('DIAGNOSTICS')); if diag_qual then VAX_cli_get_value('DIAGNOSTICS',diagf_name,diagf_len); format_qual := odd(VAX_cli_present('FORMAT')); if format_qual then begin VAX_cli_get_value('FORMAT',qual_argument,len); loc := 0; buffer[0] := xord['&']; j := 1; for i := 1 to len do begin buffer[j] := xord[qual_argument[i]]; incr(j) end; buffer[j] := xord[' ']; { |open_fmt_file| requires space after name } if format_ident <> 0 then initialize; if not open_fmt_file then goto final_end; if not load_fmt_file then begin w_close(fmt_file); goto final_end; end; w_close(fmt_file); end; end; @ Here are the things we need for |byte_file| and |word_file| files: @= @!tfm_count: 0..VAX_block_length; @!fmt_count: 0..VAX_block_length; @ Here's the interrupt stuff. At this point, we define some attributes for specifying particular sizes and alignments of numerical quantities in VAX-\PASCAL. @d VAX_word==@= word @> @d VAX_longword==@= long @> @d VAX_byte==@= byte @> @d VAX_unsigned==@= unsigned @> @= @!signed_halfword=[VAX_word] -32768..32767; @!sixteen_bits=[VAX_word] 0..65535; @!file_size=[VAX_word] 0..file_name_size; @# @!VAX_F_float = packed record {Bit pattern layout of F-Floating Reals} @!Frac1 : 0..127; {the 7 MSBits of the mantissa} @!Expo : 0..255; {8 bit exponent} @!Sign : boolean; {1 sign bit} @!Frac : 0..65535; {the 16 lower bits of the mantissa} end; @ @= @!res: [VAX_volatile] integer; @!tt_chan: [VAX_volatile] signed_halfword; @ @= [VAX_asynchronous] procedure @!ctrlc_rout; begin interrupt:=1; enable_control_C; end; @ Here is the stuff for magic file operations. @d VAX_FAB_type==@= FAB$type @> @d VAX_RAB_type==@= RAB$type @> @d VAX_NAM_type==@= NAM$type @> @= @!unsafe_file = [VAX_unsafe] file of char; @!FAB_ptr = ^VAX_FAB_type; @!RAB_ptr = ^VAX_RAB_type; @!NAM_ptr = ^VAX_NAM_type; @!chrptr = ^char; @ We supply the following two routines to be used (in a call of the VAX-\PASCAL\ |open| procedure) as a |user_action| function. When called from within the |open| routine, the addresses of the |FAB| and |RAB| allocated to the file are passed to such a function, along with the file variable; the latter is tagged as `unsafe' to prevent undesirable compiler optimizations. The |user_reset| function, used to open files for reading, performs wild card expansion on the file specification and opens the first matching file. Both |user_action| functions copy the fully qualified name of the file that was actually opened into the global variable |last_name|. Additionally, the basename part of the filename is available in the string variable |last_basename|. The latter string is converted to lowercase; to comply with normal usage on other (case-sensitive) operating systems. The two external functions |VAX_PAS_FAB| and |VAX_PAS_RAB| permit access by the program to these structures after the file has been opened. @d VAX_rms_parse==@=$parse@> @d VAX_rms_search==@=$search@> @d VAX_rms_create==@=$create@> @d VAX_rms_connect==@=$connect@> @d VAX_rms_open==@=$open@> @# @d VAX_FAB_V_NAM== @=FAB$V_NAM@> @d VAX_FAB_L_NAM== @=FAB$L_NAM@> @d VAX_NAM_B_RSL== @=NAM$B_RSL@> @d VAX_NAM_L_RSA== @=NAM$L_RSA@> @d VAX_NAM_B_NAME== @=NAM$B_NAME@> @d VAX_NAM_L_NAME== @=NAM$L_NAME@> @= function user_reset (var FAB:VAX_FAB_type; var RAB:VAX_RAB_type; var F:unsafe_file):integer; label done; var sts:integer; @!NAM:NAM_ptr; @!p:chrptr; @!i:integer; @!ichr:integer; begin last_length:=0; sts:=VAX_rms_parse(FAB); if not odd(sts) then goto done; sts:=VAX_rms_search(FAB); if odd(sts) then FAB.VAX_FAB_V_NAM:=true; {Use |NAM| block in |VAX_rms_open| call!} sts:=VAX_rms_open(FAB); if not odd(sts) then goto done; sts:=VAX_rms_connect(RAB); if not odd(sts) then goto done; NAM:=FAB.VAX_FAB_L_NAM::NAM_ptr; if NAM=nil then goto done; last_length:=NAM^.VAX_NAM_B_RSL; for i:=1 to last_length do begin p:=(NAM^.VAX_NAM_L_RSA::integer+i-1)::chrptr; last_name[i]:=p^; end; last_basenam_len:=NAM^.VAX_NAM_B_NAME; for i:=1 to last_basenam_len do begin p:=(NAM^.VAX_NAM_L_NAME::integer+i-1)::chrptr; ichr:=ord(p^); if (ichr > 64) and (ichr < 91) then ichr := ichr+32; last_basename[i]:=chr(ichr); end; done: user_reset:=sts; end; @# function user_rewrite (var FAB:VAX_FAB_type; var RAB:VAX_RAB_type; var F:unsafe_file):integer; label done; var sts:integer; @!NAM:NAM_ptr; @!p:chrptr; @!i:integer; @!ichr:integer; begin sts:=VAX_rms_create(FAB); if not odd(sts) then goto done; sts:=VAX_rms_connect(RAB); if not odd(sts) then goto done; NAM:=FAB.VAX_FAB_L_NAM::NAM_ptr; if NAM=nil then goto done; last_length:=NAM^.VAX_NAM_B_RSL; for i:=1 to last_length do begin p:=(NAM^.VAX_NAM_L_RSA::integer+i-1)::chrptr; last_name[i]:=p^; end; last_basenam_len:=NAM^.VAX_NAM_B_NAME; for i:=1 to last_basenam_len do begin p:=(NAM^.VAX_NAM_L_NAME::integer+i-1)::chrptr; ichr:=ord(p^); if (ichr > 64) and (ichr < 91) then ichr := ichr+32; last_basename[i]:=chr(ichr); end; done: user_rewrite:=sts; end; @# function VAX_PAS_FAB(var foobar:unsafe_file):FAB_ptr; extern;@;@t\2@>@/ function VAX_PAS_RAB(var foobar:unsafe_file):RAB_ptr; extern; @ @= @!in_FAB,out_FAB: FAB_ptr; @!in_RAB,out_RAB: RAB_ptr; @!last_length: integer; @!last_name:packed array[1..file_name_size] of char; @!last_basenam_len: integer; @!last_basename:packed array[1..file_name_size] of char; @ The following procedure is used to translate any logical name that may appear as its parameter into its equivalence string and makes use of the \.{\$TRNLNM} @.{\$}TRNLNM@> system service in place of the obsolete \.{\$TRNLOG}. If the content of the @.{\$}TRNLOG@> buffer is a logical name, it is replaced by its equivalence string and the routine returns |true|. If no translation can be found, the result is |false|, and the original string is left unchanged. The VAX-\PASCAL\ procedure |substr| is used to extract a substring into the |varying| array which is passed to the system service, whilst another VAX-specific function |iaddress| is used to obtain the address of various data items to fill in the |item_list|. @d VAX_trnlnm==@= $trnlnm@> @d VAX_lnm_case_blind==@= lnm$m_case_blind @> @d VAX_lnm_string==@= lnm$_string @> @# @d VAX_substr==@= substr@> @d VAX_address_of==@= iaddress@> @= function translate ( var t : packed array [l1..u1 : integer] of char; var len : signed_halfword): boolean; var @!s: varying[file_name_size] of char; @!trnlnm_return: integer; {what did the \.{\$TRNLNM} return?} @!return_length: [VAX_volatile] integer; @!attributes: unsigned; @!item_list: [VAX_volatile] array [0..1] of VMS_item_list; begin s:=VAX_substr(t,1,len); attributes := VAX_lnm_case_blind; return_length := 0; with item_list[0] do begin buffer_length := file_name_size; item_code := VAX_lnm_string; buffer_addr := VAX_address_of(t); ret_len_addr := VAX_address_of(return_length); end; item_list[1].next_item := 0; trnlnm_return := VAX_trnlnm(attributes,'LNM$DCL_LOGICAL',s,,item_list); len := return_length; translate := trnlnm_return=VAX_ss_normal; end; @ Here is a new type introduced to support \.{\$TRNLNM}. Many VMS system @.{\$}TRNLNM@> services make use of an |item_list| to pass information in and out. An |item_list| consists of a number of |item_list| elements, with each element containing the following fields: \centerline{\vtop{\offinterlineskip\hrule \halign{\vrule#\hskip2pt&\strut#\hfil&#\hfil&#\hfil&\hskip2pt\vrule#\cr height2pt&\omit&\omit&\omit&\cr &\hfil Name & \hfil Type & \hfil Usage&\cr height2pt&\omit&\omit&\omit&\cr \noalign{\hrule} height2pt&\omit&\omit&\omit&\cr &|buffer_length| & 16-bit word & Size of buffer&\cr &|item_code| & unsigned 16-bit word & Code for desired operation&\cr &|buffer_address| & Pointer to char & Address of buffer&\cr &|ret_len_addr| & Pointer to integer & To receive length of translation&\cr height2pt&\omit&\omit&\omit&\cr} \hrule }} This structure is overlaid with a single 32-bit integer whose use is solely to hold the value zero indicating the end of the list. @== @!VMS_item_list = packed record case boolean of true: ( @!buffer_length : sixteen_bits;@/ @!item_code : sixteen_bits;@/ @!buffer_addr : [VAX_longword] integer;@/ @!ret_len_addr : [VAX_longword] integer); false: ( @!next_item : [VAX_longword] integer) end; @ If the user, in response to \TeX's error message, elects to edit the source file, then we have to find some method of invoking an editor. The simplest solution, under VMS, is simply to spawn a sub-process, but this is expensive in terms of image activation and might leave the sub-process short of page file quota, since the latter is shared by all processes in the current `job'. Therefore, where possible, we invoke a ``callable'' editor, which merely requires that we find the relevant editor's entry point in an installed shareable image. However, the library routine which can perform this trick returns the entry point as an address, and yet we want the \PASCAL\ code to think that it's invoking the editor through a procedure call, passing appropriate parameter(s). The callable versions of LSEdit @^Language-sensitive editor@> @^LSE@> and TPU each require a single parameter which is @^TPU@> @.EDIT/TPU@> a string similar to the DCL command that could be used to invoke the non-callable versions. In the case of EDT @^EDT@> @.EDIT/EDT@> @^Callable editors@> and TECO, @^TECO@> @.EDIT/TECO@> the first parameter gives the name of the file to be edited, the second (if used) names the output file, whilst the third can specify the name of a command file. Both editors can also take further parameters, and their meanings differ, but luckily we don't need any of these other parameters! Unfortunately, \PASCAL\ provides no mechanism by which a routine, which has amongst its formal parameters one which is in turn another routine, may be called with anything but the name of an \\{actual} routine (with congruent parameters) substitued for that formal parameter. Therefore, it is not permissible to pass the address of the routine instead and yet that is all that we have available! We therefore provide a procedure which calls, in turn, the actual editor ``procedure'', and resorting to subterfuge, invoke a rather useful VAX Library Routine: @d VAX_lib_callg==@= lib$callg@> @= [VAX_external] function VAX_lib_callg (@/ VAX_immed arg_list : [VAX_longword] integer; VAX_immed user_proc: [VAX_longword] integer) : integer; extern;@t\2@>@# function call_editor ( @!proc: [VAX_longword] integer; @!param_1, @!param_3 : [VAX_volatile] descr_ptr ) : integer; var @!call_G_descriptor : packed array [1..4] of [VAX_longword] integer; begin call_G_descriptor[1] := 1; {Number of arguments} call_G_descriptor[2] := param_1::integer; {DCL-like command line or name of file to be edited} if param_3 <> nil then begin call_G_descriptor[1] := 3; {EDT and TECO require more arguments} call_G_descriptor[3] := 0; {Default the output file name} call_G_descriptor[4] := param_3::integer; {Editor command file} end; call_editor:=VAX_lib_callg(VAX_address_of(call_G_descriptor),proc) end; @ Here is the interface to two routines from the run-time library to handle dynamic strings. Also, we declare here the interface to the \.{LIB\$SIGNAL} @.LIB{\$}SIGNAL@> library function, because we don't have much else to fall back on if an error crops up whilst allocating strings! @d str_allocate ==@= str$get1_dx@> @d str_release ==@= str$free1_dx@> @d lib_signal ==@= lib$signal@> @d VAX_char_string==@= dsc$k_dtype_t @> @d VAX_class_S==@= dsc$k_class_s @> @d VAX_class_D==@= dsc$k_class_d @> @= [VAX_external, VAX_asynchronous] function str_allocate(@/ VAX_ref alloc : [VAX_readonly] sixteen_bits; VAX_immed descrp : descr_ptr ) : integer; extern;@t\2@> @# [VAX_external, VAX_asynchronous] function str_release(@/ VAX_immed descrp : descr_ptr ) : integer; extern;@t\2@> @# [VAX_external, VAX_asynchronous] procedure lib_signal(@/ VAX_immed cond_code: integer; VAX_immed num_of_args: integer := VAX_immed 0; VAX_immed fao_argument: [@=list,unsafe@>] integer ); extern; @ Some editors require either command or file specifications to be passed to them as parameters, which in turn requires that they be passed in the form of string descriptors. Many of the strings that we have to deal with are held within \TeX's string pool. This routine converts a \.{WEB}-type string (from the pool) into an appropriate VAX-\PASCAL\ string descriptor. Any existing string described by |dynam_str| is returned to the operating system and a new string allocated to reflect the actual length of the string in |pool_string|. @= procedure str_to_descr( @!pool_string : str_number; var @!dynam_str : [VAX_volatile] descr_ptr); var @!ch_ptr, @!str_stat : integer; @!str_size : sixteen_bits; @!ch_ctr : chrptr; begin if dynam_str = nil then begin new( dynam_str ); with dynam_str^ do begin len := 0; desc_type := VAX_char_string; desc_class := VAX_class_D; string := 0 end; end else if dynam_str^.len <> 0 then begin str_stat := str_release( dynam_str ); if not odd(str_stat) then lib_signal(str_stat) end; ch_ptr := str_start[pool_string]; str_size := str_start[pool_string+1]-str_start[pool_string]; str_stat := str_allocate(str_size,dynam_str); if not odd(str_stat) then lib_signal(str_stat); ch_ctr := dynam_str^.string :: chrptr; while str_size>0 do begin ch_ctr^ := xchr[so(str_pool[ch_ptr])]; ch_ctr := (ch_ctr::integer + 1)::chrptr; incr(ch_ptr); decr(str_size) end; end; @ Here is where we declare a structure to hold a VMS Descriptor. We could just have used one of the definitions in the \.{STARLET} library that we've inherited, but declaring it here is an aid to understanding. \centerline{\vtop{\offinterlineskip\hrule \halign{\vrule#\hskip2pt&\strut#\hfil&#\hfil&#\hfil&\hskip2pt\vrule#\cr height2pt&\omit&\omit&\omit&\cr &\hfil Name & \hfil Type & \hfil Usage&\cr height2pt&\omit&\omit&\omit&\cr \noalign{\hrule} height2pt&\omit&\omit&\omit&\cr &|len| & 16-bit word & Elements in the array&\cr &|desc_type| & unsigned 8-bit byte & Type of items in array&\cr &|desc_class| & unsigned 8-bit byte & \\{e.g.} Fixed, Varying, Dynamic&\cr &|string| & Pointer to char & Address of first item in array&\cr height2pt&\omit&\omit&\omit&\cr} \hrule }} It also makes life much easier, when passing dynamic strings as parameters, especially to system services and library routines which expect to be passed the address of such a descriptor, to have a type which is a pointer to such a descriptor, and then pass the pointer's value by immediate parameter-passing mechanism. @= @!descr_type = packed record {A VAX-descriptor object} @!len : sixteen_bits; @!desc_type : eight_bits; @!desc_class: eight_bits; @!string : [VAX_longword] integer; end; @!descr_ptr = ^descr_type; @ Here is a procedure to dispose of dynamically-allocated strings when they are no longer required. @= procedure release ( @!string : descr_ptr ); var str_stat : integer; begin if string <> nil then begin str_stat := str_release( string ); if not odd(str_stat) then lib_signal( str_stat ); dispose(string); string := nil; end; end; @ This version of \TeX\ supports various editors; that required by the user must be specified by the qualifier \.{/EDITOR} which is set by default to \.{TEX\_EDIT} (which should be defined as a VMS logical name, in analogy with @.TEX_EDIT@> @.MAIL{\$}EDIT@> \.{MAIL\$EDIT}---in fact some system managers may want to set the default in the CLD file to {\it be\/} \.{MAIL\$EDIT}). If this qualifier specifies one of the strings `\.{Callable\_LSE}', `\.{Callable\_TPU}', `\.{Callable\_EDT} @.Callable_xxx@> or `\.{Callable\_TECO}' (or a logical name translating to one of those strings), the appropriate editor is invoked from its callable shared image. Any other value for \.{/EDITOR} is treated as a DCL command, and a sub-process is spawned in which the command is executed; the name of the file to be edited, together with the location of the error, are passed as parameters to this DCL command, which will most usefully, therefore, be defined to invoke a command procedure. Because the original version of this change file simply used \.{TEX\_EDIT} directly and this is the default value, the remainder of this exposition will simply refer to the value of \.{/EDITOR} as \.{TEX\_EDIT}. Here is a data structure which holds details of the supported callable editors: @= @!editor_ident = record @!cmd_offset : integer; @!image, @!entry, @!quitting, @!exiting, @!cmd_text: str_number; @!start_qual, @!EDT_like : boolean; @!logical : packed array[1..file_name_size] of char; end; @ We need a suitably sized array of such structures: @d max_editor=4 @# @d LSE_editor=1 @d TPU_editor=2 @d EDT_editor=3 @d TECO_editor=4 @= @!editor : packed array [1..max_editor] of editor_ident; @ And we needs must initialize them: @= with editor[LSE_editor] do begin logical := 'CALLABLE_LSE'; image := "LSESHR"; entry := "LSE$LSE"; quitting := "TPU$_QUITTING"; exiting := "TPU$_EXITING"; cmd_text := "LSEdit"; cmd_offset := 0; start_qual:=true; EDT_like := false; end; with editor[TPU_editor] do begin logical := 'CALLABLE_TPU'; image := "TPUSHR"; entry := "TPU$TPU"; quitting := "TPU$_QUITTING"; exiting := "TPU$_EXITING"; cmd_text := "EDIT/TPU"; cmd_offset := 5; {Actual command expected by \.{TPU\$TPU} omits \.{EDIT/}} start_qual:=true; EDT_like := false; end; with editor[EDT_editor] do begin logical := 'CALLABLE_EDT'; image := "EDTSHR"; entry := "EDT$EDIT"; quitting := 0; exiting := 0; cmd_text := "EDIT/EDT"; cmd_offset := 0; start_qual:=false; EDT_like := true; end; with editor[TECO_editor] do begin logical := 'CALLABLE_TECO'; image := "TECOSHR"; entry := "TECO$EDIT"; quitting := 0; exiting := 0; cmd_text := "EDIT/TECO"; cmd_offset := 0; start_qual := false; EDT_like := true; end; @ When we invoke an editor, there are three (possibly more?) potential outcomes: (1) The editor cannot be invoked --- perhaps we should find some other method; (2) The user makes no change to the file (quits); (3) The use produces a new version of the file. This type allows us to discriminate between these outcomes: @= @!edit_result = (failed,quit,edited); @ If the user elects to edit the relevant input file in response to an error message, we prefer to use an editor provided as a ``callable image'', since this saves the overhead of spawning a sub-process. DEC provide callable versions of EDT, @^EDT@> @.EDIT/EDT@> @^Callable editors@> TPU, @^TPU@> @.EDIT/TPU@> LSEdit (the language-sensitive editor, highly recommended for \LaTeX), @^Language-sensitive editor@> @^LSE@> and even for that editor beloved of many, TECO. @^TECO@> @.EDIT/TECO@> To activate such a callable image, we need to load it into the process's \.{P0} space, and determine its entry point before transferring control to it with appropriate parameters. If it proves impossible to load a suitable callable image, we can adopt the expedient of spawning a new (DCL) sub-process, and pass to it the command to be executed. When such a spawned sub-process is given a single command to execute, the exit status of that command is passed back to the parent process when the sub-process exits. In most useful applications of such a sub-process, the ``command'' to be executed will be a DCL command procedure; the code below will accept an exit status of $1$ as indicating that an edit has taken place, the value $0$ (which is of warning severity level) as showing that the edit was aborted (the user quit), and any other value will be interpreted as indicative of a failure of the sub-process to perform editing. The official definition of \.{LIB\$SPAWN} has about a dozen parameters, but @.LIB{\$}SPAWN@> since all of them are optional, and we only need to pass a command (which is the first parameter) and get back the completion status (which is the seventh), we'll pretend that it only takes seven parameters. @d VAX_find_image ==@= lib$find_image_symbol@> @d VAX_lib_spawn ==@= lib$spawn@> @= [VAX_external] function VAX_find_image (@/ VAX_immed @!filenm : descr_ptr; VAX_immed @!symbol : descr_ptr; VAX_ref @!symbol_value : [VAX_volatile,VAX_longword] integer; VAX_immed @!image_name : descr_ptr := VAX_immed 0) : integer; @/ extern;@t\2@> @# [VAX_external] function VAX_lib_spawn (@/ VAX_immed @!cmd : descr_ptr; VAX_immed @!sys_input : descr_ptr := VAX_immed 0; VAX_immed @!sys_output : descr_ptr := VAX_immed 0; VAX_ref @!flags : [VAX_longword] integer := VAX_immed 0; VAX_immed @!prcnm : descr_ptr := VAX_immed 0; VAX_ref @!pid : [VAX_longword] integer := VAX_immed 0; VAX_ref @!status : [VAX_longword] integer := VAX_immed 0 ): integer; @/ extern;@t\2@> @# function Edit ( @!filenm, @!cmd_file : str_number; @!editor : editor_ident ): edit_result; var @!edit_command_line : descr_ptr; @!char_ct : sixteen_bits; @!editor_entry : integer; @!editor_status, @!str_stat : integer; @!ch_ptr : chrptr; @!quit_status, @!exit_status : integer; @!image_symbol, @!entry_point, @!bad_symbol, @!good_symbol : descr_ptr; @!edit_file, @!edit_cmd : descr_ptr; begin @; edit_command_line := nil; @; edit_file:=nil; edit_cmd:=nil; if editor.EDT_like then {Such editors take \\{filenames} as parameters} begin str_to_descr(filenm,edit_file); str_to_descr(cmd_file,edit_cmd); end; Edit := failed; {Assume the worst!} editor_status := 4; {Neither edited nor quitted} quit_status := 0; {Users' command procedures can return this for quitting} exit_status := VAX_ss_normal; @; if editor.image <> 0 then {Possibly callable} begin if VAX_find_image(image_symbol,entry_point,editor_entry)=VAX_ss_normal then @ else editor.image := 0 {Indicate inability to invoke shareable image} end; if editor.image = 0 then {Use non-shareable-image editing} str_stat:=VAX_lib_spawn(cmd:=edit_command_line,status:=editor_status); @; @ end; @ The data structure |editor| contains pool strings giving the name of the required shareable image and the names of symbols which are to be sought for in it. This is where we translate those strings into dynamic ones to be passed to \.{LIB\$FIND\_IMAGE\_SYMBOL} @.LIB{\$}FIND_IMAGE_SYMBOL@> @== image_symbol := nil; entry_point := nil; bad_symbol := nil; good_symbol := nil; str_to_descr(editor.image,image_symbol); str_to_descr(editor.entry,entry_point); str_to_descr(editor.quitting,bad_symbol); str_to_descr(editor.exiting,good_symbol) @ If we're to invoke a callable editor, we have now obtained its entry point, which will have caused its image to be loaded into the process's \.{P0} space. Now we find within the image the values associated with the symbols which indicate whether the editor was used to create a new file or whether the use quit without creating a new file (only possible for LSEdit and TPU; with EDT and TECO, we assume that any successful exit resulted in the creation of a new file). @= begin @; if editor.EDT_like then editor_status:=call_editor(editor_entry,edit_file,edit_cmd) else @; end @ Just to keep things tidy, we dispose of all dynamic strings used by |Edit| before exit; this ensures that repeated invocation of an editor will not result in the ``eating up'' of virtual memory. @= release(image_symbol); release(entry_point); release(bad_symbol); release(good_symbol); release(edit_command_line); release(edit_file); release(edit_cmd); @ After the editor, whether running in a spawned sub-process or as a callable version in a shared image, has returned control to \TeX, we attempt to interpret its exit status. Having removed any flag instructing the CLI to ignore the error status (because the editor will have reported such an error already), we attempt to match the exit status against the values which we have preset as indicating normal exit or quit from the editor. Any other value will leave the value |failed| to be returned by |Edit|: this should cause \TeX\ to inform the user that the edit will have to be performed ``off-line''. @= if editor_status>=VAX_ss_ignore then editor_status:=editor_status-VAX_ss_ignore; if editor_status = exit_status then Edit := edited else if editor_status = quit_status then Edit := quit @ As well as containing the entry point at which the callable editor should be entered, its image file may also contain global symbols which give the exit status which will be returned by the editor if the user exits successfully, having written a new file, or quits without writing a new file. We extract the values of these symbols so that this status can be interpreted on exit from this procedure |Edit|. @= if editor.quitting<>0 then if not odd(VAX_find_image(image_symbol,bad_symbol,quit_status)) then quit_status := VAX_ss_normal; if editor.exiting<>0 then if not odd(VAX_find_image(image_symbol,good_symbol,exit_status)) then exit_status := VAX_ss_normal @ If we're invoking the callable version of TPU, we have to remove the `\.{EDIT/}' from the `\.{EDIT/TPU...}' command that we've constructed in |edit_command_line|. This code removes the first |editor.cmd_offset| characters of the command by overwriting with spaces, which achieves the desired effect. We then invoke the editor through |call_editor|. @= begin ch_ptr := edit_command_line^.string :: chrptr; for char_ct := 1 to editor.cmd_offset do begin ch_ptr^ := ' '; {Expunge the first |cmd_offset| characters} ch_ptr := (ch_ptr::integer + 1)::chrptr end; editor_status:=call_editor(editor_entry,edit_command_line,nil); end @ So far, we've managed to construct in the |temp_file| a command to be passed to the callable editor (through appropriate diversion to that \PASCAL\ internal file during the analysis of the logical \.{TEX\_EDIT}). So that we can allocate @.TEX_EDIT@> an appropriately sized dynamic string and its descriptor to be passed to the callable image, we need initially to determine how long that command really is: @= reset(temp_file); char_ct:=1; while not eof(temp_file) do begin get(temp_file); incr(char_ct) end @ Now we can allocate the dynamic string to hold the editor command, and copy the latter into it. Perhaps it might be thought that this could be simplified, because we could ``replay'' the command from the |temp_file| into a pool string by setting |selector| to |new_string| and then using |str_to_descr|: however, I'm not sure that this would be safe if in so doing we exceeded the allocated string pool, so we're going to do a bit more work! @= new( edit_command_line ); with edit_command_line^ do begin len := 0; desc_type := VAX_char_string; desc_class := VAX_class_D; string := 0 end; str_stat := str_allocate( char_ct, edit_command_line ); if not odd(str_stat) then lib_signal(str_stat); ch_ptr := edit_command_line^.string::chrptr; reset(temp_file); while not eof(temp_file) do begin ch_ptr^ := temp_file^; get(temp_file); ch_ptr := (ch_ptr::integer + 1)::chrptr end @ Certain VAX callable editors (\.{LSE} and \.{TPU}) accept a qualifier which may be used to specify the row and column number at which the editor's cursor is to be positioned. This routine adds suitable characters to the editor command line currently under construction in |temp_file|. @= procedure edit_locate(@!line, @!col : integer); begin print("/START_POSITION=("); print_int(line); print_char(","); print_int(col); print(") ") end; @ The function |edit_file| is called from the error reporting routine with the context of an input file and the line number as parameters. It forms a command for the desired editor (making using of |temp_file| and various of the error printing routines). The function returns |true| if it was able to invoke an editor. If |false| is returned, the user-interface routine should tell the user what and where to edit, and exit from \TeX. First of all, we need to make a forward declaration in order that the code which interprets the user's response can be compiled to call this procedure. @= function edit_file( @!stack_item : in_state_record; line : integer ) : boolean; forward; @ But the function itself needs to {\it follow\/} all those declared in \.{WEB} modules, so we put it just before the main program itself. To determine what name to use in invoking the editor, this function attempts to translate the value of \.{/EDITOR}; if the translation is recognized, then we'll use that as the value, otherwise, we'll use the value given by \.{/EDITOR}. If the editing of the file has (or could have) created a new version of the source file, then steps are taken to ensure that further edits all access the newly created file(s) rather than the original. @= function edit_file; {|( @!stack_item : in_state_record; line : integer ) : boolean|} var @!equivalence : packed array[1..file_name_size] of char; @!equv_len : signed_halfword; @!old_setting : integer; @!edit_status : edit_result; @!edit_ctr : integer; @!edit_found : integer; @@; begin old_setting:=selector; selector:=log_only; edit_file := false; edit_status:=failed; {Assume the worst!} equivalence:=edit_name; equv_len:=edit_len; if edit_qual then if equivalence[equv_len]=':' then begin equivalence[equv_len]:=' '; decr(equv_len); edit_qual:=translate(equivalence,equv_len); end; if edit_qual then @; if edit_status<>failed then begin edit_file := true; if edit_status=edited then @ end; selector:=old_setting; end; @ If the logical \.{TEX\_EDIT} has a suitable translation, we attempt to @.TEX_EDIT@> identify the ``preferred'' editors (preferred in the sense that they can be invoked from a shareable image, without the overhead of spawning a new process). @= begin print_nl("Issuing the following command:"); @.Issuing the following command:@> @; @; if edit_found<>0 then @ else @; copy_err:=ignore_it; selector:=old_setting; end @ The equivalence string for \.{TEX\_EDIT} needs to be converted to upper-case, @.TEX_EDIT@> to ensure that it may be matched to the names of the preferred editors. @= for edit_ctr:=1 to equv_len do if equivalence[edit_ctr] in ['a'..'z'] then equivalence[edit_ctr] := xchr[xord[equivalence[edit_ctr]]+"A"-"a"] @ Now that we have the equivalence string in upper-case, we attempt to match it with the names of the preferred editors in the data structure |editor|. For testing equality between two strings, we use VAX-\PASCAL's |index| function. @d VAX_index==@= index@> @= edit_ctr:=1; edit_found:=0; while (edit_ctr<=max_editor) and (edit_found=0) do begin if VAX_index(editor[edit_ctr].logical,equivalence) = 1 then edit_found:=edit_ctr; incr(edit_ctr) end; @ Well, we now know that the user wishes to use one of the supported \\{callable} editors. So the next move is to construct suitable command strings and invoke the editor from the appropriate shareable image. @= with editor[edit_found] do begin rewrite(temp_file); copy_err:=save_it; print_nl(cmd_text); if start_qual then with stack_item do edit_locate(line,loc_field-start_field+1); if edit_found=EDT_editor then @; if edit_found=TECO_editor then @; print(stack_item.name_field); copy_err:=ignore_it; selector:=old_setting; if EDT_like then begin edit_status := Edit(stack_item.name_field,cmd_file,editor[edit_found]); @ end else edit_status := Edit(0,0,editor[edit_found]); end @ The common-or-garden \.{EDT} editor doesn't have a qualifier to specify the starting position, so we create a small command file, and specify its name on the \.{/COMMAND} qualifier for \.{EDT} The command file contains line-mode commands to position the cursor appropriately. Strictly speaking, it is illegal to issue a \.{CHANGE} command (which is the only one that accepts no-keypad commands to position the cursor) except from a terminal, and \.{EDT} will display a message about this when it executes the command from the command file; however, it \\{does} honour the command correctly, so the end does justify the means! It seemed too complicated to try to delve into \TeX's ``whatsits'', and yet we'll want to use |print|, etc, to transfer text into the file. Previous versions of the VMS implementation tried to create the file using the first free |file| in the array |write_file|. But this approach failed, if \TeX\ has got all sixteen available files in use (although this is a rare case). To prevent this interference with TeX's own use of its output streams, the present solution uses a dedicated file |edcmd_file| for creating the editor command file. It is access by setting |selector| to the additional mode |edcmd_write|. @= begin name_of_file:='TEX_EDTINI'; default_name:='.EDT'; if a_open_out(edcmd_file) then begin cmd_file:=make_name_string; equivalence:='EDTINI'; equv_len:=6; {If it's defined} if not translate(equivalence,equv_len) then equv_len:=6; copy_err:=ignore_it; selector:=edcmd_write; print("SHOW COMMAND"); print_ln; print("CHANGE "); print_int(line); print_char(";"); with stack_item do print_int(loc_field-start_field); print("(+C)"); print_ln; print("SET MODE CHANGE"); print_ln; print("SET COMMAND "); for kkk:=1 to equv_len do print_char(xord[equivalence[kkk]]); a_close(edcmd_file); copy_err:=save_it; selector:=log_only; print("/COMMAND="); print(cmd_file); print_char(" "); end end @ Here are the other variables used in the above module: @= @!kkk : integer; @!cmd_file : str_number; @ Neither does the \.{TECO} editor accept such a qualifier, so again we create a suitable command file. @= begin name_of_file:='TEX_TECOINI'; default_name:='.TEC'; if a_open_out(edcmd_file) then begin cmd_file:=make_name_string; equivalence:='TEC$INIT'; equv_len:=8; {If it's defined} copy_err:=ignore_it; selector:=edcmd_write; if translate(equivalence,equv_len) then begin if equivalence[1]='$' then begin print("EI"); for kkk:=2 to equv_len do print_char(xord[equivalence[kkk]]); end else for kkk:=1 to equv_len do print_char(xord[equivalence[kkk]]); print_char(@"1B); print_ln; end; print("@@^U1/"); print_int(line); print("U0"); with stack_item do print_int(loc_field-start_field); print("U20U1<(Q1+1)U1(Q0-Q1-1):;L(.-Z)""LF>'^E""L(Q1+1)U1'P>Q2CT/"); print_char(@"1B); print_char(@"1B); print_ln; a_close(edcmd_file); copy_err:=save_it; selector:=log_only; print("/COMMAND="); print(cmd_file); print_char(" "); @ end end @ Unfortunately, the present version (V40.36) of \.{TECO} does not appear to make use of the third parameter (which is supposed to be the name of an initialization file). Therefore, we create (or redefine) the logical name \.{TEC\$INIT}, which the callable version of TECO will then use. Afterwards, of @.TEC{\$}INIT@> course, we have to put things back as they were, since otherwise a further invocation of the editor would introduce a circularity. The requirement for \.{TEC\$INIT} is that its first character shall be a dollar sign (`\.\$') to indicate that the rest of the logical name gives the name of a file to be used for initialization. @d VAX_create_logical==@= $crelnm@> @= begin TECO_cmd := '$'; kkk:=str_start[cmd_file]; while kkk= @!TECO_cmd : [VAX_volatile] varying [file_name_size] of char; @!item_list : [VAX_volatile] array [0..1] of VMS_item_list; @ After \.{EDT} or \.{TECO} has completed its editing, we are at liberty to delete the command file that was used to direct the cursor to the appropriate place. We've got the full file specification saved up from when the file was created, so we can go ahead and use the VAX-\PASCAL\ |delete_file| command to remove the file. @d VAX_delete_logical==@= $dellnm@> @d VAX_delete_file ==@= delete_file@> @= begin if edit_found=TECO_editor then begin if equv_len>0 then begin with item_list[0] do begin buffer_length := equv_len; item_code := VAX_lnm_string; buffer_addr := VAX_address_of(equivalence); ret_len_addr := 0; end; item_list[1].next_item := 0; VAX_create_logical(,'LNM$PROCESS_TABLE','TEC$INIT',,item_list); end else VAX_delete_logical('LNM$PROCESS_TABLE','TEC$INIT'); end; VAX_delete_file(last_name) end @ Once a source file has been edited, any further calls of an editor should access the latest version of the source file, rather than that first opened by \TeX. Therefore, as a crude approximation to this desired outcome, we truncate the file specification held in the pool by substituting spaces for the `\.;' and any characters that follow it in there. (This is a good approximation, since generally any revised file will have been written out to the next higher version number, and the method adopted is easier than trying to shuffle all of the pool down to fill the vacant space.) @= begin had_semicolon := false; for next_ch := str_start[stack_item.name_field] to str_start[stack_item.name_field+1]-1 do begin if str_pool[next_ch] = si(";") then had_semicolon := true; if had_semicolon then str_pool[next_ch] := si(" ") end; end @ Here's the necessary global variables for the previous module: @= @!next_ch : pool_pointer; @!had_semicolon : boolean; @ If we were unable to recognize the equivalence string for the \.{TEX\_EDIT} @.TEX_EDIT@> logical name, it's assumed to be a DCL command (most probably preceded by an `\.@@' to invoke a command procedure). The command will be run in a sub-process, and provided with three parameters: the name of the file to be edited, and the row and column numbers (starting from 1) of the file at which the error was detected. The following code constructs the requisite DCL command ready to be passed to the spawned sub-process by procedure |Edit|. As for the callable editors above, this command is constructed in the \PASCAL\ internal file |temp_file|, using various print commands. @= begin rewrite(temp_file); copy_err:=save_it; print_ln; for kkk:=1 to equv_len do print(xord[equivalence[kkk]]); print(" "); print(stack_item.name_field); print(" "); print_int(line); print(" "); with stack_item do print_int(loc_field-start_field+1); edit_status := Edit(0,0,empty_editor); end @ Here's a dummy |editor| structure to be passed to |Edit| for non-callable editors: @= @!empty_editor : editor_ident; @ and its initialization: @= with empty_editor do begin logical := ''; image := 0; entry := 0; quitting := 0; exiting := 0; cmd_text := 0; cmd_offset := 0; start_qual := false; EDT_like := false; end; @z