.MCALL .MODULE .MODULE LET,VERSION=18,COMMENT=,AUDIT=YES ; Copyright (c) 1998 by Mentec, Inc., Nashua, NH. ; All rights reserved ; ; This software is furnished under a license for use only on a ; single computer system and may be copied only with the ; inclusion of the above copyright notice. This software, or ; any other copies thereof, may not be provided or otherwise ; made available to any other person except for use on such ; system and to one who agrees to these license terms. Title ; to and ownership of the software shall at all times remain ; in Mentec, Inc. ; ; The information in this document is subject to change without ; notice and should not be construed as a commitment by Digital ; Equipment Corporation, or Mentec, Inc. ; ; Digital and Mentec assume no responsibility for the use or ; reliability of its software on equipment which is not supplied ; by Digital or Mentec, and listed in the Software Product ; Description. .SBTTL Abstract and Edit History ; ; This program is an unsupported "CCL" program used to load the ; substitution table in SL.SYS. ; ; Author: Jim Williams, DEC ; ; Changes: ; ; 03 11-Oct-83 JFW reject ctrl chars; allow spaces in definitions; ; allow lowercase (at LET> prompt); change message ; to SY: Write locked ... ; ; 07 13-Aug-85 JFW change table layout ; ; 08 09-Mar-87 RHH Update H.TYPE and H.DATA to conform with SYSLIB ; definitions in .DREST ; ; 09 01-Jul-88 RHH Add function key support ; ; (016) 06-Jun-90 MBG Removed case insensitivity, upper and lower case ; characters are now different for purposes of ; definitions. ; ; 17 01-Nov-90 JFW bracket error messages with ;+/;ERROR/.../;- ; ; 18 17-Jun-91 JFW Change ILLEGAL to INVALID .SbTtl Macro Calls and definitions .Enable LC .NList BEX,CND .MCall .DStat .Enter .Exit .Fetch .GtLin .GVal .MCall .LookUp .Print .ReadC .ReadW .SetTop .SpFun .MCall .TtyOut .WritC .WritW .Br .Assume .Ckxx .MCall SOB ; remove this if running on new machines ; only (those that support SOB) .Macro ...... .EndM .Macro .Disable a,b,c,d,e,f .Dsabl a b c d e f .EndM .Macro Jcs Dest,?L1 Bcc L1 Jmp Dest L1: .EndM .SbTtl Equate definitions Block =: 512. ; size in bytes of a disk block HT =: 011 ; Ascii Horizontal Tab LF =: 012 ; Ascii Line Feed CR =: 015 ; Ascii Carriage Return CTRL.Z =: 032 ; Control-Z Space =: 040 ; Ascii Space LQuote =: 137 ; LET Quote char (_) NoCrLf =: 200 ; No CRLF .Print terminator LC2UC =: 040 ; value to BIC to change lowercase ; to uppercase ; Handler references H.TYPE =: 70 ; Handler's data area TYPE (R50) H.DATA =: 72 ; pointer to data area ; following pointed to by H.DATA ; and returned by copy let impure TabId =: 0 ; table begins with table ID IdVal =: ^rSLL ; the expected value is "SLL" rad50 LetNum =: 2 ; number of let entries (byte value) LetSiz =: 3 ; length of a let entry (byte value) ; follows LetNum LetSbl =: 4 ; symbol vector (bytes) ; follows LetSiz Upd$Fn =: 372 ; SpFun handler Update function CLet$S =: 20 ; copy LETImp Subfunction dLET =: 1016 ; LET flag is next byte ; next byte reserved ; SYSCOM references JSW =: 44 GtLin$ =: 10 ; non-terminating .GtLin TTLC$ =: 40000 ; pass lowercase chars .Save .ASect .=JSW .Word TTLC$ ; always allow lowercase .Restore ; RMON references Suffix =: 412 ; handler file suffix (Rad50) SpFChn =: 0 ; channel open to SL: FilChn =: 1 ; channel open to SY:SL_.SYS .SbTtl Error message processing .Enable LSB Debug:: BPT Br Start ............. ;+ ;ERROR NSLErr: Mov #NSLMsg,R1 Br Fatal ............. FetErr: Mov #FetMsg,R1 Br Fatal ............. EntErr: Mov #EntMsg,R1 Br Fatal ............. LukErr: Mov #LukMsg,R1 Br Fatal ............. ReaErr: Mov #ReaMsg,R1 Br Fatal ............. NoLErr: Mov #NoLMsg,R1 Br Fatal ............. ISLErr: Mov #ISLMsg,R1 .Br Fatal Fatal: ; process fatal errors .Print #FatMsg ; fatal error prefix .Print R1 ; rest of message .Exit ...... ;- .SbTtl Initialization .Enable LSB Start:: Mov Top,R1 ; get top address of program Mov #R50SL,R2 ; point to device name (physical) .DStat #DStat+1,R2 ; check on SL Bcs NSLErr ; not a valid handler Tst DStat+4 ; is it loaded? Bne 10$ ; yes Mov DStat+2,R0 ; need space for handler Call GetMem ; get memory .Fetch R1,R2 ; fetch it Bcs FetErr ; failed Mov R0,R1 ; new top address 10$: Mov #Block*2,R0 ; top of buffer request Call GetMem ; get memory Mov #EmtBlk,R5 ; point to general EMT arg block .Assume SpFChn EQ 0 .Enter #PEnter,#0,R2 ; access SL Non-File-Structured Bcs EntErr ; failed .GVal R5,#Suffix ; get handler suffix value ;;; Bcs ??? Add R0,SLDBlk+2 ; fix name in DBlk .LookUp R5,#FilChn,#SLDBlk ; access the SL_.SYS file Bcs LukErr ; failed .ReadW #PReaWr,#FilChn,R1,#Block*2/2,#0 ; read blocks 0 and 1 Bcs ReaErr ; failed Mov R1,R2 ; get address of buffer Cmp H.TYPE(R2),#<^RSL > ; Double check data table type Bne NoLErr ; Report as No LET support Mov H.DATA(R2),R3 ; Get LET Impure Data Address Beq NoLErr ; No LET support MovB dLet(R2),LetFlg ; save the dLET flag Mov R3,-(SP) ; save offset part Bic #^c1777,@SP ; clear out block number ; actually remember odd/even block SwaB R3 ; swap the high byte to low Asr R3 ; and get block number Bic #^c177,R3 ; clear all but block number Cmp #1,R3 ; is it already in memory? Bhis 15$ ; yes, don't bother to read again .ReadC #PReaWr,,,,,R3,Code=NoSet ; read in LetImp Blocks ; This is really a .ReadW (Completion set by previous .ReadW) Bcs ReaErr ; failed Bic #^c777,@SP ; clear all block bits 15$: Add (SP)+,R2 ; point to Let Impure area Tst DStat+4 ; was SL loaded? Beq 20$ ; no, then no SPFUN .Assume SpFChn EQ 0 .SpFun #PSpFun,#0,#Upd$Fn,R2,#-1,#CLet$S ; copy LetImp into buffer Bcc 20$ Jmp NoLErr 20$: .CKXX R2 CK.R2=TabId CK.R2 TabId,+2 Cmp #IdVal,(R2)+ ; is this the SL table? Beq 30$ Jmp ISLErr ; no CK.R2 LetNum,+1 30$: MovB (R2)+,R5 ; number of Let entries CK.R2 LetSiz,+1 MovB (R2)+,R4 ; length of value CK.R2 LetSbl Mov R2,LetSym ; address of symbol vector Add R5,R2 ; point to value array Mov R2,LetVal ; address of value array .Br GetCmd .Disable LSB .SbTtl Processing Loop .Enable LSB GetCmd: Mov #CmdBuf,R1 ; point to command buffer .GtLin R1,#Prompt ; ask for input TstB @R1 ; null command? Bne 10$ ; no Mov #NlCsi,R0 ; print ident PriGet: .Print ; print message, get next command Br GetCmd ; and get another command ............. 10$: Mov R1,R2 ; copy command buffer pointer for use Mov R1,R3 ; copy command buffer pointer for use TstB -(R3) ; adjust MovB #,-(SP) ; put the space char on the stack 20$: ; skip spaces, tabs, and "LET Quotes" TstB (R3)+ ; point to next CmpB #,@R3 ; is it a Tab? Bne 30$ ; no MovB #,@R3 ; yes, substitute a space 30$: CmpB @SP,@R3 ; is it a Space? Beq 20$ ; yes, skip it CmpB #,@R3 ; is it a "Let Quote"? Beq 20$ ; yes, skip it CmpB #'=,@R3 ; is it an "=" Bne 40$ ; yes, allow spaces MovB #377,@SP ; by making "space" an impossible char 40$: CmpB #,@R3 ; it is a legal char? Blos 50$ ; yes TstB @R3 ; is it null? Bne ChrErr ; no, a random control char 50$: MovB @R3,(R2)+ ; else copy it Bne 20$ ; copy up to NULL TstB (SP)+ ; clean up stack CmpB @R1,#'/ ; is it a switch? Beq Switc1 ; yes, process it CLR R2 ; clear F-key flag/accumulator MOVB (R1)+,R3 BIC #LC2UC,R3 CMPB R3,#'F ; possible function key? BNE 80$ ; branch if not 60$: CMPB @R1,#'0 ; Fnn=? or Fnn/? ? BLO 70$ ; branch out if not a digit CMPB @R1,#'9 BHI 70$ ; branch out if not a digit MOVB (R1)+,R0 ; get the digit BIC #177760,R0 ; get its value MOV R2,-(SP) ASL R2 ; multiply previous by 10. ASL R2 ADD (SP)+,R2 ASL R2 ADD R0,R2 ; add digit's value BR 60$ ; keep doing this. 70$: TST R2 ; no digit after F? BEQ 80$ CMP R2,#6 ; Range-check F-key value BLO FUNERR CMP R2,#20. BHI FUNERR CMP R2,#10. BLOS 80$ ; between 6 and 10 CMP R2,#17. BHIS 80$ ; between 17 and 20 CMP R2,#14. ; 14? BEQ 80$ BR FUNERR Switc1: BR Switch ; (bucket brigade) 80$: CmpB #'/,@R1 ; is it ?/?????? Bne 90$ JMP SymDel 90$: CmpB #'=,@R1 ; is it ?=?????? Bne SynErr ; no, syntax falls due (thru?) Br Assign ChrErr: CMPB @R3,#CTRL.Z BNE 100$ .EXIT ;+ ;ERROR 100$: Mov #ChrMsg,R1 Br Fatal1 .............. ;- .Disable LSB .SbTtl Process an "assignment" .Enable LSB Assign: Mov R1,R0 ; copy pointer to '=' TST R2 ; is reference to function key? BEQ 5$ ; branch if not ADD #200,R2 ; make it an 8-bit ctrl char BR 7$ 5$: MovB -(R1),R2 ; get symbol character 7$: Inc R0 ; point to value Mov R0,R1 ; save address Clr R3 ; clear counter 10$: Inc R3 ; count chars TstB (R0)+ ; including NULL Bne 10$ ; until NULL Cmp R3,R4 ; will it fit Bgt LenErr ; no Mov R5,R3 ; load number of entries Mov LetSym,R0 ; load address of symbol vector Mov #-1,EmptyN ; indicate no empty found (yet) 20$: TstB @R0 ; empty entry? Bne 30$ ; no Mov R3,EmptyN ; yes, save number 30$: CmpB R2,(R0)+ ; try to match symbol Beq 40$ ; found it Sob R3,20$ ; else try all Mov EmptyN,R3 ; not found use empty Bmi EmpErr ; no room, no empties 40$: Neg R3 ; calculate entry number Add R5,R3 ; for finding offset into value Mov R3,-(SP) ; save entry number Add LetSym,R3 ; point to symbol location MovB R2,@R3 ; put it in Mov LetVal,R0 ; point to value array Mov (SP)+,R3 ; restore entry number Beq 60$ ; 0, first entry 50$: Add R4,R0 ; skip entry Sob R3,50$ ; until enough skipped 60$: 70$: MovB (R1)+,(R0)+ ; copy new string in Bne 70$ ; ASCIZ SetSL: .WritC #PReaWr ; write it back ;This is really a .WritW (Completion set by previous .ReadW) Bcs WriErr ; failed Tst DStat+4 ; was SL loaded? Beq 80$ ; no, then no SPFUN .SpFun #PSpFun,,,,#+1,,,CODE=NoSet ; copy buffer into LetImp Jcs NoLErr ; failed 80$: GetCm1: JMP GetCmd ; and done .............. ;+ ;ERROR WriErr: Mov #WriMsg,R1 Fatal1: Jmp Fatal ............. FUNERR: .PRINT #FUNMSG ;- ADD #200,R2 CALL PRISYM MOV #NLMsg,R0 BR PRIGE1 ;+ ;ERROR SynErr: .Print #SynMsg Mov #CmdBuf,R0 PriGe1: JMP PriGet .............. LenErr: Mov #LenMsg,R1 Br Error .............. EmpErr: Mov #EmpMsg,R1 Br Error .............. ;- .Disable LSB .SbTtl Switch processing .Enable LSB Switch: INC R1 MovB @R1,R0 ; get switch letter Mov LetSym,R1 ; point to symbol vector Mov LetVal,R2 ; point to value array Bic #LC2UC,R0 ; force uppercase CmpB #'D,R0 ; is it /D? Beq Delete ; yes CmpB #'H,R0 ; is it /H? Beq Help ; yes CmpB #'L,R0 ; is it /L? Beq List ; yes ;+ ;ERROR Mov #SwiMsg,R1 .Br Error ;- .SbTtl Error Processing Error: .Print #ErrMsg ; Error error prefix Mov R1,R0 ; point to rest of message PriGe2: Br PriGe1 .............. .Disable LSB .SbTtl . SymDel -- clear an entry in the substitution table .Enable LSB SymDel: Mov R1,R0 ; copy pointer to '/' TST R2 ; is reference to function key? BEQ 5$ ; branch if not ADD #200,R2 ; make it an 8-bit ctrl char BR 7$ 5$: MovB -(R1),R2 ; get the symbol to delete 7$: Inc R0 ; point to char following '/' BicB #LC2UC,@R0 ; force uppercase CmpB #'D,@R0 ; is it ?/D? Bne SynErr ; no, error Mov LetSym,R1 ; point to symbol vector Mov R5,R0 ; load number of entries 10$: CmpB (R1)+,R2 ; is this the symbol? Beq 20$ ; yes Sob R0,10$ ; try all of them ;+ ;ERROR .Print #SymMsg ; symbol not found ;- CALL PRISYM ; print the symbol Mov #NLMsg,R0 ; point to CRLF message PriGe3: Br PriGe2 ; and print ... .............. 20$: ; found the entry ClrB -(R1) ; clear it out SetSL1: Br SetSL ; write new SL data .............. GetCm2: Br GetCm1 .............. .Disable LSB .SbTtl . Delete -- clear all entries in the substitution table .Enable LSB Delete: Mov #CmdBuf,R0 ; point to command buffer again 10$: CmpB #':,@R0 ; check for /D[ELETE]:ALL Beq 20$ ; found : TstB (R0)+ ; end of buffer? Bne 10$ ; no, keep looking Br 30$ ; no /D:ALL ........... 20$: TstB (R0)+ ; Skip : BicB #LC2UC,@R0 ; uppercase it CmpB #'A,(R0)+ ; is it :A? Bne 30$ ; no BicB #LC2UC,@R0 ; uppercase it CmpB #'L,(R0)+ ; is it :AL Bne 30$ ; no BicB #LC2UC,@R0 ; uppercase it CmpB #'L,@R0 ; is it :ALL? Beq 40$ ; yes, clear it out 30$: Mov #CmdBuf,R2 ; point to buffer Bis #GtLin$,@#JSW ; bypass any ^C .GtLin R2,#RUSure,TERM ; ask for permission Bic #GtLin$,@#JSW ; back to normal BicB #LC2UC,@R2 ; force uppercase CmpB #'N,@R2 ; NO? Beq GetCm2 ; yes, skip it CmpB #'Y,@R2 ; YES? Bne 30$ ; no, ask again 40$: Mov R5,R0 ; load number of entries 50$: ClrB (R1)+ ; clear out the vector Sob R0,50$ ; the whole thing ;+ ;ERROR .Print #AllMsg ; indicate done Br SetSL1 ; update handler ............. ;- .Disable LSB .SbTtl . Help -- provide help info .Enable LSB Help: .Print #NlCsi ; print program ID Mov #HlpMsg,R0 ; easy (here) PriGe4: Br PriGe3 ; and done .............. .Disable LSB .SbTtl .List -- display substitution definitions .Enable LSB List: .Print #Header ; print header (like RESORC) Mov R5,R3 ; number of entries Call SortTb ; Sort the table ; Display the entries Mov R3,-(SP) ; and copy for "empties" count 10$: TstB @R1 ; assigned? Beq 20$ ; no .Print #Space2 ; center it MOV R2,-(SP) MOVB @R1,R2 ; get the character CALL PRISYM ; print it MOV (SP)+,R2 Dec @SP ; reduce empties count .TtyOut # ; tab to value area .Print R2 ; print value 20$: Inc R1 ; point to next symbol Add R4,R2 ; and next value Sob R3,10$ ; do all of them .Print #Trailr ; more formatting Mov (SP)+,R0 ; get empty count Add #'0,R0 ; convert to single decimal number ;;;NOTE: this assumes 0--9 are only valid values .TtyOut ; print digit .Print #Empty ; and rest of empties message ; then start of SET SL message MovB LetFlg,R2 ; is it LET or NOLET? (and save flag) Call ShoLet ; print body of LET flag message Mov DStat+4,R1 ; address of handler Beq 30$ ; no memory copy MovB dLet-1000-6(R1),R1 ; get memory copy of Let flag CmpB R1,R2 ; same status (memory and disk)? Beq 30$ ; yes, just end it .Print #OnDisk ; indicate on disk copy of flag TstB R1 ; what is the memory flag value? Call ShoLet ; print body of Let flag .Print #InMem ; indicate in memory copy of flag 30$: Mov #NlMsg,R0 ; and new line Br PriGe4 ; and done .............. .Disable LSB .Enable LSB ShoLet: Bne 10$ ; LET .Print #NoMsg ; print NO 10$: .Print #SeZMsg ; and print last part Return ...... .Disable LSB .ENABL LSB ; Print a symbol name. The character or function key code is in R2 PRISYM: CMPB R2,#200 ; Function Key? BLO 10$ ; branch if not MOVB #'F,R0 ; display "F" .TTYOUT BIC #177600,R2 ; take off silly marker bit CALL DECIMA ; display F-key number BR 20$ ; now resume 10$: .TtyOut R2 ; print plain character symbol 20$: RETURN .DSABL LSB GetMem: ; get memory required by count in R0 Mov R1,R3 ; copy top address Add R0,R3 ; calculate room needed to fetch it .SetTop R3 ; ask for it Cmp R0,R3 ; did we get it? Bne MemErr ; no RtsPC: Return ...... ;+ ;ERROR MemErr: Mov #MemMsg,R1 Jmp Fatal ; stack is unaligned ............. ;- .Enable LSB UCR2: CmpB #'a,R2 ;Is it lower-case alphabetic? Bhi 10$ ;Nope... CmpB #'z,R2 ;Maybe, check upper limit Blo 10$ ;Nope... Bic #LC2UC,R2 ;Yes, force character to upper case 10$: Return ...... .Disable LSB .SBTTL DECIMA - Binary to Decimal conversion routine ;+ ; This routine converts a binary number stored in R2 to a decimal ; ASCII representation and prints it on the terminal ; ; R2 = Binary number to be printed ; CALL DECIMA ; ;- .ENABL LSB ; Decimal-to-ASCII, R2=num DECIMA::MOV R2,-(SP) ; Store the value CLR R2 ; Serve as counter 20$: INC R2 ; Count one SUB #10.,@SP ; Divide by repetive subtract BHIS 20$ ; Branch if not minus ADD #10.+60,@SP ; Restore the remaining number DEC R2 ; Decrement counter BEQ 30$ ; If = 0 finish CALL DECIMA ; Repeat if not 30$: MOV (SP)+,R0 .TTYOUT RETURN ; Keep printing till return address .DSABL LSB .SBTTL Sort the LET table by symbol value ;+ ; Sort the entries in place by their symbol value ; ; On entry, R1 points to the symbol list ; R2 points to the first value string ; R3 contains the number of table entries ; R4 contains the length of each string ; R5 contains the number of table entries ; ; All registers except R0 are preserved ;- .ENABL LSB SORTTB: DEC R3 ; comparisons = entries - 1 BEQ 60$ ; only one entry? don't sort. MOV R5,-(SP) ; save whatever MOV R1,-(SP) ; save the symbol pointer MOV R2,-(SP) ; push the 1st string pointer 10$: MOV R3,LOOP1 ; this many compares this pass MOV 2(SP),R1 ; point to 1st symbol MOV @SP,R2 ; point to 1st string (again) MOV R2,R5 ADD R4,R5 ; use r5 as 2nd string pointer 20$: MOVB (R1)+,R0 ; get a symbol CMPB @R1,R0 ; compare it with the next BHIS 40$ ; if already in order, skip. MOVB @R1,-1(R1) ; otherwise, MOVB R0,@R1 ; swap the entries MOV R4,R0 ; for this many characters, 30$: MOVB @R2,-(SP) ; swap the value contents MOVB @R5,(R2)+ MOVB (SP)+,(R5)+ DEC R0 BGT 30$ BR 50$ ; done swapping value 40$: ADD R4,R2 ; point to next string1 ADD R4,R5 ; point to next string2 50$: DEC LOOP1 ; done with one compare BGT 20$ DEC R3 ; done with one pass BGT 10$ ; do subsequent passes or drop MOV (SP)+,R2 ; restore value pointer MOV (SP)+,R1 ; restore symbol pointer MOV (SP)+,R5 ; restore the count 60$: MOV R5,R3 ; re-get the count RETURN .DSABL LSB .SbTtl Data Area SLDBlk: ; DBLK for handler .Rad50 "SY " ; System device R50SL: ; Handler name for Non-File Enter .Rad50 "SL " ; file name (suffix is added) .Rad50 "SYS" ; type Bottom: .Limit ; program address limits Top =:.-2 ; top address is second word PEnter: ; Emt Block for NFS Enter .BlkW 4 .Word RtsPC+1 ; Physical Enter (skip Logicals) FatMsg: .NlCsi PART=PREFIX,TYPE=I .Ascii "F-" ;+ ;ERROR NSLMsg: .Asciz "SL not installed" ISLMsg: .Asciz "Unable to find SL ident in data table" MemMsg: .Asciz "Insufficient Memory" FetMsg: .Asciz "Fetch failed for SL" EntMsg: .Asciz "Enter failed for SL" LukMsg: .Asciz "File not found SY:SLx.SYS" ReaMsg: .Asciz "Input error SY:SL_.SYS" WriMsg: .Asciz "SY: write locked" NoLMsg: .Asciz "This SL_.SYS does not support LET" FunMsg: .NlCsi PART=PREFIX,TYPE=I .Ascii "E-Invalid function key " SynMsg: .NlCsi PART=PREFIX,TYPE=I .Ascii "E-Syntax error, expecting x=string, found - " SymMsg: .NlCsi PART=PREFIX,TYPE=I .Ascii "E-Unable to delete, symbol not found - " ChrMsg: .Asciz "Invalid control character" LenMsg: .Ascii "String too long" NLMsg: .Asciz "" ErrMsg: .NlCsi PART=PREFIX,TYPE=I .Ascii "E-" EmpMsg: .Asciz "No space for new symbol" SwiMsg: .Asciz "Unknown switch" AllMsg: .NlCsi PART=PREFIX,TYPE=I .Asciz "I-all symbols deleted" ;- HlpMsg: .Ascii .Ascii "LET [_]x=string""substitutes 'string' for 'x'" .Ascii "LET Fn=string""substitutes 'string' for Function Key n" .Ascii "Note: '_' is used to inhibit substitution for 'x'" .Ascii "x/D[elete]""clears definition of 'x'" .Ascii "/D[elete]:ALL""clears all definitions" .Ascii "/H[elp]""prints this help text" .Asciz "/L[ist]""displays current definitions" Header: .Ascii "Symbol"" Value" .Asciz "------""--------------------------------" Trailr: .Ascii " " Space2: .Ascii " " Empty: .Ascii " empty entries""SET SL " NoMsg: .Ascii "NO" SeZMsg: .Ascii "LET is in effect" OnDisk: .Ascii " (on disk)""SET SL " InMem: .Ascii " (in memory)" Prompt: ; GtLin prompt string .NlCsi PART=NAME,TYPE=I .Ascii ">" NlCsi: .NlCsi ; Id string RUSure: .Ascii "LET /Delete:ALL; Are you sure?" CmdBuf: .BlkB 81. ; command buffer .Even DStat: ; DStat reply area .BlkW 1 ; status .BlkW 1 ; handler size (Read/Write buffer adr) .BlkW 1 ; load address .BlkW 1 ; device size PSpFun: .BlkW 6 ; .SpFun argument block PReaWr: .BlkW 5 ; .Read/WritW argument block EmtBlk: .BlkW 4 ; general argument block LetSym: .BlkW 1 ; address of Symbol vector LetVal: .BlkW 1 ; address of Value array EmptyN: .BlkW 1 ; number of empty or matching entry LetFlg: .BlkB 1 ; copy of dLET from SL.SYS .even LOOP1: .WORD 0 ; Temporary variable for SORTTB .End Start