SUBTTL ALCOR and DECOR -- Set up disk (or TTY) buffers ;Routine to allocate core for buffers ;Calling sequence: ; MOVEI T1,(amount of core needed) ; PUSHJ P,ALCOR ; *return* Address of core returned in T1 or -1 if none ; Uses T2 and T3 ALCOR: MOVEI T2,CORSIZ ;Assume first time here SKIPN CORBUF ;Buffer in use? MOVEM T2,CORBUF ;First time here, entire buffer is free MOVEI T2,1(T1) ;Get size + 1 (for the overhead word) MOVEI T1,CORBUF ;Start at beginning ;The word pointed to by T1 is positive if the chunk is free, negative if used ALCOR1: CAMLE T2,(T1) ;Will request fit in this chunk? JRST ALCOR2 ;No MOVN T3,T2 ;Set to negative of size EXCH T3,(T1) ;Mark this chunk as in use, get old free size SUB T3,T2 ;Decrement size of free space ADDI T2,(T1) ;T2 now points past requested chunk MOVEM T3,(T2) ;Store new free size ADDI T1,1 ;Point to the chunk (instead of overhead word) POPJ P, ;Return with addr in T1 ;Chunk is not big enough if (T1) is positive, chunk is in use if (T1) is ;negative, or CORBUF is full if (T1) is zero. ALCOR2: MOVM T3,(T1) ;Get the overhead word JUMPE T3,ALCOR3 ;Have to ask FOROTS if hit end of CORBUF ADD T1,T3 ;Point to the next overhead word JRST ALCOR1 ;Try again ;Here when CORBUF is full, get memory from FOROTS ALCOR3: MOVEI T1,-1(T2) ;Get the requested size into T1 SKIPA T2,[ALCOR.##] ;Addr of routine DECOR2: MOVEI T2,DECOR.## ;Addr of routine MOVEM T1,TEMP ;Store in memory MOVEI L,[-1,,0 ;1 arg INTEGER TEMP ;Address of arg ]+1 ;Point to args PUSHJ P,(T2) ;Ask FOROTS to do core management MOVE T1,0 ;Result was in AC0 POPJ P, ;Return with result in T1 SUBTTL ALCOR and DECOR -- Release disk (or TTY) buffers ;Routine to deallocate core for buffers ;Calling sequence: ; MOVEI T1,(addr returned from ALCOR) ; PUSHJ P,DECOR ; *return* ; Uses T2 and T3 DECOR: MOVEI T1,-1(T1) ;Get addr of overhead word CAIL T1,CORBUF ;Is this an addr in CORBUF? CAIL T1,CORBUF+CORSIZ JRST DECOR2 ;No, must be for FOROTS SKIPL T2,(T1) ;Should have -SIZE IFE FTDBUG, ;Bug, don't make things worse IFN FTDBUG,)> MOVMS (T1) ;Set -SIZE to +FREE MOVEI T1,CORBUF ;Start with first chunk ;Try to consolidate contiguous free space, pointed to by T1 DECOR1: MOVM T2,(T1) ;Get -SIZE or +FREE ADDI T2,(T1) ;Point to size word at start of next chunk SKIPN (T2) ;ZERO at end of CORBUF? POPJ P, ;Yes, all done SKIPL (T1) ;Is either chunk in use? SKIPG (T2) JRST [MOVE T1,T2 ;Yes, point to start of next chunk JRST DECOR1] ;Look for 2 ajacent free chunks MOVE T3,(T2) ;No, get size on 2nd free chunk ADDM T3,(T1) ;Add it into the size of the first chunk JRST DECOR1 ;See if next chunk is also free SUBTTL OUTDMP, OUTSTG, OUTWRD - Output a string of bytes ;Routine to output a string of bytes to plotter ;Call with byte pointer in T1, byte count in T2 (T2=0 if terminated by 0 byte) OUTDMP: PUSHJ P,OUTSTG ;Output the string TXNE P4,P4.TTY ;Output to a terminal? PUSHJ P,DUMPBF ;Yes, dump output buffer POPJ P, OUTSTG: PUSH P,T2 ;Preserve T2 MOVEI T2,0 ;ASCIZ string PUSHJ P,OUTWRD ;Send the bytes T2POPJ: POP P,T2 ;Restore T2 POPJ P, ;Return OUTWRD: TLCE T1,-1 ;LH of pointer 0 TLCN T1,-1 ; or -1? HRLI T1,(POINT 7,) ;Yes, default to 7-bit bytes PUSH P,T1 ;Store pointer OUTST1: ILDB T1,(P) ;Get a byte SKIPG T2 ;If T2 started at zero, JUMPE T1,T1POPJ ; then stop at end of ASCIZ PUSHJ P,OUTBYT ;Send it JUMPE T2,OUTST1 ;Always loop if ASCIZ SOJG T2,OUTST1 ;Loop if more bytes to output T1POPJ: POP P,T1 ;Updated pointer in T1 POPJ P, SUBTTL RETZER, RETM1, CPOPJ, CPOPJ1, T1POPJ, T2POPJ RETZER: TDZA T1,T1 ;Return 0 in T1 RETM1: SETO T1, ;Return -1 in T1 POPJ P, CPOPJ1: AOS (P) ;Skip return CPOPJ: POPJ P, ;Return SUBTTL Output numbers and bytes ;Output a decimal number. Uses T1 and T2 OUTDEC: IDIVI T1,^D10 ;Get a digit HRLM T2,(P) ;Store on stack SKIPE T1 ;If not done, PUSHJ P,OUTDEC ; recurs HLRZ T1,(P) ;Get digit ADDI T1,"0" ;Make printing PFALL OUTBYT ;Output the byte and return ;Output the byte in T1. Preserves all ACs OUTBYT: DMOVEM T1,OUTBT1 ;Preserve byte across call TXNN P4,P4.TT8 ;Sending 8-bit bytes to the terminal? JRST OUTBY1 ;No MOVEI T2,(T1) ;(Taken from page 2-114 of LSH T2,-4 ; the Processor Reference XORI T2,(T1) ; Manual) TRCE T2,14 TRNN T2,14 XORI T1,200 TRCE T2,3 TRNN T2,3 XORI T1,200 ;T1 is 7-bits plus even parity OUTBY1: SOSG BUFR.C(P4) ;Decrement byte count PUSHJ P,DUMPBF ;Get another output buffer IDPB T1,BUFR.P(P4) ;Store byte in buffer AOS BYTE.C(P4) ;Increment the cumulative byte count DMOVE T1,OUTBT1 ;Restore original byte and T2 POPJ P, TOPS20< PRINTX %TOPS20 - Many routines in PLTIOD not defined PLTIO2: UNIMP ;List of UNIMPlemented routines EXP CLRIB,INCHR,REOPEN ;Routines to be rewritten DUMPBF: UNIMP ;Dump output buffers GETNAM: UNIMP ;Get file name from caller OPNFIL: UNIMP ;Open the output file CLSFIL: UNIMP ;Close the file RELFIL: UNIMP ;Release JFN TTBINM: UNIMP ;Set terminal to PLOT (binary) mode TTASCM: UNIMP ;Set terminal to text (ASCII) mode SPTYPT: UNIMP ;Set plotter type for 'TTY' TTYINI: UNIMP ;Initialize terminal TTYFIN: UNIMP ;Finish up with the terminal TOWAIT: UNIMP ;Wait so many milliseconds after output buffer is empty GETLIM: UNIMP ;Get SETWIN limits from SYS:PRIV.SYS ISACTV: UNIMP ;Check if JFN is still open SETODV: UNIMP ;Set output device to TTY: or DSK: as appropriate POPJ P, > ;End TOPS20 TOPS10< ;This conditional lasts for many pages ;Dump output buffer, get a new one. Uses T2 DUMPBF: PUSH P,T1 ;Preserve T1 MOVE T2,BUFR.N(P4) ;Channel number HRRI T2,.FOOUT ;Output function MOVE T1,[1,,T2] ;1 word argument FILOP. T1, ;Get a new buffer MOVX T1,IO.ERR ;Unknown error TXNE T1,IO.ERR ;Any output errors? JRST [ERRSTR () HALT .+1] POP P,T1 ;No errors POPJ P, SUBTTL GETNAM - Decode output file spec ;Routine to decode output device and filename for subroutine PLOTS ;Call: MOVEI T2,[ASCII/DEV:FILNAM/] or MOVEI T2,0 ; PUSHJ P,GETNAM Called only by PLOTS routine ; *return* Sets up D.PLOT and F.PLOT GETNAM: MOVSI T1,'PLT' ;Logical device name for output MOVEM T1,D.PLOT ;Save default output device SKIPN T2 ;Was a name supplied? JRST GETNA3 ;No, use name of program SKIPE T1,(T2) ;Is the double-precision variable zero? CAMN T1,BLANKS ; or all blank? JRST GETNA3 ;Yes, forget it HRLI T2,(POINT 7,) ;Make byte pointer GETNA0: MOVE T1,[POINT 6,F.PLOT] SETZM F.PLOT ;Clear accumulated name GETNA1: ILDB T3,T2 ;Get a char CAIL T3,140 ;Lowercase? SUBI T3,40 ;Yes, convert SUBI T3," "-' ' ;Convert to SIXBIT CAIL T3,'0' ;Alphameric? CAILE T3,'Z' JRST GETNA2 ;No CAILE T3,'9' CAIL T3,'A' JRST [IDPB T3,T1 ;Yes, put in F.PLOT TLNE T2,770000 ;Done 6 chars? JRST GETNA1 ;No, loop JRST GETNA2 ] ;Yes, stop GETNA2: MOVE T1,F.PLOT ;Get name CAIN T3,':' ;End of device? JRST [MOVEM T1,D.PLOT ;Yes, store it JRST GETNA0 ] ; and go for file name JUMPN T1,GETNA4 ;Use file name if nonzero GETNA3: HRROI T1,.GTPRG ;Get the name of this program GETTAB T1, MOVSI T1,'PLT' ;Can never happen MOVEM T1,F.PLOT ;Store implicit file name GETNA4: POPJ P, ;D.PLOT and F.PLOT are set up SUBTTL NEWFIL - Create new file name ;NEWFIL - Sets up a new file for output. Increments file name if necessary, ;sets up LOOKUP block. ;Call: ; PUSHJ P,NEWFIL ; *return* NEWFIL: SKIPE T1,FILE.N(P4) ;Has a file name been set up for this plotter? JRST [PUSHJ P,INCNAM ;Yes, increment old name MOVEM T1,FILE.N(P4) ;Store for next time JRST NEWFI1] ; and use it MOVE T1,F.PLOT ;No, get name from call to PLOTS SETO T2, ;Get full mask NEWFI0: TDNE T1,T2 ;Found trailing spaces? JRST [LSH T2,-6 ;No, shift mask JRST NEWFI0 ] ;Try again AND T2,[SIXBIT /000000/] IOR T1,T2 ;Expand 'ABC' to 'ABC000', 'GRAPH' to 'GRAPH0' PUSHJ P,INCNAM ;Increment it (so 6th character is '1') MOVEM T1,FILE.N(P4) ;Store to be incremented again for 2nd plot MOVE T1,F.PLOT ;Get original file name and use it for 1st plot NEWFI1: MOVEM T1,ENT+0 ;Store file name HLLZ T1,PLTEXT(P4) ;Extension (.PLT, .PIC, or .TEK) MOVEM T1,ENT+1 SETZM ENT+2 ;Default protection SETZM ENT+3 ;Default directory MOVE T1,FILE.D(P4) ;Get output device MOVEM T1,FLP+.FODEV ;Put in FILOP. block POPJ P, PAGE ;Routine to increment name in T1. 'ABCDEF' will go to 'ABCDE1', ;'ABCDE1' will go to 'ABCDE2', 'ABCDE9' to 'ABCD10', etc. ;Uses T2-T4, returns new name in T1. Called only by NEWFIL, above INCNAM: MOVEI T2,6 ;Start with 6th position INCNA1: MOVE T3,[ POINT 6,T1,5 ;1st position POINT 6,T1,11 ;2nd POINT 6,T1,17 ;3rd POINT 6,T1,23 ;4th POINT 6,T1,29 ;5th POINT 6,T1,35 ;6th ]-1(T2) ;Get byte pointer LDB T4,T3 ;Get character CAIL T4,'0' ;Digit? CAILE T4,'9' ; ... JRST [MOVEI T4,'1' ;No DPB T4,T3 ;Set byte to 1 POPJ P, ] ;And return ADDI T4,1 ;Yes, increment digit CAIN T4,'9'+1 ;Incremented 9? MOVEI T4,'0' ;Yes, reset to 0 DPB T4,T3 ;Store new char CAIN T4,'0' ;Incremented to 0? SOJG T2,INCNA1 ;Yes, increment next digit also POPJ P, ;Return with name in T1 SUBTTL Open output file ;SETODV - Routine to set up output device in T1 ;If logical device is not the physical or spooled plotter, use it. SETODV: MOVE T1,D.PLOT ;Get specified device MOVE T2,T1 ;Copy DEVTYP T2, ;Get device type MOVX T2,.TYPLT ;Can never fail in 6 or 7 series monitors ANDX T2,TY.DEV ;Only the type CAXE T2,.TYPLT ;Is it PLT: (or logical name for PLT:)? POPJ P, ;No, use it MOVSI T1,'DSK' ;Yes, use DSK: instead TXNE P4,P4.TTY ;Unless routine is for a graphics terminal MOVSI T1,'TTY' ; in which case use TTY: POPJ P, ;ISACTV - Routine to see if the I/O channel is still active ;Call: PUSHJ P,ISACTV ; *not active* ; *is active* Preserves T1 ISACTV: HLRZ T2,BUFR.N(P4) ;Get channel number DEVNAM T2, ;Get device associated with it SKIPE T2 ;If DEVNAM returned nonzero, AOS (P) ; then the I/O channel is still OPEN POPJ P, ;OPNFIL - routine to set up FILOP. block, get channel, and open file TTBINM: ;Set TTY to BINARY mode OPNFIL: HLLZ T1,BUFR.N(P4) ;Get previous channel number JUMPN T1,OPNFI1 ;Use it if channel still open IFE FT701, ;Put in LH IFN FT701, ;Set bit to assign extended channel OPNFI1: HRRI T1,.FOCRE ;Code to create new file TXO T1,FO.PRV ;Allow [1,2] to write in [11,10,TEST] MOVEM T1,FLP+.FOFNC ;Channel,,code LDB T1,[POINTR PLTINI(P4),IN.BYT] ;Get the byte size LDB T2,[POINTR PLTINI(P4),IN.MOD] ;Get the I/O mode ;Enter here with byte size in T1, I/O mode in T2, FLP+.FOFNC set up REOPEN: MOVEM T1,BYTSIZ ;Save for after FILOP. MOVEM T2,FLP+.FOIOS ;Store mode .CREF IN.ACK ;This flag not used yet (for PTC-5 in the future) MOVSI T1,BUFR.H(P4) ;Get addr of 3 word buffer header MOVEM T1,FLP+.FOBRH ;Set for output only MOVSI T1,2 ;2 output buffers MOVEM T1,FLP+.FONBF MOVEI T1,ENT ;Address of ENTER block MOVEM T1,FLP+.FOLEB PUSHJ P,NEWFIL ;Set up device and ENTER block ;Reserve space for output buffers HRRZ T1,BUFR.N(P4) ;Get address of current buffers JUMPN T1,OPNFI2 ;Use old space if set up MOVEI T1,FLP+.FOIOS ;Point to OPEN block DEVSIZ T1, ;Get size of buffers for this device JRST RETM1 ;No such device, return -1 HRRZS T1 ;Keep only buffer size IMULI T1,2 ;Get size of 2 buffers PUSHJ P,ALCOR ;Reserve space for the buffers OPNFI2: HRRM T1,BUFR.N(P4) ;Remember address for DECOR JUMPLE T1,CPOPJ ;Abort if no core available MOVE T1,.JBFF## ;Get current first-free MOVEM T1,SAVEFF ;Save .JBFF for later OPNFI3: HRRZ T1,BUFR.N(P4) ;Get addr of buffer MOVEM T1,.JBFF## ;Tell monitor where to put buffers MOVE T1,[FLPLEN,,FLP];Point to args FILOP. T1, ;Open file for output JRST OPNERR ;Could be file already exists MOVE T1,BYTSIZ ;Get byte size LSH T1,^D18+6 ;Shift to position MOVEM T1,BUFR.P(P4) ; in byte pointer MOVE T1,FLP+.FOFNC ;Get channel number assigned TXZ T1,FO.PRV ;Clear this bit HLLM T1,BUFR.N(P4) ;Store MOVE T1,SAVEFF ;Get old .JBFF MOVEM T1,.JBFF## ;Reset first-free JRST RETZER ;Return 0 in T1 ;Here when FILOP. failed. Function .FOCRE returns error if file already exists. OPNERR: CAIN T1,ERAEF% ;Already existing file? JRST [PUSHJ P,NEWFIL ;Yes, increment file name JRST OPNFI3 ] ;Try again MOVE T1,SAVEFF ;No, reset first free MOVEM T1,.JBFF## ;... SKIPA T1,FLP+.FOFNC ;Get channel number ; and fall into RELFIL RELFIL: MOVE T1,BUFR.N(P4) ;Get channel number in left half HRRI T1,.FOREL ;Get code MOVEM T1,FLP+.FOFNC ; to RELEASe channel MOVE T2,[1,,T1] ;Point to args FILOP. T2, ;Release the channel JFCL ;Can never fail HRRZ T1,BUFR.N(P4) ;Get address of PLT buffers PUSHJ P,DECOR ;Deallocate the core IFGE FT701, ;Give it back to FOROTS SETZM BUFR.N(P4) ;No channel and no buffers assigned JRST RETM1 ;Return -1 in T1 to signify failure TTASCM: ;Set TTY to ASCII mode CLSFIL: MOVE T1,BUFR.N(P4) ;Get channel number in left half HRRI T1,.FOCLS ;Get code MOVEM T1,FLP+.FOFNC ; to CLOSE file MOVE T2,[1,,T1] ;Point to args FILOP. T2, ;CLOSE file (keeping channel around) SKIPA ;Should never happen POPJ P, ERRSTR (<% PLOT - Error closing plot>) POPJ P, SUBTTL Translate 'TTY' to appropriate plotter type ND FTTERM,0 ;Defined non-zero if any graphics terminal support IFE FTTERM, ;Return -1 in T1 if no graphics terminals IFN FTTERM,< ;This routine is called only of the plotter type is 'TTY' SPTYPT: MOVE T1,D.PLOT ;Get device name (PLT: or TTY:) MOVE T2,D.PLOT ;Need second copy DEVCHR T1, ;Check for TTY vs PLT vs DSK vs NUL TXNN T1,DV.TTY ;Is it a terminal (or NUL:)? MOVSI T2,'TTY' ;No, use TTY: instead of PLT: or DSK: MOVEM T2,D.PLOT ;Store in case changed IONDX. T2, ;Get UDX of device SETZ T2, ;No such device TXNN T2,.UXTRM ;Is logical name TTY: really a terminal? JRST RETM1 ;No, give error return for no such plotter MOVX T1,.TOTRM ;Yes, get terminal type from monitor MOVE T3,[2,,T1] ;Point to args TRMOP. T3, ;Get it MOVEI T3,0 ;If 6.03A, set to default TTY plotter MOVSI T1,-TTYNUM ;Get length of table SETYPA: CAME T3,TTY6NM(T1) ;Does monitor type match (SIXBIT) ? AOBJN T1,SETYPA ;No match, try next one SKIPGE T1 ;Found a match? SKIPA T1,TTY7NM(T1) ;Yes, get it MOVX T1,DTTPLT ;Unknown terminal type, set default POPJ P, ;Go back and check this plotter type PAGE ;Still in IFN FTTERM DEFINE X(SIXNAM,ASCNAM),< SIXBIT /SIXNAM/ ;ASCNAM > DEFINE TTYS, ;End of IFDEF TEKINI IFDEF RGSINI,< X GIGI,GIGI X VT125,VT125 X VT100,REGIS;;Assume VT125 or VK100(GIGI) in VT100 mode > ;End of IFDEF RGSINI SALL> ;End of DEFINE TTYS TTY6NM: TTYS ;List of monitor types in SIXBIT TTYNUM==.-TTY6NM ;Number of equivalences DEFINE X(SIXNAM,ASCNAM),< ASCII /ASCNAM/ ;SIXNAM > TTY7NM: TTYS ;List of plotter types in ASCII ;End of SPTYPT routine > ;End of IFN FTTERM SUBTTL TTYINI - Set up terminal IFE FTTERM, IFN FTTERM,< ;Initialize the terminal for output. By using .IOBIN (binary mode) output, ;the monitor will pass tabs, formfeeds, and blank lines regardless of terminal ;settings, and will not do auto CRLF. As long as the job is not in a binary ;input wait, Control-C will stop the program. By using .IOPIM (packed image) ;for input,;the monitor will not echo the response, and will pass nulls and ;Control-C to subroutine XHAIRS. TTYINI: TXZ P4,P4.TTY!P4.TT8;Should be zero already PUSHJ P,SETUDX ;Set up TRMOP data if output to a TTY POPJ P, ;Not a terminal TXO P4,P4.TTY ;Output is going to a TTY LDB T1,[POINTR PLTINI(P4),IN.MOD] ;Get I/O mode CAILE T1,.IOASL ;ASCII or ASCII line? TXO P4,P4.TT8 ;No, set 8th bit to parity for binary modes MOVE T1,[INTDAT,,INTBLK] ;Source,,destination BLT T1,INTBLK+3 ;Set up 4-word interrupt block MOVEI T1,INTBLK ;Tell monitor EXCH T1,.JBINT## ; to trap Control-C CAIE T1,INTBLK ;Second time around? MOVEM T1,OLDINT ;No, save old .JBINT in case its important MOVEI T1,0 ;Clear send bit (TTY GAG) PJRST P,STOSND ;Set the send bit to zero INTDAT: 4,,INTNPC ;Length,,new PC on interrupt ER.ICC ;Intercept Control-C EXP 0,0 ;Last 2 words initially zero TTYFIN: MOVE T1,OLDINT ;Get previous .JBINT MOVEM T1,.JBINT## ;Restore it MOVEI T1,1 ;Bit to enable sends (TTY NO GAG) PFALL STOSND ;Set .TOSND and return STOSND: MOVEM T1,TRM+2 ;Store argument, 0=NOSEND(GAG), 1=SEND(NOGAG) MOVEI T1,.TOSND+.TOSET;Function code MOVEM T1,TRM+0 ;Store MOVE T1,[3,,TRM] ;Point to args TRMOP. T1, ;SET TTY (NO) GAG JFCL ;No big deal POPJ P, ;Here on Control-C during normal output (not during XHAIRS) ;Reset the terminal to ASCII mode. INTNPC: MOVEM 17,INTS17 ;Save all ACs MOVEI 17,INTS00 BLT 17,INTS16 MOVE P,[IOWD INTPDS,INTPDL] ;Set up new PDL PUSH P,INTBLK+.EROPC ;Save PC at time of interrupt SKIPN .JBDDT## ;If not debugging, SETZM INTBLK+.EROPC ;Trap further Control-Cs MOVSI P3,-PLTNUM ;Get size of table INTNP1: SKIPL P4,PLTTAB(P3) ;Is this plotter active? JRST INTNP2 ;No, try next one TXNN P4,P4.TTY ;Is this going to a terminal? JRST INTNP2 ;No PUSHJ P,@PLTFIN(P4) ;Yes, set plotter to ASCII mode PUSHJ P,DUMPBF ;Dump output buffer INTNP2: AOBJN P3,INTNP1 ;Loop for all IFN FT2CC,< ;Try to notify other intercept routine MOVE T1,OLDINT ;Get old value of .JBINT MOVEM T1,.JBINT## ;Restore it SETZM OLDINT ;Be paranoid and clear to prevent recursion TRNE T1,-1 ;Anything in RH? SKIPN T2,.ERCLS(T1) ;Yes, any bits set? JRST INTNP3 ;No TRNN T2,ER.ICC ;Does it want to trap Control-C JRST INTNP3 ;No POP P,.EROPC(T1) ;Get PC at time of interrupt MOVE T2,INTBLK+.ERCCL;Get cause of interrupt MOVEM T2,.ERCCL(T1) ;Copy HRRZ T2,.ERNPC(T1) ;Get address of interrupt handler HLL T2,.EROPC(T1) ;Set PC flags MOVEM T2,INTPDL ;Store in memory MOVSI 17,INTS00 ;Point to saved ACs BLT 17,17 ;Restore accumulators JRSTF @INTPDL ;Go to other Control-C handler > ;End of IFN FT2CC INTNP3: ERRSTR () MONRT. ;Exit to monitor IFE FT2CC, ;Cannot continue IFN FT2CC,< ;Try to resume MOVSI P3,-PLTNUM ;Get size of table INTNP4: SKIPGE P4,PLTTAB(P3) ;Was this plotter active? TXNN P4,P4.TTY ; and going to a TTY? JRST INTNP5 ;No, try next one PUSHJ P,@PLTINI(P4) ;Yes, set plotter to graphics mode INTNP5: AOBJN P3,INTNP4 ;Loop for all POP P,INTPDL ;Get old PC and flags MOVSI 17,INTS00 ;Point to saved ACs BLT 17,17 ;Restore accumulators JRSTF @INTPDL ;.CONTINUE > ;End of IFN FT2CC SUBTTL Terminal I/O routines ;Routine to test for TTY as output device and set up TRMOP. data. ;Calling sequence: ; PUSHJ P,SETUDX ; *error* ;Output device not a TTY ; *ok return* ;Output device is a TTY ; Uses T1 SETUDX: HLRZ T1,BUFR.N(P4) ;Get channel number IONDX. T1, ;Get I/O index number MOVEI T1,0 ;Error, not a TTY MOVEM T1,TRM+1 ;Save UDX TXNE T1,.UXTRM ;Output to a TTY? AOS (P) ;Yes, give skip return POPJ P, ;Routine to wait a while after the terminal output buffer is empty. ; Calling sequence: ; MOVEI T1,(milliseconds to wait) ; PUSHJ P,TOWAIT ; *return* ; Preserves all ACs TOWAIT: PUSH P,T1 ;Save delay time PUSHJ P,SETUDX ;Set TRM if it's a TTY JRST T1POPJ ;Not, can't wait for DSK WAIT0: MOVEI T1,.TOSOP ;Set up to wait for MOVEM T1,TRM ; the TTY buffer MOVE T1,[2,,TRM] ; going empty TRMOP. T1, ;Skip if Output in Progress JRST WAIT1 ;Output buffer is empty MOVEI T1,^D250 ;Wait HIBER T1, ; 1/4 JFCL ; second JRST WAIT0 ;See if output buffer empty now WAIT1: POP P,T1 ;Get delay time HIBER T1, ;Hibernate for a while JFCL ;Can never happen POPJ P, ;Routine to input a character from the terminal INCHR: PUSHJ P,SETUDX ;Set up TRM JRST RETZER ;Not a TTY, return 0 in T1 MOVEI T1,.TOISC ;Code to input single char MOVEM T1,TRM+0 ;Store function MOVE T1,[2,,TRM] ;Point to args TRMOP. T1, ;Get a char SETO T1, ;Only if detached ;*; IDPB T1,HEADBP ;Store POPJ P, ;Routine to clear input buffer of typeahead CLRIB: PUSHJ P,SETUDX ;Set up TRM POPJ P, ;No input buffer to clear MOVEI T1,.TOCIB ;Code to clear input buffer MOVEM T1,TRM+0 ;Store function MOVE T1,[2,,TRM] ;Point to args TRMOP. T1, ;Clear typeahead JFCL ;Only if detached POPJ P, ;Routine to read TTY response in binary ;Call: ; MOVEI T1,[ASCIZ /Prompt or trigger/] ; MOVE T2,[bytecount,,terminator] ; PUSHJ P,RDTBIN ; *return* Returns pointer to response in T1, byte count in T2 ;RDTBIN: POPJ P, > ;End of IFN FTTERM SUBTTL I/O routines - Read window limits from SYS:PRIV.SYS %0==0 ;Temporary I/O channel, will be released before returning DFWINS==DFWINS ;Should be about 35.0 inches IFE FTPRIV GETLIM: GETPPN T1, ;Get this guy's PPN JFCL MOVEM T1,MYPPN SETZB X,Y ;In case OPEN fails SETZM P.WIND ;Clear priv bits IFDEF DSKINI,< IFN FTPRIV,< ;Read file for limits MOVX T1,UU.PHS!.IODMP;Physical only, dump mode MOVSI T2,'SYS' ;System device SETZ T3,0 ;No buffers OPEN %0,T1 ;Go get an I/O channel JRST GETLI9 ;??? Use default MOVE T1,['PRIV '] ;Set up to lookup file 'PRIV.SYS' MOVSI T2,'SYS' ; .. SETZB T3,T4 ; .. LOOKUP %0,T1 ;Lookup the file 'PRIV.SYS' JRST GETLI4 ;Can't find it - go use the default GETLI1: IN %0,GETLIO ;Go get a block of data TDZA T3,T3 ;Skip and set up pointer to SWBUFR JRST GETLI4 ;EOF and no match, use default GETLI2: SKIPE T1,WINPPN(T3) ;Pick up next PPN CAML T1,MYPPN ;Searched far enough? JRST GETLI3 ;Yes, see if it matches PPN ADDI T3,WINLEN ;Increment the counter CAIGE T3,200-WINLEN ;Skip if finished with this block JRST GETLI2 ;No - go try the next entry then JRST GETLI1 ;Go read the next block GETLI3: CAME T1,MYPPN ;Searched past PPN? JRST GETLI4 ;Yes, go use the default DMOVE X,WINX(T3) ;Get max X and Y for this PPN DATE T1, ;The today's date MOVE T2,WINDAT(T3) ;Get the user's privileges and exp-date HLRZM T2,P.WIND ;Save priv bits (all zero for now) CAILE T1,(T2) ;Today less than expiration date? GETLI4: SETZB X,Y ;No, zeros means use default SKIPN X ;If expired or default, SETZM P.WIND ; clear window privs RELEAS %0 ;Release the I/O channel > ;End of IFN FTPRIV > ;End of IFDEF DSKINI GETLI9: CAMG X,[DFWINS] ;PRIV.SYS too small or zero? MOVE X,[DFWINS] ;Yes, use default of 11.0 inches CAMG Y,[DFWINS] MOVE Y,[DFWINS] DMOVEM X,X.WMAX ;Save max from SYS:PRIV.SYS POPJ P, SUBTTL Misc - IFX.X and IFX.Y IFN FTKA,< ;PUSHJ P,IFX.X is equivalent to FIXR X,X ;Uses T2 and T3, preserves T1 IFX.X: TDZA T3,T3 ;Set up to use X IFX.Y: MOVEI T3,1 ;Set up to use Y PUSH P,T1 ;Preserve T1 MOVE T1,X(T3) ;Get value into the right place MOVSI T2,(DEC 0.5) ;Assume we round positive SKIPGE T1 ;Do we? MOVSI T2,(DEC -0.5) ;No, then use negative rounding factor FADR T1,T2 ;Round it. PUSHJ P,IFX.1## ;Go convert the number to an integer MOVEM T1,X(T3) ;Store the value back where is belongs POP P,T1 ;Restore T1 POPJ P, ;Return > ;End of IFN FTKA SUBTTL ALCHN and DECHN IFE FT701,< ; Subroutine ALCHN - this routine gets an I/O channel for the caller ; Calling sequence: ; PUSHJ P,ALCHN ; *no channel* ; *good return* ALCHN: PRINTX ?ALCHN/DECHN not written DECHN: POPJ P, > ;End IFE FT701 > ;End of TOPS10 from many pages back SUBTTL Data area -- Global variables TOPS10< IFN FTPRIV,< GETLIO: IOWD 200,SWBUFR ;IOWD for reading 1 block, H.ZERO must follow 0 ;Zero marks the end > ;End IFN FTPRIV > ;End TOPS10 ;Some handy constants BLANKS: ASCII / / ;5 spaces CRLF: BYTE (7) CR,LF,0 ;NOTE: All Y varibles must immediately follow the X variables for DMOVE X,var. $LOSEG ;PLOTS variables PLTTAB: BLOCK PLTNUM ;Pointers to defined plotters E.PLOT: BLOCK 1 ;Counter for window-exceeded errors T.PLOT: BLOCK 1 ;Default plotter type C.PLOT: BLOCK 1 ;Count of calls to PLOT (never zeroed) D.PLOT: BLOCK 1 ;Output device from PLOTS F.PLOT: BLOCK 1 ;Output file name " " ;PLOT variables X.CALL: BLOCK 2 ;Last pen position as set by CALL PLOT(X,Y,I) and Y.CALL=X.CALL+1 ; returned by CALL WHERE(X,Y) P.DOWN: BLOCK 1 ;-1 to drop pen before moving, 0 to raise before moving X.ORIG: BLOCK 2 ;Offset due to origin shifting, Y.ORIG=X.ORIG+1 ; set by CALL PLOT(X,Y,-3) S.ORIG: BLOCK 1 ;Negative to change the origin ;SETWIN variables X.WIND: BLOCK 5 ;Universal window, set by call to SETWIN, and Y.WIND=X.WIND+1 ; is limited by X.WMAX and Y.WMAX X.WMAX=X.WIND+2 ;Maximum window size, as defined in SYS:PRIV.SYS Y.WMAX=X.WIND+3 ;(Subroutine GETWIN depends on this particular order) P.WIND=X.WIND+4 ;Privileges (currently zero) ;NEWPEN variables C.NPEN: BLOCK 1 ;New pen color L.NPEN: BLOCK 1 ;New pen line type (not yet implemented) ;ROTATE variables A.ROTA: BLOCK 1 ;Angle from previous call to ROTATE, in degrees X.ROTA: BLOCK 2 ;Origin set by ROTATE Y.ROTA=X.ROTA+1 ;Origin set by ROTATE ;FACTOR variables X.FACT: BLOCK 2 ;Scaling factor in X direction Y.FACT=X.FACT+1 ;Scaling factor in Y direction SUBTTL Data area -- Temporary variables SAVE0: BLOCK 17 ;Place to save ACs, 0-16 SAVET1=SAVE0+T1 SAVEL= SAVE0+L MYPPN: BLOCK 1 ;For checking in SETWIN ANGLE: BLOCK 1 ;Argument for SIN. and COS. TEMP: BLOCK 6 ;Temporary storage OUTBT1: BLOCK 2 ;Saves T1 and T2 for OUTBYT SAVEFF: BLOCK 1 ;Holds old .JBFF while creating buffers X.NEWP: BLOCK 2 ;New pen position for CHECK Y.NEWP==X.NEWP+1 ;New pen position for CHECK FILPTR: BLOCK 1 ;Pointer to file name for PLOTS BYTSIZ: BLOCK 1 ;Byte size for OPNFIL FLPLEN==6 ;Length of block FLP: BLOCK FLPLEN ;FILOP. block ENT: BLOCK 4 ;ENTER block IFN FTTERM,< TRM: BLOCK 3 ;TRMOP. block INTBLK: BLOCK 4 ;Interrupt block (Control-C) OLDINT: BLOCK 1 ;Previous value of .JBINT INTPDS==20 ;Size of interrupt PDL INTPDL: BLOCK INTPDS ;Interrupt PDL INTS00: BLOCK 20 ;Save all ACs on interrupt INTS16=INTS00+16 INTS17=INTS00+17 > ;End of IFN FTTERM IFN FTHEAD,< ;Plot headers and trailers HDRHIT: BLOCK 1 ;Height of header/trailer in inches (0.10) NINETY: BLOCK 1 ;Plot it at +90 degrees (90.0) ONE: BLOCK 1 ;Number for ISETAB (must be in LOSEG) (1) HEADBF: BLOCK ^D20 ;Space for 100 chars HEADCT: BLOCK 1 ;Count of chars in HEADBF HEADBP: BLOCK 1 ;Byte pointer to HEADBF > ;End of IFN FTHEAD ND BUFSIZ,203*2 ;Default size is 2 disk buffers IFN FTAPLT,*2> ;Enough to handle 2 plotters ND CORSIZ,<1+BUFSIZ>+<1+PLTSIZ> ;Enough to handle any single plotter CORBUF: BLOCK CORSIZ+1;Used by ALCOR/DECOR L.ZERO=.-1 ;Guarenteed zero word in the LOSEG IFN FTPRIV,< SWBUFR: BLOCK 200 ;Buffer for SETWIN routine (1 block in DUMP mode) WINPPN=SWBUFR+0 ;PPN WINDAT=SWBUFR+1 ;Date in 15 bit format WINX= SWBUFR+2 ;Max X in floating point WINY= SWBUFR+3 ;Max Y in floating point WINLEN==4 ;Size of each entry > ;End of IFN FTPRIV SUBTTL Literals and END statement $HISEG ;End of DATA, back to CODE section LITIOD: LIT PLTEND=.-1 END ;End of PLTIOD.MAC