; LAST UPDATED ON: 09 OCT 83 -- Ver 2.2i+ ; REASON FOR UPDATE: Significant restructuring of the CRT I/O interrupt ; handlers, addition of "DTR" protocol. aep ; ; 22 JUL 83, Ver 2.2i+ Debug interrupt driven CRT I/O. aep ; ; 11 JUN 83, Ver 2.2+ Set up new vector utilities to match the "invariance" ; of code position which match the changes in matching ; "HMX2BIOS", and both are now under control of the ; external commom library "ACTIVE.LIB" aep ; ; PROGRAM NAME: HMX2IO.ASM -- Additional code module loaded and attached ; to the customized BIOS for CP/M-80 version 2.2, ; developed for use with CompuPro Systems Components. ; ; ========================== Copyright 1983, CompuPro Corporation, ; || || A division of Godbout Electronics. ; || HMX2IO.ASM || Oakland Airport, Oakland, CA ; || || ; ========================== ; ; This product is a copyright program product of CompuPro and is ; supplied for use with the CompuPro Computer Systems. ; ; PURPOSE: ; Set up extended character I/O routines as a secondary file ; loaded by CP/M as part of the cold boot initialization sequence. This ; may be loaded alone by name, or possibly as one of several files placed ; in a submit file (STARTUP.SUB). The method of specifying the cold boot ; file is discussed in this program's corresponding main BIOS source ; "HMX2BIOS.ASM". Use of this secondary load module permits a larger ; primary disk control program in the BIOS first loaded, in addition to ; a more powerful I/O or interrupt utility package defined here. ; ; Please be aware however that this only a "skeletal" system - ; an interrupt driven system is nearly always subjected to a great deal ; of customization since there is a wide variety of size/speed/complexity ; tradeoffs to be made. The intent of this source code is to provide a ; working example of what can be done to enhance the operation of your ; computer, and the code presented here should form a firm basis for ; experimentation. ; ; LIBRARY CONSTANTS: MACLIB COMPUPRO ;Disk and Serial/Parallel interface constants MACLIB ASCII ;Mnemonics for common ASCII, other special characters MACLIB CPMDISK ;CP/M disk defaults, CBIOS offsets, BDOS functions MACLIB ACTIVE ;Flags directing construction for the various ;CompuPro products to "customize" the BIOS ; ; CONSTANTS: ; LDRCODE EQU 0 - (XLOADZ + HSTSIZ + 256) ;Base of loaded code in CBIOS ; if INTRACT ;If interrupts are active ; ; System Support I Priority Interrupt Controller masks for interrupts: MMASK EQU 0111$1111b ;Master initial mask (Slave at I7 enabled) ; 7654 3210 ;Interrupt selection bits (enabled if "0") SMASK EQU 0111$1111b ;Slave initial mask (Uart recv enabled) ; -- 8085 internal interrupt mask register -- ; 765.5 ;Interrupt selection bits M8085 EQU 0000$1111b ;Mask for RST 5.5, 6.5, and 7.5 ; ; System Support I as CRT (interrupt driven). CRTSS EQU SS1US ;System support 1 status CRTDAV EQU SS1DAV ;Data available mask CRTTMSK EQU SS1TMSK ;Xmit ready mask CRTFMSK EQU SS1FMSK ;Xmit buffer flip bits CRTDATA EQU SS1UD ;Data port CRT$DC EQU TRUE ;CRT uses XON/XOFF protocol CRT$DSR EQU TRUE ;CRT uses hardware DSR protocol CRTILEN EQU 48 ;Length of input buffer CRTOLEN EQU 128 ;Length of output buffer else ;Interrupts are to be deactivated ; MASTER EQU 0 ;Master PIC code base is zeroed SLAVE EQU 0 ;Slave PIC code base is zeroed MMASK EQU 1111$1111b ;Master interrupt mask has all disabled SMASK EQU 1111$1111b ;Slave interrupt mask has all disabled M8085 EQU 0000$1111b ;Mask out RST 5.5, 6.5, and 7.5 (inactive) ; ; System Support I as CRT (interrupt driven). CRTSS EQU SS1US ;System support 1 status CRTDAV EQU SS1DAV ;Data available mask CRTTMSK EQU SS1TMSK ;Xmit ready mask CRTFMSK EQU SS1FMSK ;Xmit buffer flip bits CRTDATA EQU SS1UD ;Data port CRT$DC EQU TRUE ;CRT uses XON/XOFF protocol CRT$DSR EQU TRUE ;CRT uses hardware DSR protocol CRTILEN EQU 48 ;Length of input buffer CRTOLEN EQU 128 ;Length of output buffer endif ; ; ; PROGRAM: ASEG ;Used Digital Research RMAC assembler and ORG TPA ;LINK linker to assemble this code ;TPA start for program START: DI ;Make sure interrupts are dead during operation LXI SP,MSTACK ;Init temp stack LHLD 1 ;Get CBIOS base vector MVI L,1 ;Point to altered cold boot vector in CBIOS MOV E,M ;This point will be used as start area INX H ;of utility routines in this module MOV D,M ;Base of code area in "D,E" LXI H,-LDRCODE! DAD D ;See if matches specified area MOV A,H! ORA L ;Error if not perfect match JNZ BASEERR ; ; First fix CBIOS vectors to correspond to relocated code. LDA 2 ;CBIOS base MVI C,0! MOV B,A ;in "B,C" LXI H,0 ;Make cold boot vector now a warm boot restart CALL RELVEC ;Vector relocated INX B! INX B! INX B ;Skip WBOOT (warm boot stays the same) LXI H,CONST ;Console status CALL RELVEC ;Vector relocated LXI H,CONIN ;Console input CALL RELVEC ;Vector relocated LXI H,CONOUT ;Console output CALL RELVEC ;Vector relocated LXI H,LISTOUT ;List output CALL RELVEC ;Vector relocated LXI H,PUNCH ;Punch output CALL RELVEC ;Vector relocated LXI H,READER ;Reader input CALL RELVEC ;Vector relocated LXI H,7*3 ;Skip HOME,SELDSK,SETTRK,SETSEC,SETDMA,READ,WRITE DAD B MOV B,H! MOV C,L LXI H,LISTST ;List Status CALL RELVEC ;Vector relocated ; ; Now actually move fixed (relocated) code to active area. LXI H,LDRCODE ;Get base address to put code module LXI D,MODULE ;Point to code module to relocate LXI B,CODE$SIZE ;Size of code to relocate MOVCODE:LDAX D! MOV M,A ;Move code to high memory INX D! INX H DCX B MOV A,B! ORA C JNZ MOVCODE ; ; Set up new I/O devices (if any change). LHLD BOOTSW ;Get boot switch data MVI H,0! DAD H ;times 2 in "H,L" as offset LXI D,BIOTBL! DAD D ;Add to base of I/O control switch bytes MOV A,M ;Get first value STA IOBYTE ;Save as IOBYTE (main CP/M character director) INX H ;Point to next value MOV A,M ;Get the auxilary control byte (CompuPro only) STA IOCNTL ;and save it in the CBIOS workspace ; ; All runtime code is now ready, so set up interrupt controllers and ; initialize remaining UARTS and other devices not done by the boot loader, ; "HMXxBOOT.COM" or possibly in the BIOS. ; IOINIT: LXI H,INISEQ ;Point to initialization sequence string IOINIT1:MOV A,M! INX H ;Get the port to xmit to, point to next value STA INIPORT+1 ;Store in code sequence for transmission INR A ;See if highest address port JZ INITCPU ;Do CPU specific initialization if so MOV A,M! INX H ;Get value to xmit in "A", point to next value INIPORT:OUT 0 ;Send data to correct port JMP IOINIT1 ;Loop until all ports initialized ; INITCPU: ;Initialize CPU specific interrupt controls if INTRACT ;if they are to be active ; ; Mask internal interrupts (5.5, 6.5, 7.5) if 8085. if I8085 INIT85: LXI D,0FBC9h ;EI, RET opcodes LXI H,(4*2+1)*4 ;TRAP (RST 4.5) MOV M,D ;Put in enable interrupt opcode INX H MOV M,E ;And return opcode if (not M8085) and 001b LXI H,(5*2+1)*4 ;RST 5.5 MOV M,D ;Put in enable interrupt opcode INX H MOV M,E ;And return opcode endif if (not M8085) and 010b LXI H,(6*2+1)*4 ;RST 6.5 MOV M,D ;Put in enable interrupt opcode INX H MOV M,E ;And return opcode endif if (not M8085) and 100b LXI H,(7*2+1)*4 ;RST 7.5 MOV M,D ;Put in enable interrupt opcode INX H MOV M,E ;And return opcode endif MVI A,M8085 ;Get mask for these internal interrupts DB 30h ;(SIM, set interrupt mask opcode) endif EI ;Turn on interrupts in processor NOP ;Process any while our stack is active LXI D,INTRGO ;Show that interrupts are "all systems go" else LXI D,CODEGO ;Show that code module loaded and active endif JMP LOADOK ;Output message, Return to CP/M ; BASEERR:LXI D,BASEMSG ;Point to error message LOADOK: CALL OUTMSG ;Xmit it EXIT: MVI C,WBOOTX ;And re-enter CP/M with warm boot JMP BDOS ;thru the BDOS vector ; if INTRACT INTRGO: DB 'Code module relocated, Interrupts active.', CR,LF,0 else CODEGO: DB 'Code module relocated, Interrupts deactivated.',CR,LF,0 endif BASEMSG:DB 'Mismatch between base of CBIOS code area', CR,LF DB ' and assembled load module base address.', CR,LF DB 'Interrupts deactivated, no code relocated.', CR,LF,0 ; ;**************************************** ;* UTILITIES FOR CODE RELOCATION * ;**************************************** ; ; Relocate CBIOS vector. RELVEC: INX B ;Move past JMP opcode MOV A,L ;Save new locations to STAX B! INX B ;Fix CBIOS vector MOV A,H STAX B! INX B ;Point to next vector RET ; ; Output a message pointed to in D,E. OUTMSG: LDAX D! INX D ;Get character, point to next ORA A! RZ ;See if end of message, Done if so PUSH B! PUSH D! PUSH H MOV C,A ;Get character in "C" MVI A,0Ch ;Console output offset from start of cbios CALL CBIOS ;Xmit character in "A" POP H! POP D! POP B JMP OUTMSG ;Loop until entire message transmitted ; ; Direct CBIOS call. CBIOS: LHLD 1 ;Get cbios vector (CP/M is always on even page) MOV L,A ;Put offset in lower half PCHL ;Vector to CBIOS jump location ; PAGE ;******************************************************** ;* INPUT/OUTPUT DEVICE INITIAL SELECT TABLE * ;******************************************************** ; BIOTBL: ;I/O byte (IOBYTE) value, Aux I/O control byte (IOCNTL) value ; Switch = 0 DB 10$00$00$01b ;LST:=LPT:, PUN:=TTY:, RDR:=TTY:, CON:=CRT: DB 01$00$00$10b ;LPT:=Interfacer I UART 1, CRT:=Interfacer I UART 0 ; Switch = 1 DB 10$00$00$01b ;LST:=LPT:, PUN:=TTY:, RDR:=TTY:, CON:=CRT: DB 00$00$01$00b ;LPT:=Interfacer 3 USER 4 xon/xoff, CRT:=USER 0 ; Switch = 2 DB 10$00$00$01b ;LST:=LPT:, PUN:=TTY:, RDR:=TTY:, CON:=CRT: DB 00$00$01$01b ;LPT:=Interfacer 3,4 USER 4, CRT:=System Support I ; Switch = 3 DB 00$00$00$11b ;LST:=TTY:, PUN:=TTY:, RDR:=TTY:, CON:=UC1: DB 00$00$01$01b ;LPT:=Interfacer 3,4 USER 4, CRT:=System Support I ; ; IOBYTE value is the first entry for each switch selection, and -- ; IOCNTL = ww$xx$yy$zzb selects the following: ;(second byte ww xx yy 00 CRT:=Interfacer 3 USER 0. ;of each entry ww xx yy 01 CRT:=System Support I. ;in BIOTBL). ww xx yy 10 CRT:=Interfacer 1,2 UART 0. ; xx yy 11 CRT:=Interfacer 1,2 UART 1 (Custom Routine). ; 00 xx yy -- LPT:=Interfacer 3,4 USER 4. ; 01 xx yy -- LPT:=Interfacer 1,2 UART 1. ; 10 xx yy -- LPT:=Interfacer 1,2 UART 2 (Custom Routine). ; 11 xx yy -- LPT:= " " " " " ; -- xx -- -- Interfacer 3,4 USER 5 list routine select, ; -- -- yy -- Interfacer 3,4 USER 4 list routine select, ;Where xx and/or yy = 00 Straight output, no software protocol. ; 01 XON/XOFF software protocol active. ; 10 ETX/ACK software protocol active. ; And (always): ; UC1:= Interfacer 3,4 USER 7 ; TTY:= Interfacer 3,4 USER 6 ; UL1:= Interfacer 3,4 USER 5 at all times. ; ;<========= If CON:=BAT: then -- ;/==| BAT:= RDR:= Interfacer 3,4 USER 3 when RDR:=UR2: on input. ;\==|__ BAT:= PUN:= " " 3 when PUN:=UP2: on output. ;/==| BAT:= RDR:= Interfacer 3,4 USER 2 when RDR:=UR1: on input. ;\==|__ BAT:= PUN:= " " 2 when PUN:=UP2: on output. ;/==| BAT:= RDR:= Interfacer 3,4 USER 1 when RDR:=PTR: on input. ;\==|__ BAT:= PUN:= " " 1 when PUN:=PTP: on output. ;x /--| BAT:= ----- Interfacer 3,4 USER 0 when RDR:=TTY: on input. ;x \--| BAT:= ----- " " 0 when PUN:=TTY: on output. ; and for reader/punch vectors only -- ;x -- ------ RDR:= Interfacer 3,4 USER 6 when RDR:=TTY: on input. ;x -- ------ PUN:= " " 6 when PUN:=TTY: on output. ; PAGE ;**************************************************************** ;* INPUT/OUTPUT DEVICE INITIALIZATION SEQUENCE TABLE * ;**************************************************************** INISEQ: ;Port, Value to transmit sequence until Port = 0FFh. ; ; Interfacer 3,4 UART and interrupt initialization. if INTERFACER3 DB IF3UX, 0 ;Select Uart 0 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 1 ;Select Uart 1 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 2 ;Select Uart 2 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ;9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 3 ;Select Uart 3 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low endif ; if INTERFACER3 or INTERFACER4 DB IF3UX, 4 ;Select Uart 4 DB IF3UM,01011010b ;Async, 16x, 7 bits, Odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 5 ;Select Uart 5 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 6 ;Select Uart 6 DB IF3UM,01101110b ;Async, 16x, 8 bits, no parity, 1 stop DB IF3UM,01110111b ; 1200 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 7 ;Select Uart 7 DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3IR,00000000b ;Interrupt on data received control port (disabled) DB IF3IT,00000000b ;Interrupt on xmit ready control port (disabled) endif ; if (INTERFACER3 and INTERFACER4) DB IF3UX, 8+0 ;Select Uart 0 (USER 8) DB IF3UM,01011010b ;Async, 16x, 7 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 8+1 ;Select Uart 1 (USER 9) DB IF3UM,01111111b ;Async, 16x, 8 bits, even parity, 2 stop DB IF3UM,01110101b ; 300 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 8+2 ;Select Uart 2 (USER 10) DB IF3UM,01011110b ;Async, 16x, 8 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3UX, 8+3 ;Select Uart 3 (USER 11) DB IF3UM,01011110b ;Async, 16x, 8 bits, odd parity, 1 stop DB IF3UM,01111110b ; 9600 baud DB IF3UC,00100111b ;Trans. on, DTR low, rec. on, no break/ reset, RTS low ; DB IF3IR,00000000b ;Interrupt on data received control port (disabled) DB IF3IT,00000000b ;Interrupt on xmit ready control port (disabled) endif ; ; System Support I UART initialization. if SYSUP1 DB SS1UM,11101110b ;Async, 16x, 8 bits, No parity, 2 stop DB SS1UM,01111110b ;9600 baud DB SS1UC,00100111b ;Xmit on, DTR low, rec. on, no break, run, RTS low ; ; System Support I timer initialization. DB SS1TC,00$11$011$0b ;Timer 0, 16 bit load, square wave, binary DB SS1T0,low TIMEBASE ;Get divisor for time base for other 2 timers DB SS1T0,high TIMEBASE ;Set up timer 0 ; DB SS1TC,01$11$000$0b ;Timer 1, 16 bit, interrupt on count, binary DB SS1T1,low TIME1 ;Get divisor for time base for other 2 timers DB SS1T1,high TIME1 ;Set up timer 1 (Real Time Clock tick) ; DB SS1TC,10$11$000$0b ;Timer 2, 16 bit, interrupt on count, binary DB SS1T2,low TIME2 ;Set interrupt interval in units of time base DB SS1T2,high TIME2 ; ; Initialize Slave 8259A Interrupt Controller. DB SS1SP0,(low SLAVE and 111$00000b) + 000$11101b ;Make sure only 3 ; address bits used, level trigger, 4 byte inverval, cascade mode -- ICW1 DB SS1SP1,high SLAVE ;High address of Slave interrupt base -- ICW2 DB SS1SP1,00000$111b ;Slave ID is interrupt 7 -- ICW3 DB SS1SP1,000$00000b ;Non-buffered, normal EOI, 8085 -- ICW4 DB SS1SP1,SMASK ;Slave PIC initial Active Interrupt Mask - OCW1 DB SS1SP0,EOI ;Clear controller of pending interrupts -- OCW2 DB SS1SP0,SETPRI+6 ;Set CRT transmit to lowest priority -- OCW2 DB SS1SP0,READISR ;Set to read interrupt service register -- OCW3 DB SS1SP0,SMMOFF ;Special mask mode off -- OCW3 ; ; Initialize Master 8259A Interrupt Controller. DB SS1MP0,(low MASTER and 111$00000b) + 000$11101b ;Make sure only 3 ; address bits used, level trigger, 4 byte inverval, cascade mode -- ICW1 DB SS1MP1,high MASTER ;High address of Master interrupt base -- ICW2 DB SS1MP1,1000$0000b ;Only interrupt 7 is a slave -- ICW3 DB SS1MP1,000$10000b ;Full nest, non-buffered, norm EOI, 8085 - ICW4 DB SS1MP1,MMASK ;Master initial Active Interrupt Mask -- OCW1 DB SS1MP0,EOI ;Clear controller of pending interrupts -- OCW2 DB SS1MP0,READISR ;Set to read interrupt service register -- OCW3 DB SS1MP0,SMMOFF ;Special mask mode off -- OCW3 endif DB 0FFh ;End of I/O port initialization string ; DS 64 MSTACK: DS 0 ;Program stack just under code to relocate ; PAGE ;**************************************************************** ;* RELOCATED CODE MODULE (INTERRUPT HANDLING ROUTINES) * ;**************************************************************** ORG ($ + 256) and 0FF00h ;Place module on next page boundary MODULE: ;Base address of code module OFFSET EQU LDRCODE - $ ;Offset to relocate labels with ; if INTRACT ; Master priority interrupt controller vectors. ;===>> ORG ($ AND 0FFE0h) + 32 ;Must be on 32 byte boundary for interrupts ; MASTER EQU ($+offset) ;*-==-< ;Interrupt interval of 4 bytes PUSH PSW! JMP MASTERI ;VI0 (Slave CPU Service Request)- Restore interrupts PUSH PSW! JMP MASTERI ;VI1 (Input Character Ready) - Restore interrupts PUSH PSW! JMP MASTERI ;VI2 (Output Character Ready) - Restore interrupts PUSH PSW! JMP MASTERI ;VI3 (Disk 1 Service Request) - Restore interrupts PUSH PSW! JMP MASTERI ;VI4 (Disk 2, Disk 3, Disk 4) - Restore interrupts PUSH PSW! JMP MASTERI ;VI5 (MPX-1, Character I/O ) - Restore interrupts PUSH PSW! JMP MASTERI ;VI6 (MPX-1, Disk I/O Service) - Restore interrupts PUSH PSW! JMP MASTERI ;Slave interrupt (inactive code response) ; ; Slave priority interrupt controller vectors. ;===>> ORG ($ AND 0FFE0h) + 32 ;Must be on 32 byte boundary ; SLAVE EQU ($+offset) ;*-==-< PUSH PSW! JMP SLAVEI ;VI7 (Systick Master Interval) - Restore interrupts PUSH PSW! JMP SLAVEI ;Timer 0 (General Time Base) - Restore interrupts PUSH PSW! JMP SLAVEI ;Timer 1 (Real Time Clock Server)-Restore interrupts PUSH PSW! JMP SLAVEI ;Timer 2 (Job Activity Timeout) - Restore interrupts PUSH PSW! JMP SLAVEI ;Math chip service request - Restore interrupts PUSH PSW! JMP SLAVEI ;Math chip end of process - Restore interrupts PUSH PSW! JMP CRTXMIT ;Master CRT RS232 transmit byte request PUSH PSW ;Master CRT RS232 recieve byte request SHLD HL$HOLD ;Save incoming "H,L" XCHG! SHLD DE$HOLD ; and "D,E" IN CRTDATA ;Get data to reset source of interrupt ANI 7FH ;Strip out parity bit STA CRTICHR ;Save character in storage if CRT$DC ;If CRT uses Device Control (XON/XOFF) protocol CPI XON ;See if restore transmission command JZ CRTQX CPI XOFF ;See if turn off transmission command JNZ CRT2RD ;Put character in buffer if neither STA CRTXCTL ;Save control in storage JMP CRT3RD ;Finish interrupt ; ; Re-enable output transmission if incoming was "XON". CRTQX EQU ($+offset) ;*-==-< STA CRTXCTL ;Save control in storage LDA CRTXDIF ;Get output buffer character count ORA A ;See if any characters to transmit JZ CRT3RD ;Skip xmit enable if not, finish interrupt IN SS1SP1 ;Get slave interrupt mask ANI 1011$1111b ;Set CRT xmit bit so we can re-enter OUT SS1SP1 ;when transmit interrupt occurs JMP CRT3RD ;Finish interrupt endif ; CRT2RD EQU ($+offset) ;*-==-< LXI H,CRTICNT ;Get CRT input counter MOV A,M CPI CRTILEN ;See if at end of buffer JNC CRT3RD ;Done with interrupt if no room for char INR M! INX H ;Bump by one for next, point to start of buffer ADD L! MOV L,A ;Point to current buffer position MOV A,H! ACI 0! MOV H,A LDA CRTICHR ;Get character again MOV M,A ;Put character in buffer CRT3RD EQU ($+offset) ;*-==-< MVI A,SEOI+7 ;Specific end of interrupt 7 JMP SLV2EOI ;Finish with interrupt ; ; Interrupt driven CRT transmission routine. ; CRTXMIT EQU ($+offset) ;*-==-< SHLD HL$HOLD ;Save entering "H,L" XCHG! SHLD DE$HOLD ; and "D,E" if CRT$DSR CRTWAIT EQU ($+offset) ;*-==-< IN SS1US ;Get System Support I uart status ANI SS1DSR ;See if the Data Set Ready bit is active JZ CRTWAIT ;Loop until it is (hardware handshake line) endif if CRT$DC LDA CRTXCTL ;Get transmission control byte CPI XOFF ;See if "on hold" status set JZ CRTXOFF ;Turn off transmission interrupts if so endif LXI H,CRTXCNT ;Point to xmit position counter DCR M ;Back down one position in buffer JP CRTXNXT ;Proceed if not past bottom of buffer MVI M,CRTOLEN-1 ;Place pounter/counter at rear of buffer CRTXNXT EQU ($+offset) ;*-==-< MOV E,M! MVI D,0 ;Place offset to character in "D,E" INX H ;Point to aggragate difference of load, xmit DCR M ;Show one character removed from buffer ;The Zero flag set here is not altered below CRTX1C EQU ($+offset) ;*-==-< INX H! DAD D ;Point to character position in buffer MOV A,M ;Get character OUT CRTDATA ;Transmit it JNZ CRTXM3 ;Transmit normally if not the last (zero test) CRTXOFF EQU ($+offset) ;*-==-< IN SS1SP1 ;Get slave interrupt mask ORI 0100$0000b ;Set CRT xmit bit so no transmission OUT SS1SP1 ;when interrupts are enabled in this routine CRTXM3 EQU ($+offset) ;*-==-< MVI A,SEOI+6 ;Specific end of interrupt 6 SLV2EOI EQU ($+offset) ;*-==-< LHLD DE$HOLD! XCHG ;Recover entering "D,E" LHLD HL$HOLD ;Recover entering "H,L" SLVXEOI EQU ($+offset) ;*-==-< OUT SS1SP0 ;End of interrupt to slave ; ; General Master return from interrupt (only "A" saved, non-specific source). MASTERI EQU ($+offset) ;*-==-< MVI A,EOI ;Non-specific End Of Interrupt OUT SS1MP0 ;To Master PIC POP PSW ;Recover entering "A", Status EI ;Enable interrupts RET ;After return ; ; General Slave return from interrupt (only "A" saved, non-specific source). SLAVEI EQU ($+offset) ;*-==-< MVI A,EOI ;Non-specific End Of Interrupt JMP SLVXEOI ;To Slave PIC endif ; ;------------------------------- ; ; CONSOLE STATUS INPUT ROUTINE: ; ;Exit: A = 0 (zero), means no character currently ready to read. ; A = FFh (255), means character currently ready to read. ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = CRT:, 2 = BAT:, 3 = UC1: ; USER 6 xxx xxx USER 7 ;----- If CRT, secondary select done using IOCNTL byte: ; 0 = USER 0, 1 = SysSup 1, 2 = IF1P0, 3 = Custom. ;----- If BAT, secondary select done using READER of IOBYTE: ; 0 = USER 0 1 = USER 1, 2 = USER 2, 3 = USER 3 ; CONST EQU ($+offset) ;*-==-< LDA IOBYTE ;Get I/O Byte (0=TTY,1=CRT,2=BAT,3=UC1) ANI 3 ;Select console bits JNZ CONST1 ;If not TTY, check for others ; ; T T Y -- Used by all six logical device vectors. TTYST EQU ($+offset) ;*-==-< MVI A,6 ;TTY is always Interfacer 3,4 USER 6 IF3STS EQU ($+offset) ;*-==-< OUT IF3UX ;Select mux IN IF3US ;Get TTY status IFXST EQU ($+offset) ;*-==-< ANI UDAV ;Mask data available XCRTST EQU ($+offset) ;*-==-< RZ ORI 0FFh ;Show ready RET ; CONST1 EQU ($+offset) ;*-==-< DCR A ;See if CRT selected JNZ CONST2 ;Check for UC1 or BATCH if not ; ; C R T -- Video Display Terminal. CRTST EQU ($+offset) ;*-==-< LDA IOCNTL ;Get I/O control select byte ANI 00$0000$11b ;Check on CRT select bits JZ IF3STS ;If zero, CRT is Interfacer 3,4 USER 0 DCR A ;See if System Support I UART JNZ CRTST2 ;Try devices 2,3 if not ; if INTRACT ; Use interrupt driven SS1 UART. LDA CRTICNT ;See if anything in buffer ORA A! RZ ;Non-zero if something there, return if nothing MVI A,0FFh ;Show character ready status RET else IN CRTSS ;Get console status JMP IFXST ;Mask data available and return with status endif ; CRTST2 EQU ($+offset) ;*-==-< DCR A ;See if Interfacer I or II port 0 as CRT JNZ CRTST3 ;Use custom crt driver if not IN IF1US0 ;Interfacer I,II UART 0 status JMP IFXST ;Mask data available and return with status ; ; Custom CRT routine, initially set for Interfacer I,II UART 1. CRTST3 EQU ($+offset) ;*-==-< IN IF1US1 ;BUILD YOUR OWN CUSTOM CRT DRIVER HERE ANI UDAV ;Select status bit(s) JMP XCRTST ;Universal return from status check ; ; More checks on regular console devices. CONST2 EQU ($+offset) ;*-==-< DCR A ;See if UC1 selected ; ; U C 1 -- Optional user console device. UC1ST EQU ($+offset) ;*-==-< MVI A,7 ;Get optional user 7 console status JNZ IF3STS ;Complete status mask if not BATCH selected ; ; B A T -- BATCH Mode (use READER select bits to chose USER 0-3). LDA IOBYTE RRC! RRC ;Put READER select bits in lower 2 bits ANI 3 ;To select low user # JMP IF3STS ;And get IF3 status ; ;------------------------------- ; ; CONSOLE DATA INPUT ROUTINE: ; ; Read the next character into the A register, clearing ; the high order bit. If no character currently ready to ; read then wait for a character to arrive before returning. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = CRT:, 2 = BAT:, 3 = UC1: ; USER 6 xxx xxx USER 7 ;--- If CRT, secondary select done using IOCNTL byte: ; 0 = USER 0, 1 = SysSup 1, 2 = IF1P0, 3 = Custom. ;--- If BAT, secondary select done using READER of IOBYTE: ; 0 = USER 0 1 = USER 1, 2 = USER 2, 3 = USER 3 ; ;Exit: A = character read from terminal. ; CONIN EQU ($+offset) ;*-==-< LDA IOBYTE ;Get I/O Byte (0=TTY,1=CRT,2=BAT,3=UC1) ANI 3 ;Select console bits JNZ CONIN1 ;If not TTY, check for others ; ; T T Y -- Used by all six logical device vecotrs. TTYIN EQU ($+offset) ;*-==-< MVI A,6 ;TTY is always Interfacer 3,4 USER 6 IF3IN EQU ($+offset) ;*-==-< OUT IF3UX ;Select mux IF3IN2 EQU ($+offset) ;*-==-< IN IF3US ;Get TTY status ANI UDAV ;Mask data available JZ IF3IN2 ;Loop until ready IN IF3UD ;Get data ANI 7Fh ;Strip out parity RET ; CONIN1 EQU ($+offset) ;*-==-< DCR A ;See if CRT JNZ CONIN2 ;Try UC1 or BATCH if not ; ; C R T -- Video Display Terminal. CRTIN EQU ($+offset) ;*-==-< LDA IOCNTL ;Get I/O control select byte ANI 00$0000$11b ;Check on CRT select bits JZ IF3IN ;If zero, CRT is Interfacer 3,4 USER 0 DCR A ;See if System Support I UART JNZ CRTIN2 ;Try devices 2,3 if not ; if INTRACT ; Interrupt driven console input. CRTCHK EQU ($+offset) ;*-==-< LDA CRTNULL! ORA A ;See if output null control on JNZ CRTIN0 ;See if character ready if not DCR A! STA CRTNULL ;Turn off for next pass CRTSTW EQU ($+offset) ;*-==-< LDA CRTXDIF ;See if any characters left in xmit buffer ORA A ;(no characters to xmit if so) JNZ CRTSTW ;Loop until output buffer empty CRTIN0 EQU ($+offset) ;*-==-< LXI H,CRTICNT ;See if anything in buffer MOV A,M! ORA A ;Non-zero if something there JZ CRTIN0 ;Loop until character ready DI ;Hold off interrupts to get end character MOV C,M ;Get length left in "C" DCR M ;Bump down 1 for next, point at buffer - 1 ADD L! MOV L,A ;Point to last character in buffer position MOV A,H! ACI 0! MOV H,A MOV A,M ;Get char at end of buffer EI ;Re-enable interrupts CRTIN1 EQU ($+offset) ;*-==-< DCR C ;Bump counter RZ ;Done if at start of buffer DCX H ;Back up 1 at a time until start of buffer MOV B,M ;Get current character MOV M,A ;Put previous in its place MOV A,B ;Move current to previous JMP CRTIN1 ;Loop until we have char at start of buffer else CRTCHK EQU ($+offset) ;*-==-< IN CRTSS ;Get console crt status ANI UDAV ;Mask out data available bit JZ CRTCHK ;Wait if not ready IN CRTDATA ;Get console crt data ANI 7Fh ;Mask out upper bit (parity) RET endif ; CRTIN2 EQU ($+offset) ;*-==-< DCR A ;See if Interfacer I or II, port 0 as CRT JNZ CRTIN3 ;Use device 3 if not CRTIN2X EQU ($+offset) ;*-==-< IN IF1US0 ;Interfacer I,II UART 0 status ANI UDAV ;Strip out console status bits JZ CRTIN2X ;Loop if data not available IN IF1UD0 ;Get data ANI 7Fh ;Strip out parity RET ; ; Custom CRT routine, initially set for Interfacer I,II UART 1. CRTIN3 EQU ($+offset) ;*-==-< IN IF1US1 ;BUILD YOUR OWN CUSTOM CRT INPUT ROUTINE ANI UDAV ;Strip out console status bits XRI 0 ;Flip status bits as necessary JZ CRTIN3 ;Loop if data not available IN IF1UD1 ;Get data ANI 7Fh ;Strip out parity RET ; ; Check for other console devices. CONIN2 EQU ($+offset) ;*-==-< DCR A ;See if UC1 selected ; ; U C 1 -- Optional user console device. UC1CI EQU ($+offset) ;*-==-< MVI A,7 ;Get optional user 7 console status JNZ IF3IN ;Complete data input if not BATCH selected ; ; B A T -- BATCH Mode (use READER select bits to chose USER 0-3). LDA IOBYTE RRC! RRC ;Put READER select bits in lower 2 bits ANI 3 ;To select low user # JMP IF3IN ;And get IF3 data input ; ;------------------------------- ; ; READER LOGICAL DEVICE DATA INPUT ROUTINE: ; ; Read the next character from the currently assigned ; reader device into the A register, no parity bit is stripped. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = PTP:, 2 = UP1:, 3 = UP2: ; USER 6 USER 1 USER 2 USER 3 ; ;Exit: A = character read from the reader device. ; READER EQU ($+offset) ;*-==-< LDA IOBYTE ;Get I/O BYTE RRC! RRC ;Move select to lower two bits ANI 3 ;Mask select bits (0=TTY,1=PTR,2=UR1,3=UR2) JNZ IF3RI ;Else get USER 1-3 as reader inputs MVI A,6 ;TTY is USER 6 IF3RI EQU ($+offset) ;*-==-< OUT IF3UX ;Select mux IF3RI2 EQU ($+offset) ;*-==-< IN IF3US ;Get TTY status ANI UDAV ;Mask data available JZ IF3RI2 ;Loop until ready IN IF3UD ;Get data RET ; ;------------------------------- ; ; SEND CHARACTER TO PUNCH OUTPUT LOGICAL DEVICE: ; ; Send a character (8 bits) to the selected punch device. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = PTP:, 2 = UP1:, 3 = UP2: ; USER 6 USER 1 USER 2 USER 3 ; ;Entry: C = ASCII character or byte to output. ; PUNCH EQU ($+offset) ;*-==-< LDA IOBYTE ;Get I/O BYTE ANI 00$11$00$00b ;Mask out punch device select bits JZ TTYOUT ;Use TTY if zero PUNCH2 EQU ($+offset) ;*-==-< RRC! RRC! RRC! RRC ;Move select to lower two bits ANI 3 ;Mask select bits JMP IF3OUT ;Select USER for Interfacer 3,4 ; ;------------------------------- ; ; CONSOLE DATA OUTPUT ROUTINE: ; ; Send a character to the console. If the console is not ready ; to output a character, wait until it is, then do transmission. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = CRT:, 2 = BAT:, 3 = UC1: ; USER 6 xxx xxx USER 7 ;----- If CRT, secondary select done using IOCNTL byte: ; 0 = USER 0, 1 = SysSup 1, 2 = IF1-P0, 3 = Custom. ;----- If BAT, secondary select done using PUNCH of IOBYTE: ; 0 = USER 0 1 = USER 1, 2 = USER 2, 3 = USER 3 ; ;Entry: C = ASCII character to output to console. ; CONOUT EQU ($+offset) ;*-==-< LDA IOBYTE ;Get I/O Byte (0=TTY,1=CRT,2=BAT,3=UC1) ANI 3 ;Mask select bits JNZ CONOUT1 ;If not TTY, check for others ; ; T T Y -- Used by all six logical device vectors. TTYOUT EQU ($+offset) ;*-==-< MVI A,6 ;TTY is always Interfacer 3,4 USER 6 IF3OUT EQU ($+offset) ;*-==-< OUT IF3UX ;Select mux IF3OUT2 EQU ($+offset) ;*-==-< IN IF3US ;Get TTY status ANI IF3TMSK ;Mask TBE, DSR bits XRI IF3FMSK ;Flip status of both JNZ IF3OUT2 ;Loop until ready MOV A,C OUT IF3UD ;Xmit data RET ; CONOUT1 EQU ($+offset) ;*-==-< DCR A ;See if CRT JNZ CONOUT2 ;Try UC1 or BATCH if not ; ; C R T -- Video Display Terminal. CRTOUT EQU ($+offset) ;*-==-< LDA IOCNTL ;Get I/O control select byte ANI 00$0000$11b ;Check on CRT select bits JZ IF3OUT ;If zero, CRT is Interfacer 3,4 USER 0 DCR A ;See if System Support I UART JNZ CRTOUT2 ;Try devices 2,3 if not ; if INTRACT ; ; Interrupt driven console output. SS1CRT EQU ($+offset) ;*-==-< LXI H,CRTXDIF ;Point to aggragate difference of load, xmit MOV A,M! CPI CRTOLEN ;See if room for another character in buffer JNC SS1CRT ;Loop until transmitter catches up if not ; DI ;Disable interrupts while we fix pointers INR M ;Show one character added to buffer LXI H,CRTOCNT ;Point to load character position counter DCR M ;Back down one position in buffer JP SS1CRT0 ;Proceed if not past bottom of buffer MVI M,CRTOLEN-1 ;Place pointer/counter at rear of buffer SS1CRT0 EQU ($+offset) ;*-==-< MOV E,M! MVI D,0 ;Place offset to character in "D,E" LXI H,CRTOBUF DAD D ;Point to character position in buffer MOV M,C ;Get character loaded into buffer LDA CRTNULL! ORA A ;Get null control status byte, see if active JZ SS1CRT2 ;Skip status storage if so MOV A,C! STA CRTNULL ;Mark null control with current character SS1CRT2 EQU ($+offset) ;*-==-< if CRT$DC LDA CRTXCTL ;See if transmit is software enabled CPI XOFF ;is in the xmit suspend state JZ SS1CRT3 ;Don't turn on transmitter if so endif IN SS1SP1 ;Get slave interrupt mask ANI 1011$1111b ;Enable CRT xmit bit so OUT SS1SP1 ;interrupts are enabled for transmission SS1CRT3 EQU ($+offset) ;*-==-< EI ;Enable interrupts again RET else CRTOUT1 EQU ($+offset) ;*-==-< IN CRTSS ;Get console crt status XRI CRTFMSK ;Flip selected status bits ANI CRTTMSK ;Mask transmit enable bits JNZ CRTOUT1 ;Wait if not ready MOV A,C ;Get character to transmit OUT CRTDATA ;Sent to console crt RET endif ; CRTOUT2 EQU ($+offset) ;*-==-< DCR A ;See if device 3 selected JNZ CRTOUT3 ;Use custom CRT routine if so CRTO2LP EQU ($+offset) ;*-==-< IN IF1US0 ;Switch selects Interfacer I,II ANI IF1TMSK ;Mask data xmit flags XRI IF1FMSK ;Flip TBE status bit JZ CRTO2LP ;Loop if xmit buffer not empty MOV A,C ;Get char to xmit OUT IF1UD0 ;Send it on it's way RET ; ; Custom CRT routine, initially set for Interfacer I,II UART 1. CRTOUT3 EQU ($+offset) ;*-==-< IN IF1US1 ;BUILD YOUR OWN CUSTOM CRT OUTPUT ROUTINE ANI IF1TMSK ;Mask data xmit flags XRI IF1FMSK ;Flip TBE status bit JZ CRTOUT3 ;Loop if xmit buffer not empty MOV A,C ;Get char to xmit OUT IF1UD1 ;Send it on it's way RET ; ; Check for other console devices. CONOUT2 EQU ($+offset) ;*-==-< DCR A ;See if UC1 selected ; ; U C 1 -- Optional user console device. UC1CO EQU ($+offset) ;*-==-< MVI A,7 ;Get USER 7 console status if UC1 selected JNZ IF3OUT ;Complete data input if so ; ; B A T -- BATCH Mode (use PUNCH select bits to chose USER 0-3). LDA IOBYTE ;Get I/O byte value again for PUNCH select JMP PUNCH2 ;And use their value to select the USER number ; ;------------------------------- ; ; OUTPUT CHARACTER TO LIST LOGICAL DEVICE: ; ; Send a character to the list device. If the list device is not ; ready to receive a character wait until the device is ready. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = CRT:, 2 = LPT:, 3 = UL1: ; USER 6 xxx xxx USER 5. ;----- If CRT, secondary select done using IOCNTL byte: ; 0 = USER 0, 1 = SysSup 1, 2 = IF1-P0, 3 = Custom. ;----- If LPT, secondary select done using IOCNTL byte: ; 0 = USER 4 1 = IF1-P1, 2,3 = Custom. ; ;Entry: C = ASCII character to be output. ; LISTOUT EQU ($+offset) ;*-==-< LDA IOBYTE ;Get IOBYTE status RLC! RLC ;Move select to lower two bits ANI 3 ;Mask out select bits JZ TTYOUT ;Use TTY if zero DCR A ;See if CRT output JZ CRTOUT ;Use it if so DCR A ;See if line printer JNZ UL1OUT ;User list device if not ; ; L P T -- Line printer list output. LDA IOCNTL ;Get I/O control switch byte ANI 11$0000$00b ;Mask out LPT control bits JM LPTCUST ;If custom, use routine JZ LPTUSR4 ;If control value was zero, USER 4 ; LPTIF1 EQU ($+offset) ;*-==-< IN IF1US1 ;Get status ANI IF1TMSK ;Mask ready bits XRI IF1FMSK ;Flip TBE bit JNZ LPTIF1 ;Loop until ready MOV A,C ;Get char OUT IF1UD1 ;Xmit it RET ; LPTUSR4 EQU ($+offset) ;*-==-< MVI A,4 ;USER 4 as list device if so OUT IF3UX ;Select mux in Interfacer 3,4 LDA IOCNTL ;Get I/O control byte ADD A! ADD A ;Shift left 2 bits to mask USER 4 routine JMP LSTSPCL ;Check for special list protocol ; ; U L 1 -- User device list output. UL1OUT EQU ($+offset) ;*-==-< MVI A,5 ;USER 5 is special list device OUT IF3UX ;Select mux in Interfacer 3,4 LDA IOCNTL ;Get I/O control byte LSTSPCL EQU ($+offset) ;*-==-< ANI 00$11$00$00b ;Mask out USER 5 output routine select bits JZ IF3OUT2 ;Normal transmit if zero ADD A! ADD A ;Shift left 2 bits JM ETX$ACK ;Use ETX/ACK protocol if higher bit set ; ; XON/XOFF (DC1/DC3) software protocol in use. DC1$DC3 EQU ($+offset) ;*-==-< IN IF3US ;Get status ANI UDAV JZ IF3OUT2 ;List if no char ready on input IN IF3UD ;Get character ANI 7Fh ;Strip out parity bit CPI XOFF ;^S? (XOFF) JNZ IF3OUT2 ;Continue if not DC1X2 EQU ($+offset) ;*-==-< IN IF3US ;Get status ANI UDAV JZ DC1X2 ;Wait for data from printer IN IF3UD ;Get it ANI 7Fh CPI XON ;^Q? (XON) JNZ DC1X2 ;Loop until found JMP IF3OUT2 ;Xmit data using usual Interfacer 3,4 output ; ; ETX/ACK software protocol in use. ETX$ACK EQU ($+offset) ;*-==-< MOV A,C ;Get character to transmit CPI LF ;See if line feed (always last character if in ;an ESCAPE sequence) JNZ IF3OUT2 ;Transmit data if not CALL IF3OUT2 ;Transmit Line Feed and return for more MVI C,ETX ;Show end of line (End of Transmission, ETX) CALL IF3OUT2 ;Transmit and return to wait for ACK ACKX2 EQU ($+offset) ;*-==-< IN IF3US ;Get status ANI UDAV JZ ACKX2 ;Wait for data from printer IN IF3UD ;Get it ANI 7Fh ;Strip out parity bit CPI ACK ;See if ACKnowledge of buffer empty JNZ ACKX2 ;Loop until found RET ; ; Custom list routine for LPT selection. LPTCUST EQU ($+offset) ;*-==-< IN IF1US2 ;Get status ANI IF1TMSK ;Mask ready bits XRI IF1FMSK ;Flip TBE bit JNZ LPTCUST ;Loop until ready MOV A,C ;Get char OUT IF1UD2 ;Xmit it RET ; ;------------------------------- ; ; LIST DEVICE OUTPUT READY STATUS ROUTINE: ; ; Return the ready status for the assigned list device. ; ; IOBYTE selects device to use as follows: ; 0 = TTY:, 1 = CRT:, 2 = LPT:, 3 = UL1: ; USER 6 xxx xxx USER 5. ;----- If CRT, secondary select done using IOCNTL byte: ; 0 = USER 0, 1 = SysSup 1, 2 = IF1-P0, 3 = Custom. ;----- If LPT, secondary select done using IOCNTL byte: ; 0 = USER 4 1 = IF1-P1, 2,3 = Custom. ; ;Exit: A = 0 (zero), list device is not ready. ; A = 0FFh (255), list device is ready. ; LISTST EQU ($+offset) ;*-==-< LDA IOBYTE ;Get IOBYTE status RLC ;if LPT or UL1, carry set JC LPTLOS ;See which if either selected RLC ;if CRT, carry is set, else TTY MVI A,6 ;TTY select USER 6 on Interfacer 3,4 JNC IF3LOS ; ; C R T -- List status. CRTLOS EQU ($+offset) ;*-==-< LDA IOCNTL ;Get I/O control select byte ANI 00$0000$11b ;Check on CRT select bits JZ IF3LOS ;If zero, CRT is Interfacer 3,4 USER 0 DCR A ;See if System Support I UART JNZ CRTLOS2 ;Try devices 2,3 if not ; if INTRACT ; Interrupt driven console output. LDA CRTXCTL ;See if output buffering is suspended SUI XOFF ;Transmission stopped if in "XOFF" mode RZ ;Show not ready if so LDA CRTXDIF ;Get the total active characters in the buffer SUI CRTOLEN-1 ;See if all full RZ ;Show not ready if so ORI 0FFh ;Show ready if any room RET else IN CRTSS ;Get console status ANI CRTTMSK ;Mask transmit enable bits XRI CRTFMSK ;Flip selected transmit status bits DCR A ;Make zero into 0FFh if was ready RNZ ;Return with status if so XRA A ;Show not ready RET endif ; CRTLOS2 EQU ($+offset) ;*-==-< DCR A ;See if Interfacer I or II, UART 0 MVI A,0FFh ;Use custom routine if not RNZ ;Show always ready IN IF1US0 ;alternate if Interfacer I or II selected JMP IF1LOS ;Use common Interfacer I output status ; LPTLOS EQU ($+offset) ;*-==-< RLC ;carry set if UL1, reset for LPT MVI A,5 ;USER 5 for UL1 on Interfacer 3,4 JC IF3LOS ; user list device selected ; ; L P T -- Line printer list status. LDA IOCNTL ;Get I/O control switch byte ANI 11$0000$00b ;Mask out LPT control bits JM CRTLOS2 ;If custom, show ready MVI A,4 ;USER 4 of Interfacer 3,4 JZ IF3LOS ;if control value was zero ; IN IF1US1 ;Get alternate status port IF1LOS EQU ($+offset) ;*-==-< ANI IF1TMSK ;Mask ready bits XRI IF1FMSK ;Flip TBE bit RZ ;Done if ready ORI 0FFh ;Show not ready RET ; ; U L 1 -- User device list status. IF3LOS EQU ($+offset) ;*-==-< OUT IF3UX ;Select mux in Interfacer 3,4 IN IF3US ;Get status ANI IF3TMSK ;Mask TBE, DSR bits XRI IF3FMSK ;Flip status of both RZ ;If ready ORI 0FFh ;Show not ready RET ;------------------------------- if INTRACT ; HL$HOLD EQU ($+offset) ;*-==-< DW 0 ;Storage for entering "H,L" registers during interrupts DE$HOLD EQU ($+offset) ;*-==-< DW 0 ;Storage for entering "D,E" registers during interrupts ; ; CRT console input buffering control CRTICHR EQU ($+offset) ;*-==-< DB 0 ;Temp storage for input character CRTICNT EQU ($+offset) ;*-==-< DB 0 ;Initially no chars in buffer CRTIBUF EQU ($+offset) ;*-==-< DS CRTILEN ;Leave room for fair amount of type ahead ; ; CRT console output buffering control CRTNULL EQU ($+offset) ;*-==-< DB 0FFh ;Null character output buffering control CRTXCTL EQU ($+offset) ;*-==-< DB XON ;CRT output control initially on CRTOCNT EQU ($+offset) ;*-==-< DB CRTOLEN -1 ;Output load counter/pointer init at rear of buffer CRTXCNT EQU ($+offset) ;*-==-< DB CRTOLEN -1 ;Output xmitted character pointer, init at rear CRTXDIF EQU ($+offset) ;*-==-< DB 0 ;Output buffer character difference counter CRTOBUF EQU ($+offset) ;*-==-< DS CRTOLEN ;Large enough for 1 line with some controls endif ;-------------------------------- ; CODE$SIZE EQU ($ - MODULE) ;Size of module code if CODE$SIZE gt XLOADZ ;If present module larger than permitted for ; assembly in the CBIOS, then display: --:ERROR:-- Module larger than CBIOS permits OVER$SIZE EQU CODE$SIZE-XLOADZ ;Size of overflow else SIZE$LEFT EQU XLOADZ-CODE$SIZE ;Size of underflow (expansion area) endif END