SUBTTL Revision History ;NOTE: PLTUNV.UNV defines the following: ; TTL Macro to generate the TITLE statement ; T0-T4,P1-P4,X,Y All AC definitions ; FTMKTB Feature test for subroutine MKTBL ; REAL,INTEGER,STRING Data types ; $RELOC,$HISEG,$LOSEG Relocation macros ; FLOAT,ERRSTR,PFALL General macros SALL ;Edit ; 442 1980 JMS Separate SYMBOL, NUMBER, and ISETAB from the rest. ; This allowed the use of SYMBOL.DAT for plotting ; characters on the VERSATEC using standard calls to ; subroutine PLOT. ; ; 505 20-Oct-82 JMS Remove debugging HALT that limited X,Y to 11.0 inches. ; ; 506 20-Oct-82 JMS Implemented CR, LF, TAB, BS, SI, and SO characters. ; ; 512 29-Oct-82 JMS Implement subroutine SETSYM to replace ISETAB/MSETAB. ; ; 513 2-Nov-82 JMS Fix bug near ISETA6 introduced by edit 512 ; ; 514 9-Nov-82 JMS Do not special case CR, LF for centered symbols. ; ;End of Revision History SUBTTL Table of contents ; Table of Contents for SYMBOL plotter ; ; ; Section Page ; ; 1. Table of contents . . . . . . . . . . . . . . . . . . 2 ; 2. Subroutine Descriptions ; 2.1 ISETAB - Fake a call to SETSYM . . . . . . . . 3 ; 2.2 MKTBL - Make table from in-core array . . . . 4 ; 2.3 MSETAB - Fake a call to SETSYM . . . . . . . . 5 ; 2.4 NUMBER - Draw numbers on the plot . . . . . . 6 ; 2.5 SETABL - Change table for SYMBOL (DEC routin . 7 ; 2.6 SETSYM - Get data from SYMBOL.DAT . . . . . . 8 ; 2.7 SYMBOL - Plot symbols (letters, digits, etc) . 9 ; 3. NUMBER ; 3.1 Entry point . . . . . . . . . . . . . . . . . 10 ; 3.2 Convert floating point to ASCII . . . . . . . 13 ; 3.3 Variables . . . . . . . . . . . . . . . . . . 15 ; 4. Definitions for SYMBOL and MYPLOT . . . . . . . . . . 16 ; 5. SETSYM ; 5.1 Dispatch, 'QUERY' and 'WIDTH' . . . . . . . . 17 ; 5.2 'TABLE' - Change symbol tables . . . . . . . . 18 ; 5.3 Get table from SYMBOL.DAT . . . . . . . . . . 19 ; 6. SYMBOL ; 6.1 Get args, set up mode . . . . . . . . . . . . 20 ; 6.2 Set up translation and rotation . . . . . . . 21 ; 6.3 Main loop, do a character . . . . . . . . . . 22 ; 6.4 Control characters, CR, LF, etc . . . . . . . 24 ; 6.5 Variables . . . . . . . . . . . . . . . . . . 25 ; 7. ISETAB table #1 ; 7.1 Pointers . . . . . . . . . . . . . . . . . . . 26 ; 7.2 Data . . . . . . . . . . . . . . . . . . . . . 27 SUBTTL Subroutine Descriptions -- ISETAB - Fake a call to SETSYM SEARCH PLTUNV ;Search the universal file TTL () ; INTEGER FUNCTION ISETAB(ITABLE) ; CALL SETSYM ('TABLE',ITABLE,IERR) ; ISETAB = IERR ; RETURN ; END ;For a description of symbols, see SETSYM routine. ENTRY ISETAB ISETAB: MOVEI 0,ISET00 ;Functions must preserve ACs BLT 0,ISET00+L MOVE T1,@0(L) ;Get argument to ISETAB(ITABLE) MOVEM T1,ITABLE ;Store as 2nd arg to SETSYM ;*; ERRSTR (<[Function ISETAB has called subroutine SETSYM to change tables>) ;Call SETSYM directly to avoid the message MOVEI L,[-3,,0 ;3 args STRING IFUNC ;'TABLE' INTEGER ITABLE ;Postive or 0 table number INTEGER IERR ;Error flag ]+1 ;Point to args PUSHJ P,%SETSYM## ;Call the routine in SYMBOL module MOVSI L,ISET00 ;Restore ACs BLT L,L MOVE 0,IERR ;Return error flag as function value POPJ P, $LOSEG ;Variables ISET00: BLOCK 1+16 ;Place to store ACs 0-16 IFUNC: ASCII /TABLE/ ;Arg to change tables ITABLE: BLOCK 1 ;Positive number for ISETAB IERR: BLOCK 1 ;Returned error flag $HISEG PRGEND SUBTTL Subroutine Descriptions -- MKTBL - Make table from in-core array SEARCH PLTUNV ;Search the universal file IFN FTMKTB,< TTL (,DUMMY) ;Calling sequence: ; CALL MKTBL(ITABLE, IARRAY) ; ; ITABLE - The table to define. Integer from 1 to 15. ; IARRAY - Table of 128 pointers, the left half has the number of offsets ; in the character, the right half points to a string of 5 bit bytes ; in triplets (Pen up-down, X, and Y). ENTRY MKTBL MKTBL=%MKTBL## ;Defined in SYMBOL module PRGEND > ;End of IFN FTMKTB SUBTTL Subroutine Descriptions -- MSETAB - Fake a call to SETSYM SEARCH PLTUNV ;Search the universal file TTL () ; INTEGER FUNCTION MSETAB(ITABLE) ; CALL SETSYM ('TABLE',-ITABLE,IERR) !Negative ; MSETAB = IERR ; RETURN ; END ENTRY MSETAB MSETAB: MOVEI 0,MSET00 ;Functions must preserve ACs BLT 0,MSET00+L MOVE T1,@0(L) ;Get argument to MSETAB(ITABLE) MOVNM T1,ITABLE ;Store as 2nd arg to SETSYM (negated) ;*; ERRSTR (<[Function MSETAB has called subroutine SETSYM to change tables>) ;Call SETSYM directly to avoid the message MOVEI L,[-3,,0 ;3 args STRING IFUNC ;'TABLE' INTEGER ITABLE ;Postive or 0 table number INTEGER IERR ;Error flag ]+1 ;Point to args PUSHJ P,%SETSYM## ;Call the routine in SYMBOL module MOVSI L,MSET00 ;Restore ACs BLT L,L MOVE 0,IERR ;Return error flag as function value POPJ P, $LOSEG ;Variables MSET00: BLOCK 1+16 ;Place to store ACs 0-16 IFUNC: ASCII /TABLE/ ;Arg to change tables ITABLE: BLOCK 1 ;Negative number for MSETAB IERR: BLOCK 1 ;Returned error flag $HISEG PRGEND SUBTTL Subroutine Descriptions -- NUMBER - Draw numbers on the plot ;Calling sequence: ; CALL NUMBER (X, Y, HEIGHT, FNUMB, ANGLE, NDIG) ; CALL NUMBER (X, Y, HEIGHT, FNUMB, ANGLE, NDIG, IRAD) ; ; (X,Y) - The coordinate of the first char to be drawn ; HEIGHT - The height of the numbers in inches ; FNUMB - The number for output (floating point real number) ; ANGLE - The angle of rotation ; NDIG - The number of digits beyond the decimal point ; IRAD - (optional) The output radix, from 2 to 36. ;Convert REAL number in FNUMB to a string of digits in NUMTXT, set NUMDIG, ; and then "CALL SYMBOL (X,Y,HEIGHT,NUMTXT,ANGLE,NUMDIG)". ;For example: ; Z = 3.141592653 ; CALL NUMBER(X,Y,0.2,Z,90.0,2) ;will draw '3.14' at 90 degrees. SUBTTL Subroutine Descriptions -- SETABL - Change table for SYMBOL (DEC routine) SEARCH PLTUNV ;Search the universal file IFN FTMKTB,< TTL (,DUMMY) ;Calling sequence: ; CALL SETABL (ITABLE, IFLAG) ; ; ITABLE - The table to define. An integer from 1 to 15, or 0. ; IFLAG - Set to 0 if table is defined, -1 if not. If ITABLE is zero ; IFLAG is returned as the number of the current table ; ; This routine is included for compatiblity with DEC routines, subroutine ;SETSYM should be used instead. Description of SETABL and MKTBL in MKTBL.DOC ENTRY SETABL SETABL=%SETABL## ;Defined in SYMBOL module PRGEND > ;End of FTMKTB SUBTTL Subroutine Descriptions -- SETSYM - Get data from SYMBOL.DAT SEARCH PLTUNV ;Search the universal file TTL (,DUMMY) ; This subroutine reads the SYMBOL table from either SYS:SYMBOL.DAT[1,4] ;or SYMBOL:SYMBOL.DAT[-], or returns information about the tables. ;NOTE: In order to use the negative tables, the user must define the ;logical device SYMBOL: via the ASSIGN or PATH commands to the Monitor. ;Calling sequence: ; CALL SETSYM(IFUNC,IARG,IANS) !The 3rd arg may be a REAL variable ; IFUNC = (input) Name of the function to perform ; IARG = (input) The argument of the function ; IANS = (output) Returned answer (not necessarily an integer) ; CALL SETSYM('TABLE',ITABLE,IERR) ; IFUNC = 'TABLE' - Change tables or return the value of the current one. ; ITABLE = The number of the table to be loaded into memory for SYMBOL. ; + = Positive values read from SYS:SYMBOL.DAT[1,4] ; - = Negative values read from SYMBOL:SYMBOL.DAT[-] ; 0 = ZSame as CALL SETSYM('QUERY',0,IANS) ; IERR = The error flag . Returned as 0 if no errors, as -1 if errors. ; CALL SETSYM('QUERY',0,IANS) ; IFUNC = 'QUERY' - Read the current table number. ; IARG = Ignored. ; IANS = The table number. Positive if the table was read from ; SYS:SYMBOL.DAT[1,4], negative if from SYMBOL:SYMBOL.DAT[-]. ; CALL SETSYM('WIDTH',LETTER,WIDTH) ; IFUNC = 'WIDTH' - Read the width for the specified letter. ; LETTER = The ASCII code for the character in question. "A"=65. ; WIDTH = The width as compared to the height, a number from 0.0 to 1.0. PAGE ;The tables defined in SYS:SYMBOL.DAT are: ; ; Description Upper Lower Number Punctu- Bracket Symbols ; case case ation [\]^_ #$%+-<=>@ ; -- -------------- ----- ----- ------ ------ ------- --------- ; 1. CSM standard Yes Yes Yes Yes Yes Yes ; 2. DEC standard Yes No Yes Yes Yes Yes ; 3. Olde English Yes Yes Yes Yes Yes $ only ; 4. Old German Yes Yes No No No No ; 5. Old Itialian Yes Yes No No No No ; 6. Script Yes Yes No No No No ; 7. Double line Yes Yes Yes Yes [] +-/<=> ; 8. Italics Yes Yes Yes Yes [] +-/<=> ; 9. Triple line Yes Yes Yes Yes No #$%+-= ; 10. Triple Italics Yes Yes Yes Yes No #$%+-= ; 11. Round letters Yes Yes Yes Yes No #$%+-= ; 12. Greek letters Yes Yes No No No No ; 13. Double Greek Yes Yes No No No No ;There are 26 centered symbols in SETSYM tables +1 and +2. ; 0 Square box 8 Z ; 1 Circle 9 Y ; 2 Triangle 10 Square star ; 3 Plus sign 11 Asterisk ; 4 X 12 Hourglass ; 5 Diamond 13 Vertical bar ; 6 Up arrow 14 Five pointed star ; 7 X with a bar on top 15 Horizontal bar ; 16-25 Digits 0 through 9, centered about the point ENTRY SETSYM SETSYM=%SETSYM## ;Defined in SYMBOL module PRGEND SUBTTL Subroutine Descriptions -- SYMBOL - Plot symbols (letters, digits, etc) ;Calling sequence: ; CALL SYMBOL (X, Y, HEIGHT, ICHAR, ANGLE, NUMCHR) ; ; (X,Y) - The coordinate of the first character to be drawn. ; HEIGHT - The height of the characters in inches. ; ICHAR - An array of characters to be plotted, or an integer number. ; ANGLE - The angle of rotation. ; NUMCHR - the number of characters to be plotted. ; If NUMCHR is zero, plot the single character whose ASCII code is in ICHAR. ; If NUMCHR is negative, plot a centered symbol whose number is in ICHAR. ; -2 will draw the symbol with a connecting line to the old position. ; Any other negative number will not draw the connecting line. ; ;For a description of symbols, see SETSYM routine above. EXTERN PLOT ;User's program must also request PLOT routine SUBTTL NUMBER -- Entry point SEARCH PLTUNV ;Search the universal file TTL () ;Definitions ND MAXCHR,^D30 ;Max number of digits sent to SYMBOL ND FTTYPE,0 ;Do not use $TYPE macro EXTERN SYMBOL,PLOT ;Call upon subroutine SYMBOL to do the plotting EXTERN EXP2. ;Math routine from FORLIB IFN FTKA, ;Convert REAL in T1 to INTEGER IFN FTTYPE,< SEARCH SYSUNV ;Get definition of $TYPE macro .REQUEST REL:TYPER ;Floating point conversion routine > A=P1 ;Preserved AC B=P2 ;Byte pointer C=P3 ;Counter D=P4 ;Data PURGE P1,P2,P3,P4 ;CALL NUMBER (X,Y,HEIGHT,FNUMB,ANGEL,NDIG,IRAD) ENTRY NUMBER ;Set up entry point SIXBIT /NUMBER/ ;For subroutine TRACE. NUMBER: MOVEM L,NUMB16 ;Save arg pointer ;Set up pointers to variables MOVEI T0,ARGLST-1 ;Set up to get the arguments PUSH T0,0(L) ;Get address of X PUSH T0,1(L) ;Get address of Y PUSH T0,2(L) ;Get address of HEIGHT PUSH T0,@3(L) ;Get value of FNUMB PUSH T0,4(L) ;Get address of ANGLE PUSH T0,@5(L) ;Get value of NDIG MOVE T1,[POINT 7,NUMTXT] ;Set up a pointer to MOVEM T1,NUMPNT ; the data array ;Get the output radix (IRAD) IFE FTTYPE,< HLRZ T1,-1(L) ;Get number of arguments on this call CAIE T1,-7 ;Skip if there are 7 arguments JRST NUMBE0 ;Assume radix ten output MOVE T1,@6(L) ;Get the radix to use CAIL T1,^D2 ;Keep it if between 2 CAILE T1,^D36 ; and 36 NUMBE0: MOVEI T1,^D10 ;Set number of the radix to 10 MOVEM T1,IRAD ;Save the radix for later ;Get number of digits beyond decimal point (NDIG) SKIPGE T1,NDIG ;Skip if number of digits beyond d. p. is positive ADDI T1,1 ;Add 1 to the number digits trucated CAILE T1,^D8 ;Skip if less than 9 digits behind the d. p. MOVEI T1,^D8 ;Set the number of digits to 8 MOVNM T1,NUMDIG ;Save negative as argument to EXP2. ;Convert number to string of characters in NUMTXT, put the count in NUMDIG PUSHJ P,N2TEXT ;Convert number to text > ;End of IFN FTTYPE IFN FTTYPE,< ;Create data for $NUMBER block for $TYPE macro MOVX T1,<+T2> ;Set up for the $NUM substitution ;Note: Regular floating point ; and a width of 0 MOVE T2,NDIG ;Get the number of fractional digits CAILE T2,^D8 ;Skip if less 9 fractional digits MOVEI T2,^D8 ;Assume 8 fractional digits CAIGE T2,^D0 ;Skip if an the decimal point is wanted MOVEI T2,NM%INT ;Output only the integer portion LSH T2,N%%DEC ;Put it in the correct place for OR T1,T2 ; floating-point output routine MOVE T2,FNUMB ;Get the number to output SETZM NUMDIG ;Reset the character count ;Convert number to string of characters in NUMTXT, put the count in NUMDIG $TYPE (N,,$NUM,<|>,N,,NUMOUT) > ;End of IFN FTTYPE ;Plot the data MOVE T1,[INTEGER NUMTXT] MOVEM T1,ARGLST+3 ;Point 4th arg to NUMTXT MOVE T1,[INTEGER NUMDIG] MOVEM T1,ARGLST+5 ;Point 6th arg to NUMDIG MOVEI L,ARGLST ;Point to arguments PUSHJ P,SYMBOL## ;Do the plotting MOVE L,NUMB16 ;Restore AC 16 CPOPJ: POPJ P, ;Return IFN FTTYPE,< ;Character output routine called by $TYPE NUMOUT: IDPB T1,NUMPNT ;Save the character AOS NUMCNT ;Increment the digit count POPJ P, ;Return > ;End of IFN FTTYPE SUBTTL NUMBER -- Convert floating point to ASCII IFE FTTYPE,< ;Use this routine instead of REL:TYPER.REL N2TEXT: FLOAT T1,IRAD ;Convert the radix to floating point MOVEM T1,FRAD ;Save for EXP2. MOVEI L,[-2,,0 ;2 args REAL FRAD ;Base INTEGER NUMDIG ;Power to raise base to ]+1 ;Point to args PUSHJ P,EXP2.## ;Raise floating-point base to integer exponent MOVE T1,T0 ;Duplicate the answer FSC T1,-1 ;Set up for rounding SKIPGE FNUMB ;Check to see if it's negative MOVNS T1 ;It was negative, therefore negate FADR T1,FNUMB ;Round the number to be used ;Convert number to properly scaled integer FDVR T1,T0 ;Produce a whole number in floating point IFN FTKA,< PUSHJ P,IFX.1## > ;Go convert the number to integer IFE FTKA,< FIX T1,T1 > ;Convert the number to integer JFCL .+1 ;Tell FOROTS to ignore %FRSAPR Integer Overflow AOS NDIG ;Set up to put the d. p. in the right place ;Convert integer to ASCII MOVSI C,-MAXCHR ;AOBJN pointer for character count PUSHJ P,RADOUT ;Go put the number into NUMTXT HRRZM C,NUMDIG ;Store number of characters POPJ P, ;Return from N2TEXT ;Convert integer to ASCII using radix in IRAD RADOUT: JUMPGE T1,RADOU0 ;Jump if the number is positive MOVNS T1 ;Make the number positive MOVEI D,"-" PUSHJ P,CHAR ;Put a '-' before the number RADOU0: SOSE NDIG ;Skip if a '.' should be output JRST RADOU1 ;Not yet MOVEI D,"." HRLM D,(P) ;Save the '.' for later PUSH P,[RADOU2] ;Set up so POPJ will do the right thing RADOU1: IDIV T1,IRAD ;Divide by proper radix MOVEI D,"0"(T2) ;Convert to ASCII CAILE D,"9" ;Skip if char is a digit ADDI D,"A"-"9"-1 ;Convert the char to a letter SKIPG NDIG ;Skip next test to output trailing zeros JUMPE T1,CHAR ;Jump and return if no more numbers for output HRLM D,(P) ;Store char on PDL PUSHJ P,RADOU0 ;Go get an other number RADOU2: HLRZ D,(P) ;Get char off PDL CHAR: AOBJP C,NUMERR ;Count characters IDPB D,NUMPNT ;Store a char POPJ P, NUMERR: MOVE D,[ASCII/*****/];Too many digits MOVEM D,NUMTXT ;Set up to display MOVEI C,5 ; 5 characters POPJ P, ;Unwind the stack SUBTTL NUMBER -- Variables $LOSEG ;Variables -6,,0 ;Six args for SYMBOL ARGLST: BLOCK 6 ;Argument pointers ;X0= ARGLST+0 ;Address of starting coordinates ;Y0= ARGLST+1 ; .. ;HEIGHT=ARGLST+2 ;Address of height FNUMB= ARGLST+3 ;The floating point number ;ANGLE= ARGLST+4 ;Address of angle NDIG= ARGLST+5 ;The number of digits to be plotted NUMB16: BLOCK 1 ;Save AC 16 IRAD: BLOCK 1 ;Radix, integer NUMPNT: BLOCK 1 ;Byte pointer to NUMTXT NUMDIG: BLOCK 1 ;Number of characters in NUMTXT NUMTXT: BLOCK MAXCHR/5 ;Room for 30 digits (including "-" and ".") IFE FTTYPE,< FRAD: BLOCK 1 > ;Radix, floating point IFN FTTYPE,< ;The $NUMBER argument block NUMBLK: NM%FLT_N%%TYP!NM%SNG_N%%DTP!NM%IMD_N%%DPT!NM%NRM_N%%%NOT!^D5_N%%FRC BLOCK 1 ;2nd word of $NUMBER block > ;End of IFN FTTYPE $HISEG LITS: PRGEND SUBTTL Definitions for SYMBOL and MYPLOT SEARCH PLTUNV ;Search the universal file TTL () EXTERN SIND., COSD., TRACE. ;Routines in FORLIB EXTERN PLOT ;Routine to move the pen ND SYMDEV,SIXBIT/SYS/ ;SYMBOL.DAT resides on SYS: ND %0,0 ;Temporary I/O channel for reading SYMBOL.DAT ND MAXSET,^D20 ;Maximum argument for SETSYM (^D127 is abs max) ND OLDVAL,999.0 ;Flag to continue where last symbol left off ND SETSIZ,^D12*200 ;Table can be up to 12 blocks long FT701==0 ;Do not use FILOP. with extended channels yet. IFE FT701,> ;ACs defined in PLTUNV A=P1 ;Preserved AC B=P2 ;Byte pointer C=P3 ;Counter D=P4 ;Data X=X ;Current position Y=Y ; ... PURGE P1,P2,P3,P4 SAVACL==A ;First AC to save before calling PLOT## SAVACH==Y ;Last " " " ;Interface to the PLOT routine. Destroys T1-T4, preserves A thru Y ;Call: ; MOVEI T1,ICODE ;PEN.UP or PEN.DN ; DMOVE X,[coordinates in inches] ; PUSHJ P,MYPLOT ; *return* MYPLOT: MOVE T1,[SAVACL,,SYMB00+SAVACL] BLT T1,SYMB00+SAVACH;Store X,Y,IC in memory MOVEI L,[-3,,0 ;Three args REAL PLOT.X ;X coordinate REAL PLOT.Y ;Y coordinate INTEGER PLOT.P ;Pen up/down code ]+1 ;Point to args PUSHJ P,PLOT## ;Go plot the segment MOVE T1,[SYMB00+SAVACL,,SAVACL] BLT T1,SAVACH ;Restore A,B,C,D,X,Y POPJ P, ;Return from MYPLOT SUBTTL SETSYM -- Dispatch, 'QUERY' and 'WIDTH' ; CALL SETSYM(IFUNC,IARG,IANS) ENTRY %SETSYM ;Set up entry point SIXBIT /SETSYM/ %SETSY: MOVEM L,SYMB16 ;Preserve AC 16 MOVE T1,@0(L) ;Get 1st arg ANDCM T1,[BYTE(7)40,40,40,40,40] ;Translate lower to uppercase ;(also converts spaces to nulls) MOVSI T2,-FUNLEN ;Set up AOBJN counter SETSY1: CAMN T1,FUNASC(T2) ;Match? JRST @FUNDSP(T2) ;Yes, do it AOBJN T2,SETSY1 ;Try next ERRSTR () PUSHJ P,TRACE.## ;Trace the subroutine calls POPJ P, FUNASC: ASCII /TABLE/ ;Change symbol tables ASCII /QUERY/ ;Return current table number ASCII /WIDTH/ ;Get width of a symbol FUNLEN==.-FUNASC FUNDSP: EXP DTABLE,DQUERY,DWIDTH ;Dispatch table ;'QUERY' - Return current table number DQUERY: MOVE T1,NUMB0 ;Get old number (+ or -) MOVEM T1,@2(L) ;Return as IANS POPJ P, ;'WIDTH' - Return width of a particular letter DWIDTH: MOVE D,@1(L) ;Get the character TLNE D,774000 ;Left justified ASCII? LSH D,-^D29 ;Yes, right justify it SUB D,MINC.N ;Subtract min CAMG D,MAXC.N ;Within range? SKIPN B,IPOINT(D) ;And pointer non-zero POPJ P, ;No, return 0 AND B,[777700,,007777] ;Remove byte count ADDI B,STROKS ;Point to the data area ILDB T1,B ;Get the width of the character FLOAT T1 ;To floating point FDVR T1,HITE.N ;Ratio of width/height MOVEM T1,@2(L) ;Return WIDTH fraction POPJ P, SUBTTL SETSYM -- 'TABLE' - Change symbol tables DTABLE: MOVE T1,@1(L) ;Get the table to use JUMPE T1,DQUERY ;Zero to return current table CAILE T1,MAXSET ;If out of range, JRST ISETA3 ; return error MOVMM T1,NUMB ;Save it for later MOVEM T1,NUMB0 ;Positive means table was set up by ISETAB CAMN T1,OLDSET ;Is this table already set up? JRST ISETA5 ;Yes, use it SKIPG T1 ;Positive? SKIPA T3,USRSYM ;Use SIXBIT/SYMBOL/ for negative (MSETAB) MOVX T3,SYMDEV ;Use SIXBIT/SYS/ for positive (ISETAB) MOVEI T2,.IODMP ;Dump mode SETZ T4, ;No buffers IFN FT701, TOPS20< PRINTX [The non-701 code at ISETA1: should work with PA1050]> IFE FT701,< ;Use OPEN/LOOKUP instead of FILOP. OPEN %0,T2 ;INIT SYS: or SYMBOL: JRST ISETA3 ;No MOVE T1,USRSYM ;File name 'SYMBOL' MOVSI T2,'DAT' ;Extension SETZB T3,T4 ;Implied directory LOOKUP %0,T1 ;Find SYMBOL.DAT JRST ISETA2 ;Not there ; The first block is an index, each entry is <-WORD.LENGTH,,BLOCK.NUMBER> INPUT %0,[IOWD MAXSET,SETBUF 0] ;Read in the index block MOVE T1,NUMB ;Get requested number again SKIPN T3,SETBUF-1(T1) ;Skip if the pointer to table is non-zero JRST ISETA2 ;Go die USETI %0,(T3) ;Get the right block to start with CAML T3,[-SETSIZ,,0] ;If the IOWD is bigger than our buffer TLNN T3,-1 ; or zero HRLI T3,-SETSIZ ;Use the biggest we can handle HRRI T3,BUFFER-1 ;Complete RH of IOWD SETZ T4, ;Stop word IN %0,T3 ;Read in the data for this table JRST ISETA4 ;Data read in OK PFALL ISETA2 ;Error, return -1 ISETA2: RELEAS %0, ;Release the DSK ISETA3: SETO T2, ;Set the error indicator to bad JRST ISETA6 ;Return the value ISETA4: RELEAS %0, ;Release the DSK > ;End of IFE FT701 MOVE T1,NUMB0 ;Get the number of the stoke table read in MOVEM T1,OLDSET ;Save the number for later HLLZS SYMPTR ;Not centered and not normal yet ISETA5: SETZ T2, ;Set error indicator to good ISETA6: MOVE L,SYMB16 ;Restore arg pointer MOVEM T2,@2(L) ;Store IERR as 3rd arg to SETSYM POPJ P, ;End of ISETAB/MSETAB IFN FTMKTB,< SUBTTL MKTBL & SETABL -- Entry points> SUBTTL SYMBOL -- Get args, set up mode ; Subroutine SYMBOL - this routine plots char and symbols ; Calling sequence: ; CALL SYMBOL (X,Y,HEIGHT,ICHAR,ANGLE,NUMCHR) ENTRY SYMBOL ;Set up entry point USRSYM: SIXBIT /SYMBOL/ ;Routine name and file name SYMBOL: MOVEM L,SYMB16 ;Preserve L across call MOVEI T0,ARGS-1 ;Set up to get the arguments PUSH T0,@0(L) ;Get X PUSH T0,@1(L) ;Get Y PUSH T0,@2(L) ;Get HEIGHT PUSH T0,3(L) ;Get the address of ICHAR PUSH T0,@4(L) ;Get ANGLE PUSH T0,@5(L) ;Get NUMCHR MOVEI T0,@ICHAR ;The start point of the ICHAR array HRLI T0,(POINT 7,) ;Make into a byte pointer MOVEM T0,ICHAR ;Save it for later ;Mode 1 (NUMCHR positive) Plot left justified string of characters ;Mode 2 (NUMCHR zero) Plot single right justified ASCII character ;Mode 3 (NUMCHR -2 or -3) Plot centered symbol, with or without connecting line ;The RH of TABLE is IPOINT for normal chars, is IPOINT+140 for centered symbols SKIPL T1,NUMCHR ;Mode 1 or 2? (Normal) JRST SYMNOR ;Yes, set up for normal symbols ;Mode 3 (Centered) SYMCEN: HRRZ T2,SYMPTR ;Get address of current table CAIE T2,IPOINT ;Set up for normal symbols? JUMPN T2,SYMBO1 ;No, mode 3 set up if it is not zero SKIPN HITE.C ;Skip if there is a centered symbol table height JRST SYMBER ;Go print an error MOVE T2,[PENU.C,,PENU.$] ;BLT pointer BLT T2,MAXC.$ ;Set up PENU.$, HITE.$, MINC.$, and MAXC.$ SKIPE T2,MAXC.C ;Should not skip, must have some symbols MOVE T2,MAXC.N ;Get number of normal symbols JUMPE T2,SYMBER ;Must have something there ADDI T2,IPOINT ;Add to the start of the strokes HRRM T2,SYMPTR ;Set the stroke pointer for mode 3 JRST SYMBO1 ;Go plot the symbol SYMNOR: HRRZ T2,SYMPTR ;Get the address used to point to strokes CAIN T2,IPOINT ;Check if set for normal symbols JRST SYMBO1 ;Already set up MOVE T2,[PENU.N,,PENU.$] ;BLT pointer BLT T2,MAXC.$ ;Set up PENU.$, HITE.$, MINC.$, MAXC.$ MOVEI T2,IPOINT ;Get the start of the stroke array HRRM T2,SYMPTR ;Set the stroke pointers for mode 1 and 2 SUBTTL SYMBOL -- Set up translation and rotation SYMBO1: DMOVE X,SYMB.X ;Get the requested coordinates CAMN X,[OLDVAL] ;If 999.0, SKIPA X,POS.X ; use old position, MOVEM X,CRLF.X ; else remember for CR and LF CAMN Y,[OLDVAL] ;Same for Y SKIPA Y,POS.Y MOVEM Y,CRLF.Y DMOVEM X,POS.X ;Set current position MOVE T1,NUMCHR ;Get number of chars (negative for centered) MOVEI D,PEN.DN ;Assume centered symbol with connecting line CAMN T1,[-2] ;If -2 draw line from old pen position to PUSHJ P,MYPLOT ; current position, if -3 do not draw line SKIPN T1,HEIGHT ;Get the height of the symbols MOVE T1,OLDHIT ;Zero, use previous MOVEM T1,OLDHIT FDVR T1,HITE.$ ;Divide by the max deltas allowed MOVEM T1,ROTSIN ;Save for later MOVEM T1,ROTCOS ; .. MOVEI L,[-1,,0 ;One arg REAL ANGLE ;Number of degrees ]+1 ;Point to args PUSHJ P,SIND. ;Go get the sine of the angle FMPRM T0,ROTSIN ;Multiply by the height and save PUSHJ P,COSD. ;Go get the cosine of the angle FMPRM T0,ROTCOS ;Multiply by the height and save SKIPLE T1,NUMCHR ;Get the character count JRST SYMLOP ;Output a string for NUMCHR=positive MOVE D,@ICHAR ;Get the char code JUMPE T1,SYMLP0 ;Do single ASCII character if NUMCHR=0 JRST SYMLP2 ;Do centered symbol if NUMCHR=negative SUBTTL SYMBOL -- Main loop, do a character SYMLOP: ILDB D,ICHAR ;Get next character from string ;Special case CR and LF SYMLP0: SETO C, ;Set counter in case of match MOVSI T1,-SCHARS ;Get AOBJN pointer SYMLP1: HLRZ T2,SCHTAB(T1) ;Get a special character HRRZ T3,SCHTAB(T1) ; and its dispatch addr CAMN D,T2 ;Match? JRST (T3) ;Yes, handle specially AOBJN T1,SYMLP1 ;No try next one SUB D,MINC.$ ;Subtract offset (so that 0=space) SYMLP2: JUMPL D,SYMB08 ;Jump if the char is to small CAMGE D,MAXC.$ ;Skip if the char is to big SKIPN B,@SYMPTR ;Get pointer to data, indexed by D JRST SYMB08 ;Punt off this char, pointer is zero LDB C,[POINT 12,B,23];Get the number of strokes in the char AND B,[777700,,007777];Remove the count from byte pointer ADDI B,STROKS ;Add in the relocation of the data area ILDB T1,B ;Get the width of the character MOVEM T1,SPC.X ;Save for it later ILDB T1,B ;Get the subtractive offset for the X direction MOVEM T1,SUB.X ;This is used to allow negative offsets ILDB T1,B ;Get the offset for Y MOVEM T1,SUB.Y ;This allows for negative Y, for descenders SOJLE C,SYMB06 ;Jump if this is the space character ;The first move is with the pen up SYMB03: MOVEI D,PEN.UP ;Set to raise the pen on this move SYMB04: ILDB X,B ;Get the X value to be used CAMN X,PENU.$ ;Is it the pen up command? SOJA C,SYMB03 ;Yes, next movement will be with the pen up ILDB Y,B ;Get the Y value to be used SUB Y,SUB.Y ;Relocate the Y value SYMB05: SUB X,SUB.X ;Relocate the X value FLOAT X ;Convert the number to floating point FLOAT Y ;Convert the number to floating point PUSHJ P,ROT.XY ;Rotate coordinates FADR X,POS.X ;Add in the offset for the starting position FADR Y,POS.Y ; for this character PUSHJ P,MYPLOT ;Go move the pen to X, Y, and pen up/down in D MOVEI D,PEN.DN ;Make the next segment be for pen down SOJG C,SYMB04 ;Loop if more strokes left to do JUMPL C,SYMB07 ;Stop if finished with character ;Here on last movement for this char SYMB06: MOVE X,SPC.X ;Get the width of this character SYMB6A: MOVEI Y,0 ;At the baseline MOVEI D,PEN.UP ;Raise the pen JRST SYMB05 ; and move to the end of the character SYMB07: DMOVEM X,POS.X ;Save current position as start of next char ;Here when finished with the current character SYMB08: SOSLE NUMCHR ;Skip if no more char left JRST SYMLOP ;Loop for next character ;The coordinates for the start of the next symbol (POS.X and POS.Y) are ;available by calling subroutine WHERE(X,Y). MOVE L,SYMB16 ;Restore L POPJ P, ;Return from SYMBOL ;ROT.XY - Normalize the data and rotate the coordinates ;X0 = arg to SYMBOL, X1 = data from table, X2 = arg passed to PLOT ;SIZE = HEIGHT / ;X2 = X0 + ( X1*SIZE*COS(ANG) - Y1*SIZE*SIN(ANG) ) ;Y2 = Y0 + ( Y1*SIZE*COS(ANG) + X1*SIZE*SIN(ANG) ) ROT.XY: MOVE T3,X ;Get a copy of X MOVE T4,Y ;Get a copy of Y FMPR T4,ROTSIN ;Rotate the X FMPR X,ROTCOS ; .. FSBR X,T4 ; .. FMPR T3,ROTSIN ;Rotate the Y FMPR Y,ROTCOS ; .. FADR Y,T3 ; .. POPJ P, SUBTTL SYMBOL -- Control characters, CR, LF, etc ;Table of special control characters SCHTAB: 10,,DOBS ;Backspace 11,,DOTAB ;Horizontal tab 12,,DOLF ;Linefeed 15,,DOCR ;Carriage return 16,,DOSO ;Shift-out (superscript) 17,,DOSI ;Shift-in (subscript) 36,,DORS ;Record Separator (newline = CR + LF) SCHARS==.-SCHTAB DOTAB: SKIPA X,SPC.X ;TAB - go forward DOBS: MOVN X,SPC.X ;BS - backspace JRST SYMB6A ;Move with pen up DOCR: DMOVE X,CRLF.X ;CR - Reset to start of line DMOVEM X,POS.X ;Change position JRST SYMB08 ;Loop if more chars to do DORS: DMOVE X,CRLF.X ;RS (Record Separator) - Do CR and LF DMOVEM X,POS.X DOLF: MOVN Y,HITE.$ ;LF - Get height of chars (in increments f.p.) FMPRI Y,(1.5) ;Leave room for descenders MOVEI X,0 ;No change in X coordinate PUSHJ P,ROT.XY ;Account for rotation FADRM X,CRLF.X ;Update position of "column 1" FADRM Y,CRLF.Y DOLF1: FADRB X,POS.X ;Update position FADRB Y,POS.Y JRST SYMB08 ;Loop if more chars to do DOSO: SKIPA Y,HITE.$ ;SO - Get +height for superscripts DOSI: MOVN Y,HITE.$ ;SI - Get -height for subscripts FDVRI Y,(2.0) ;Move only half that distance MOVEI X,0 ;No change in X coordinate PUSHJ P,ROT.XY ;Account for rotation JRST DOLF1 ;Do a +/- half linefeed SYMBER: ERRSTR () PUSHJ P,TRACE.## ;Trace the subroutine calls POPJ P, ;Return to caller SUBTTL SYMBOL -- Variables $LOSEG SYMB00: BLOCK 17 ;Place to save caller's ACs, 0-16 PLOT.P=SYMB00+D ;Pen up/down data PLOT.X=SYMB00+X ;X position PLOT.Y=SYMB00+Y ;Y position SYMB16=SYMB00+L ;Accumulator L POS.X: BLOCK 2 ;Starting position for current character POS.Y=POS.X+1 CRLF.X: BLOCK 2 ;Saved position for doing CR or LF CRLF.Y=CRLF.X+1 OLDHIT: BLOCK 1 ;Previous non-zero height COUNT: BLOCK 1 ;Char count NUMB: BLOCK 1 ;Argument to ISETAB/MSETAB (always positive) NUMB0: BLOCK 1 ;Positive if from ISETAB, negative if from MSETAB ROTSIN: BLOCK 1 ;SIN(ANG) * HEIGHT / ROTCOS: BLOCK 1 ; for rotation ARGS: BLOCK 6 ;Temporary storage SYMB.X=ARGS+0 ;X coord for NUMBER or SYMBOL SYMB.Y=ARGS+1 ;Y coord for NUMBER or SYMBOL HEIGHT=ARGS+2 ;Size of characters ICHAR= ARGS+3 ;Start of string to plot ANGLE= ARGS+4 ;Degrees of rotation NUMCHR=ARGS+5 ;Number of characters in ICHAR SUBTTL ISETAB table #1 -- Pointers .DIRECTIVE FLBLST ;First line binary list SETBUF: BLOCK MAXSET ;First block of SYMBOL.DAT, index pointers ;These 3 values get set by ILDB at the start of each character plotted SPC.X: BLOCK 1 ;The spacing for this char SUB.X: BLOCK 1 ;The X subtractive value SUB.Y: BLOCK 1 ;The Y subtractive value ;These 4 values get set by BLT from PENU.C or PENU.N PENU.$: BLOCK 1 ;If X = PENU.$ the next movement will be pen up HITE.$: BLOCK 1 ;The max height of the char in delta units MINC.$: BLOCK 1 ;Subtract this off to get rid of unwanted chars MAXC.$: BLOCK 1 ;Number of graphic characters this mode SYMPTR: Z 0,0(D) ;RH is IPOINT for NORMAL, IPOINT+140 for CENTER OLDSET: EXP 1 ;The last symbol table used, table #1 is set up BUFFER: ;This data gets overwritten when ISETAB is called PENU.N: 37 ;Pen-up code, -1 in 5 bits HITE.N: 8.0 ;Units of height in floating point MINC.N: 40 ;First normal character (octal code for SPACE) MAXC.N: 140 ;Number of normal chars (96 including RUBOUT) PENU.C: 7 ;-1 expressed in 3 bits HITE.C: 6.0 ;Units of height in floating point MINC.C: 0 ;First centered symbol MAXC.C: ^D26 ;Number of centered symbols EXP 0,0,0,0, 0,0,0,0 ;Reserved for future expansion ;The next 200 words are byte pointers, the address an offset from STROKS, ; the count of strokes is in the middle 12 bits. All zero if no such character IPOINT: +01_^D12 ;space 40 +06_^D12 ;! 41 XLIST ;Save paper +06_^D12 ;" 42 +14_^D12 ;# 43 +21_^D12 ;$ 44 +25_^D12 ;% 45 +14_^D12 ;& 46 +03_^D12 ;' 47 +05_^D12 ;( 50 +05_^D12 ;) 51 +14_^D12 ;* 52 +06_^D12 ;+ 53 +07_^D12 ;, 54 +03_^D12 ;- 55 +06_^D12 ;. 56 +03_^D12 ;/ 57 +15_^D12 ;0 60 +04_^D12 ;1 61 +12_^D12 ;2 62 +14_^D12 ;3 63 +05_^D12 ;4 64 +13_^D12 ;5 65 +13_^D12 ;6 66 +04_^D12 ;7 67 +21_^D12 ;8 70 +13_^D12 ;9 71 +14_^D12 ;: 72 +15_^D12 ;; 73 +04_^D12 ;< 74 +06_^D12 ;= 75 +04_^D12 ;> 76 +13_^D12 ;? 77 LIST +24_^D12 ;@ 100 +07_^D12 ;A 101 XLIST +16_^D12 ;B 102 +11_^D12 ;C 103 +10_^D12 ;D 104 +12_^D12 ;E 105 +07_^D12 ;F 106 +13_^D12 ;G 107 +11_^D12 ;H 110 +11_^D12 ;I 111 +11_^D12 ;J 112 +11_^D12 ;K 113 +06_^D12 ;L 114 +06_^D12 ;M 115 +05_^D12 ;N 116 +12_^D12 ;O 117 +10_^D12 ;P 120 +15_^D12 ;Q 121 +13_^D12 ;R 122 +13_^D12 ;S 123 +06_^D12 ;T 124 +07_^D12 ;U 125 +04_^D12 ;V 126 +06_^D12 ;W 127 +06_^D12 ;X 130 +07_^D12 ;Y 131 +05_^D12 ;Z 132 +05_^D12 ;[ 133 +03_^D12 ;\ 134 +05_^D12 ;] 135 +07_^D12 ;^ 136 +07_^D12 ;_ 137 +03_^D12 ;` 140 +17_^D12 ;a 141 +14_^D12 ;b 142 +11_^D12 ;c 143 +15_^D12 ;d 144 +13_^D12 ;e 145 +11_^D12 ;f 146 +17_^D12 ;g 147 +11_^D12 ;h 150 +10_^D12 ;i 151 +10_^D12 ;j 152 +11_^D12 ;k 153 +03_^D12 ;l 154 +17_^D12 ;m 155 +11_^D12 ;n 156 +12_^D12 ;o 157 +14_^D12 ;p 160 +14_^D12 ;q 161 +10_^D12 ;r 162 +13_^D12 ;s 163 +11_^D12 ;t 164 +10_^D12 ;u 165 +04_^D12 ;v 166 +06_^D12 ;w 167 +06_^D12 ;x 170 +07_^D12 ;y 171 +05_^D12 ;z 172 +10_^D12 ;{ 173 +03_^D12 ;| 174 +10_^D12 ;} 175 LIST +05_^D12 ;~ 176 +04_^D12 ; 177 ;Centered symbols +10_^D12 ; 0 +14_^D12 ; 1 XLIST +06_^D12 ; 2 +07_^D12 ; 3 +07_^D12 ; 4 +07_^D12 ; 5 +07_^D12 ; 6 +06_^D12 ; 7 +07_^D12 ; 8 +07_^D12 ; 9 +16_^D12 ; 10 +15_^D12 ; 11 +07_^D12 ; 12 +04_^D12 ; 13 +11_^D12 ; 14 +04_^D12 ; 15 +14_^D12 ; 16 +10_^D12 ;1 17 +13_^D12 ;2 18 +20_^D12 ;3 19 +11_^D12 ;4 20 +14_^D12 ;5 21 +17_^D12 ;6 22 +11_^D12 ;7 23 +24_^D12 ;8 24 LIST +17_^D12 ;9 25 BLOCK 200-<.-IPOINT> ;Unused pointers SUBTTL ISETAB table #1 -- Data STROKS: BYTE (5) 10,0,6 (5)10,0,6,2, 6,2,7,-1,2,10,2 BYTE (5) 15 (5)10,0,6,2,14,2, 16,-1,4,16,4,14 (5)10 BYTE (5) 0,6,2,7,2,15,-1, 4,15,4,7,-1,6,11 XLIST ;More of the same BYTE (5) 0,11,-1,0,13,6,13 (5)10,0,6,0,10,2,6 BYTE (5) 4,6,6,10,4,12,2, 12,0,14,2,16,4,16 BYTE (5) 6,14,-1,4,16,4,6, -1,2,6,2,16 (5)10,0 BYTE (5) 6,0,6,6,14,1,14, 0,13,0,12,1,11,2 BYTE (5) 11,3,12,3,13,2,14, -1,4,11,3,10,3,7 BYTE (5) 4,6,5,6,6,7,6, 10,5,11,4,11 (5)10,0 BYTE (5) 6,6,6,1,13,1,15, 2,16,3,16,4,15,0 BYTE (5) 11,0,7,1,6,3,6, 5,10 (5)10,0,6,2,14 BYTE (5) 4,16 (5)10,0,6,2,6, 0,10,0,14,2,16 (5)10 BYTE (5) 0,6,0,6,2,10,2, 14,0,16 (5)10,0,6,0 BYTE (5) 10,4,14,-1,2,14,2, 10,-1,4,10,0,14,-1 BYTE (5) 0,12,4,12 (5)10,0,6, 2,7,2,13,-1,0,11 BYTE (5) 4,11 (5)10,0,6,3,6, 3,7,2,7,2,6,3 BYTE (5) 6,2,5 (5)10,0,6,0, 11,4,11 (5)10,0,6,2 BYTE (5) 6,3,6,3,7,2,7, 2,6 (5)10,0,6,0,6 BYTE (5) 6,14 (5)10,0,6,0,7, 6,15,-1,6,14,4,16 BYTE (5) 2,16,0,14,0,10,2, 6,4,6,6,10,6,14 BYTE (5)10,0,6,1,14,3,16, 3,6 (5)10,0,6,0,14 BYTE (5) 0,15,1,16,5,16,6, 15,6,13,0,7,0,6 BYTE (5) 6,6 (5)10,0,6,0,15, 1,16,5,16,6,15,6 BYTE (5) 14,4,12,6,10,6,7, 5,6,1,6,0,7 (5)10 BYTE (5) 0,6,5,6,5,16,0, 11,6,11 (5)10,0,6,0 BYTE (5) 7,1,6,4,6,6,10, 6,11,5,12,1,12,0 BYTE (5) 11,0,16,6,16 (5)10,0, 6,0,11,1,12,5,12 BYTE (5) 6,11,6,7,5,6,1, 6,0,7,0,12,4,16 BYTE (5)10,0,6,0,16,6,16, 1,6 (5)10,0,6,1,12 BYTE (5) 0,11,0,7,1,6,5, 6,6,7,6,11,5,12 BYTE (5) 6,13,6,15,5,16,1, 16,0,15,0,13,1,12 BYTE (5) 5,12 (5)10,0,6,2,6, 6,12,6,15,5,16,1 BYTE (5) 16,0,15,0,13,1,12, 5,12,6,13 (5)10,0,6 BYTE (5) 2,6,3,6,3,7,2, 7,2,6,-1,2,12,3 BYTE (5) 12,3,13,2,13,2,12 (5)10,0,6,3,6,3,7 BYTE (5) 2,7,2,6,3,6,2, 5,-1,2,12,3,12,3 BYTE (5) 13,2,13,2,12 (5)10,0, 6,3,7,0,12,3,15 BYTE (5)10,0,6,0,10,6,10, -1,6,12,0,12 (5)10,0 BYTE (5) 6,0,7,3,12,0,15 (5)10,0,6,1,15,2,16 BYTE (5) 4,16,5,15,5,14,3, 12,3,10,-1,3,7,3 BYTE (5) 6 (5)10,0,6,1,6,0, 7,0,13,1,14,5,14 BYTE (5) 6,13,6,10,5,7,4, 10,4,13,-1,4,12,3 BYTE (5) 13,2,13,1,12,1,11, 2,10,3,10,4,11 (5)10 BYTE (5) 0,6,0,6,3,16,6, 6,-1,1,11,5,11 (5)10 BYTE (5) 0,6,0,6,0,16,5, 16,6,15,6,13,5,12 BYTE (5) 0,12,-1,5,12,6,11, 6,7,5,6,0,6 (5)10 BYTE (5) 0,6,6,15,5,16,2, 16,0,14,0,10,2,6 BYTE (5) 5,6,6,7 (5)10,0,6, 0,6,0,16,4,16,6 BYTE (5) 14,6,10,4,6,0,6 (5)10,0,6,0,6,0,16 BYTE (5) 6,16,-1,4,12,0,12, -1,0,6,6,6 (5)10,0 BYTE (5) 6,0,6,0,16,6,16, -1,4,12,0,12 (5)10,0 BYTE (5) 6,6,15,5,16,2,16, 0,14,0,10,2,6,4 BYTE (5) 6,6,10,6,12,4,12 (5)10,0,6,0,6,0,16 BYTE (5) -1,6,16,6,6,-1,0, 12,6,12 (5)10,0,6,1 BYTE (5) 6,5,6,-1,3,6,3, 16,-1,1,16,5,16 (5)10 BYTE (5) 0,6,1,7,2,6,3, 6,4,7,4,16,-1,2 BYTE (5) 16,6,16 (5)10,0,6,1, 6,1,16,-1,1,12,5 BYTE (5) 16,-1,1,12,5,6 (5)10, 0,6,0,6,0,16,-1 BYTE (5) 0,6,6,6 (5)10,0,6, 0,6,0,16,3,13,6 BYTE (5) 16,6,6 (5)10,0,6,0, 6,0,16,6,6,6,16 BYTE (5)10,0,6,0,10,0,14, 2,16,4,16,6,14,6 BYTE (5) 10,4,6,2,6,0,10 (5)10,0,6,0,6,0,16 BYTE (5) 5,16,6,15,6,13,5, 12,0,12 (5)10,0,6,0 BYTE (5) 10,0,14,2,16,4,16, 6,14,6,10,4,6,2 BYTE (5) 6,0,10,-1,4,10,6, 6 (5)10,0,6,0,6,0 BYTE (5) 16,5,16,6,15,6,13, 5,12,0,12,-1,2,12 BYTE (5) 6,6 (5)10,0,6,0,10, 2,6,4,6,6,10,4 BYTE (5) 12,2,12,0,14,2,16, 4,16,6,14 (5)10,0,6 BYTE (5) 3,6,3,16,-1,0,16, 6,16 (5)10,0,6,0,16 BYTE (5) 0,7,1,6,5,6,6, 7,6,16 (5)10,0,6,0 BYTE (5) 16,3,6,6,16 (5)10,0, 6,0,16,0,6,3,11 BYTE (5) 6,6,6,16 (5)10,0,6, 0,6,6,16,-1,0,16 BYTE (5) 6,6 (5)10,0,6,0,16, 3,13,6,16,-1,3,13 BYTE (5) 3,6 (5)10,0,6,0,16, 6,16,0,6,6,6 (5)10 BYTE (5) 0,6,3,4,0,4,0, 16,3,16 (5)10,0,6,0 BYTE (5) 14,6,6 (5)10,0,6,3, 4,6,4,6,16,3,16 BYTE (5)10,0,6,0,13,3,16, 6,13,-1,3,16,3,6 BYTE (5)10,0,6,3,7,0,12, 3,15,-1,0,12,6,12 BYTE (5)10,0,6,2,16,4,14 (5)10,0,6,0,11,1,12 BYTE (5) 3,12,4,11,4,6,-1, 4,10,3,11,1,11,0 BYTE (5) 10,0,7,1,6,3,6, 4,7 (5)10,0,6,0,6 BYTE (5) 0,15,-1,0,11,1,12, 3,12,4,11,4,7,3 BYTE (5) 6,1,6,0,7 (5)10,0, 6,4,11,3,12,1,12 BYTE (5) 0,11,0,7,1,6,3, 6,4,7 (5)10,0,6,0 BYTE (5) 7,0,11,1,12,3,12, 4,11,4,7,3,6,1 BYTE (5) 6,0,7,-1,4,6,4, 15 (5)10,0,6,4,7,3 BYTE (5) 6,1,6,0,7,0,11, 1,12,3,12,4,11,4 BYTE (5) 10,0,10 (5)10,0,6,2, 6,2,14,3,15,4,15 BYTE (5) 5,14,-1,0,13,4,13 (5)10,0,6,4,11,3,12 BYTE (5) 1,12,0,11,0,7,1, 6,3,6,4,7,-1,4 BYTE (5) 12,4,5,3,4,1,4, 0,5 (5)10,0,6,0,6 BYTE (5) 0,15,-1,0,11,1,12, 3,12,4,11,4,6 (5)10 BYTE (5) 0,6,3,14,3,13,-1, 3,12,3,7,4,6,5 BYTE (5) 6 (5)10,0,6,3,14,3, 13,-1,3,12,3,5,2 BYTE (5) 4,1,4 (5)10,0,6,0, 6,0,15,-1,0,10,2 BYTE (5) 12,-1,0,10,2,6 (5)10, 0,6,2,6,2,15 (5)10 BYTE (5) 0,6,0,6,0,12,-1, 0,11,1,12,2,12,3 BYTE (5) 11,3,6,-1,3,11,4, 12,5,12,6,11,6,6 BYTE (5)10,0,6,0,6,0,12, -1,0,11,1,12,2,12 BYTE (5) 3,11,3,6 (5)10,0,6, 0,7,0,11,1,12,3 BYTE (5) 12,4,11,4,7,3,6, 1,6,0,7 (5)10,0,6 BYTE (5) 0,4,0,12,-1,0,11, 1,12,3,12,4,11,4 BYTE (5) 7,3,6,1,6,0,7 (5)10,0,6,4,11,3,12 BYTE (5) 1,12,0,11,0,7,1, 6,3,6,4,7,-1,4 BYTE (5) 12,4,4 (5)10,0,6,0, 6,0,12,-1,0,11,1 BYTE (5) 12,3,12,4,11 (5)10,0, 6,0,7,1,6,3,6 BYTE (5) 4,7,3,10,1,10,0, 11,1,12,3,12,4,11 BYTE (5)10,0,6,2,15,2,7, 3,6,4,6,5,7,-1 BYTE (5) 1,13,3,13 (5)10,0,6, 0,12,0,7,1,6,3 BYTE (5) 6,4,7,4,12,4,6 (5)10,0,6,0,12,2,6 BYTE (5) 4,12 (5)10,0,6,0,12, 0,6,2,10,4,6,4 BYTE (5) 12 (5)10,0,6,0,6,4, 12,-1,0,12,4,6 (5)10 BYTE (5) 0,6,0,12,2,6,-1, 4,12,1,4,0,4 (5)10 BYTE (5) 0,6,0,12,4,12,0, 6,4,6 (5)10,0,6,3 BYTE (5) 16,2,15,2,13,0,11, 2,7,2,5,3,4 (5)10 BYTE (5) 0,6,2,4,2,16 (5)10, 0,6,0,16,1,15,1 LIST BYTE (5) 13,3,11,1,7,1,5, 0,4 (5)0,0,6,2,20 ;350 & 351 = "~" BYTE (5) 3,21,4,20,5,21 (5)0, 0,6,1,20,4,20,4 ;352 & 353 BYTE (5) 17 (3) 3,3,3,3,5,5,5,5,1,1 ;Start of centered symbols BYTE (3) 1,1,5,3,5,3,3,3,3,3,3,5 ;355 BYTE (3) 4,5,5,4,5,2,4,1,2,1,1,2, 1,4,2,5,3,5,3,3,3,3,3,3 BYTE (3) 5,5,1,1,1,3,5,3,3,3,3,3, 3,5,3,1,3,3,1,3,5,3,3,3 XLIST BYTE (3) 3,3,3,5,5,1,1,3,3,1,5,5, 1,3,3,3,3,3,3,5,5,3,3,1 BYTE (3) 1,3,3,5,3,3,3,3,3,3,1,3, 5,5,3,1,3,3,5,3,3,3,3,3 BYTE (3) 1,1,5,5,1,5,5,1,3,3,3,3, 3,1,5,5,5,1,1,5,1,-1,3,3 BYTE (3) 3,3,3,1,5,3,3,5,5,3,3,3, 1,3,3,3,3,3,5,5,4,4,2,4 BYTE (3) 1,5,2,4,2,2,1,1,2,2,4,2, 5,1,4,2,4,4,3,3,3,3,3,3 BYTE (3) 5,3,1,3,3,5,5,1,1,3,3,5, 3,1,3,3,3,5,1,1,5,3,3,3 BYTE (3) 3,3,3,3,5,5,1,5,5,1,1,1, 3,3,3,3,3,3,5,3,1,3,3,3 BYTE (3) 3,3,3,6,5,1,1,4,5,4,1,1, 3,6,-1,3,3,3,3,3,1,3,5,3 BYTE (3) 3,3,3,3,3,2,0,4,0,5,1,5, 5,4,6,2,6,1,5,1,1,2,0,-1 BYTE (3) 3,3,3,3,3,2,5,3,6,3,0,2, 0,4,0,-1,3,3,3,3,3,1,5,2 BYTE (3) 6,4,6,5,5,5,4,1,1,1,0,5, 0,-1,3,3,3,3,3,1,5,2,6,4 BYTE (3) 6,5,5,5,4,4,3,2,3,4,3,5, 2,5,1,4,0,2,0,1,1,-1,3,3 BYTE (3) 3,3,3,1,6,1,3,5,3,-1,4,6, 4,0,-1,3,3,3,3,3,1,1,2,0 BYTE (3) 4,0,5,1,5,2,4,3,1,3,1,6, 5,6,-1,3,3,3,3,3,5,5,4,6 BYTE (3) 2,6,1,5,1,1,2,0,4,0,5,1, 5,2,4,3,2,3,1,2,-1,3,3,3 BYTE (3) 3,3,1,5,1,6,5,6,5,5,3,1, 3,0,-1,3,3,3,3,3,1,5,2,6 BYTE (3) 4,6,5,5,5,4,4,3,2,3,4,3, 5,2,5,1,4,0,2,0,1,1,1,2 BYTE (3) 2,3,1,4,1,5,-1,3,3,3,3,3, 1,1,2,0,4,0,5,1,5,5,4,6 LIST BYTE (3) 2,6,1,5,1,4,2,3,4,3,5,4, -1,3,3,0 ;End of centered data BLOCK SETSIZ-<.-BUFFER> ;Reserve the rest of the space SETEND==.-1 $HISEG ;For the literals LITS: END