home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
ftp.barnyard.co.uk
/
2015.02.ftp.barnyard.co.uk.tar
/
ftp.barnyard.co.uk
/
cpm
/
walnut-creek-CDROM
/
BEEHIVE
/
ZCAT
/
SYSIOP21.LBR
/
SYSIOP.ZZ0
/
SYSIOP.Z80
Wrap
Text File
|
2000-06-30
|
44KB
|
1,231 lines
VERSION EQU 211
;**************************************************************************
;**************************************************************************
;** ***
;** System IO: A set of redirectable I/O drivers for ZCPR3 ***
;** ***
;**************************************************************************
;**************************************************************************
;
; File Name : SYSIOP.Z80
; Author : Edmund Cramp
; Creation Date : 10-Jun-1986
;
; Proccessor Type : HD64180
; Assembler Name : Z80ASM (S.L.R Systems)
;
; Ammendment Record
; *****************
; Name Date Details of Ammendment
; ---- ---- ---------------------
; Edmund Cramp 10-Jun-1986 Creation from Richard Conns distribution copy.
; Edmund Cramp 28-Jun-1986 Release 2.00
; Edmund Cramp 27-Aug-1986 Determine interrupt table location from 64180
; registers. RDR and PUN modified. Console ISR
; checks for chars stacked in ASCI. System size
; determined from WB addrs.
; Edmund Cramp 31-Aug-1986 Rearranged the list ISR logic.
; Edmund Cramp 03-Sep-1986 Release 2.11 - shorter LST: driver code. Buffer
; sizes adjusted and VT100 keypad mode bug fixed.
;
; Module Function
; ***************
; This device driver package is to be assembled and the resulting .COM
; file is to be renamed to SYS.IOP for use by the ZCPR3 system loader. This
; version is not banked and resides in the normal ZCPR IOP area only.
; As some of the devices are XON/XOFF devices I have implemented a key
; translation table for ANSI (VT-100) terminals and Zenith (VT-52) arrow keys.
; These keys generate an escape (ESC) sequence that is translated via a simple
; lookup table in the data area to the ZCPR standard of ^E,^X,^S,^D. This is
; nessesary as the ^S key is XOFF and all XOFFs are gobbled in the interrupt
; service routine. For precise details on the XON/XOFF protocol see the DEC
; VT100 user manual.
; For installation details see the "-READ.ME" file.
;**************************************************************************
; ==============
; External Files
; ==============
MACLIB HD64180.MLB ; HD64180 macro library.
MACLIB PORTS.LIB ; SB-180 Hardware configuration file.
MACLIB Z3BASE.LIB ; ZCPR3 definition file.
; =============
; Local Equates
; =============
; Arrow key time-out value
DELAY_VALUE EQU 800 ; Adjust if arrow keys don't work.
BDOS EQU 0005H ; O/S entry vector.
; Console input character mask (select 7 or 8 bit input).
IOMASK EQU 01111111B ; Select 7 bit console input.
; ASCII control characters.
XON EQU 11H ; ^Q
XOFF EQU 13H ; ^S
ESC EQU 1BH ; Escape.
; Arrow key translation support for VT52 or VT100
VT100 EQU 100 ; DEC VT1xx and ANSI terminals.
VT52 EQU 52 ; DEC VT52 and Heath terminals.
FOREIGN EQU 0 ; Unknown terminal type - no translation
; IOP device driver offsets
DEVCON EQU 0 ; Console.
DEVRDR EQU DEVCON+1 ; Reader.
DEVPUN EQU DEVRDR+1 ; Punch.
DEVLST EQU DEVPUN+1 ; List.
; Printer control codes
NORMAL EQU 18 ; EPSON switches to 80 column print.
COMPRS EQU 15 ; EPSON switches to 132 column print.
; HD64180 ASCI equates.
RDRF EQU 10000000B ; Receive register full.
OVRN EQU 01000000B ; Receiver buffer overrun.
PE EQU 00100000B ; Parity error.
FE EQU 00010000B ; Framing error.
DCD0 EQU 00000100B ; Carrier detect.
TDRE EQU 00000010B ; Transmit register empty.
EFR EQU 00001000B ; Error flag reset.
; ============
; Local Macros
; ============
PRINTE MACRO MSG,N ;; Macro to display free byte count
IF2
.PRINTX * MSG N bytes *
ENDIF
ENDM
MVERSN MACRO ;; Expand version number.
DEFB VERSION/100+'0'
DEFB '.'
DEFB (VERSION MOD 100/10)+'0'
DEFB (VERSION MOD 10)+'0'
ENDM
;***************************************************************************
;*** SYSIOP ****
;***************************************************************************
.PHASE IOP ; Base Address of I/O Drivers (from Z3BASE).
JP STATUS ; Internal Status Routine
JP SELECT ; Device Select Routine
JP NAMER ; Device Name Routine
JP TINIT ; Initialize I/O package.
JP CONST ; Console Input Status
JP CONIN ; Console Input Char
JP CONOUT ; Console Output Char
JP LIST ; List Output Char
JP PUNCH ; Punch Output Char
JP READER ; Reader Input Char
JP LISTST ; List Output Status
JP NEWIO ; New I/O Driver Installation Routine
JP COPEN ; Open CON: Disk file.
JP CCLOSE ; Close CON: Disk file.
JP LOPEN ; Open LST: Disk file.
JP LCLOSE ; Close LST: Disk file.
;+
; I/O Package Identification
;-
DEFB 'Z3IOP' ; Read by Z3LOADER
DEFZ 'SB180b' ; Package name.
;+
; Return information on devices supported by this I/O Package. On exit, HL
; points to an eight byte logical device table. If error or no I/O support,
; return with Zero Flag Set. Also, if no error, A=Driver Module Number
; (Msb=0 if "OPEN" and "CLOSE" functions are not implemented).
;-
STATUS: LD HL,CNTTBL ; Point to table
LD A,00000010B ; Module 2 (SB180b) w/o Disk Output.
OR A ; Set Flags
RET ;
;+
; Select devices indicated by B and C. B is the number of the logical device,
; where CON:=0, RDR:=1, PUN:=2, LST:=3, and C is the desired device (range 0
; to dev-1). Return with Zero Flag Set if Error.
;-
SELECT: CALL RANGER ; Do a range check for device and driver
JR NC,SELERR ; ...branch if error.
;
INC HL ; Bump pointer to selected device...
LD (HL),C ; ...and select the device driver.
;
SELOK: OR -1 ; Return no error...
RET ; ...0FFh and NZ.
;+
; Check that a requested device and driver are legal. On entry B is the logical
; device number (0-3) and C is the physical device number (0 to dev-1).
; Exit NC if either device or driver are out of range. If device is legal then
; return with offset (0,2,4,6) in Reg DE and Reg HL pointing to the entry in
; CNTTBL and the CY flag set.
;-
RANGER: LD A,B ; Check that device is legal...
CP DEVLST+1 ; ...ie DEVCON to DEVLST...
RET NC ; ...exit if illegal device requested.
;
ADD A,B ; Double B so offset is 0,2,4,6
LD E,A ; Build offset in Reg DE...
LD D,0 ; ...
LD HL,CNTTBL ; Point to the IOP table and adjust...
ADD HL,DE ; ...to point to to device in CNTTBL.
;
LD A,C ; Read the maximum number of devices...
CP (HL) ; Check for illegal driver request.
;
RET ; Exit CY set if OK, clear CY if not.
;+
; Return text string of physical device. Logical device number is in B and the
; physical selection is in C. HL is returned pointing to the first character of
; the string. The strings are structured to begin with a device name followed
; by a space and then a description string which is terminated by a binary 0.
; Return with Zero Flag Set if error.
;-
NAMER: CALL RANGER ; Check device and driver numbers...
JR NC,NAMERROR ; Exit if error in name request.
;
LD HL,NAMPTB ; Point to device name table pointers.
ADD HL,DE ; ...offset to driver name pointer.
LD E,(HL) ; Copy driver name pointer into...
INC HL ; ...
LD D,(HL) ; ...reg DE.
EX DE,HL ; HL now points to driver name table.
;
LD A,C ; Generate the driver offset...
ADD A,C ; ...(0,2,4,6)...
LD E,A ; ...load Reg DE...
LD D,0 ; ...
ADD HL,DE ; HL now points to driver name address.
;
LD E,(HL) ; Get address of NAME string...
INC HL ; ...
LD D,(HL) ; ...into Reg DE.
EX DE,HL ; Swop pointer, HL -> driver name.
;
JR SELOK ; Exit after setting OK flags.
NAMERROR: LD HL,ERRMSG ; Point to an error message...
;
SELERR: XOR A ; ...Exit, error.
RET
;+
; Get the status for the currently assigned console.
;-
CONST: LD HL,CSTBLE ; Beginning of jump table
;
CONMSK: LD E,DEVCON*2 ; Point to console device in config table
JR SELDEV ; Select correct jump
;+
; Input a character from the currently assigned console.
;-
CONIN: LD HL,CITBLE ; Beginning of character input table
JR CONMSK ; Get Console Mask
;+
; Output the character in C to the currently assigned console.
;-
CONOUT: LD HL,COTBLE ; Beginning of the character out table
JR CONMSK ; Get the Console Mask
;+
; Input a character from the currently assigned reader.
;-
READER: LD HL,RTBLE ; Beginning of reader input table
LD E,DEVRDR*2 ; Point to reader device in config table
; Fall through into SELDEV....
;+
; Entry at SELDEV will form an offset into the table pointed to by HL and
; then pick up the address and jump there. The configuration of the physical
; device assignments is pointed to by B. Note that the Acc and flags are
; preserved as the SB180 bios has a non-standard RDR and PUN driver.
;-
SELDEV: PUSH AF ; Save CY state for SB180 RDR/PUN.
PUSH HL ; Save driver pointer
;
LD HL,CNTTBL ; Point to IOP control table...
; Reg E contains 8-bit offset...
LD D,0 ; Make Reg DE a 16-bit offset...
ADD HL,DE ; Add offset to HL...
INC HL ; ...and adjust HL to point to device #.
;
LD E,(HL) ; Read current physical device from table
SLA E ; Double device for word pointer (D=0).
POP HL ; Retrive driver pointer from stack...
ADD HL,DE ; ...and adjust HL to physical device.
;
LD E,(HL) ; Get physical driver address...
INC HL ; ...
LD D,(HL) ; ...
EX DE,HL ; ...into reg HL.
;
POP AF ; Restore CY state for RDR/PUN (SB-180).
JP (HL) ; Branch to physical device driver.
;+
; Output char in C to the currently assigned punch device.
;-
PUNCH: LD HL,PTBLE ; Beginning of punch table
LD E,DEVPUN*2 ; Offset to punch devices.
JR SELDEV ; Select Device and Go
;+
; Output char in C to the currently assigned list device.
;-
LIST: LD HL,LTBLE ; Beginning of the list device routine
;
LSTMSK: LD E,DEVLST*2 ; Select list devices...
JR SELDEV ; ...branch to select function.
;+
; Get the output status of the currently assigned list device.
;-
LISTST: LD HL,LSTBLE ; Beginning of the list device status
JR LSTMSK ; Branch to point to list devices.
;**************************************************************************
;** I/O Driver Support Specification Tables ***
;**************************************************************************
;+
; IOP control table
; The first byte is the number of device drivers supported; the second is
; the currently selected device.
;-
CNTTBL: DEFB CONSIZE,00 ; CON:
DEFB RDRSIZE,00 ; RDR:
DEFB PUNSIZE,00 ; PUN:
DEFB LSTSIZE,00 ; LST:
;+
; Logical Device name text pointers.
;-
NAMPTB: DEFW CONAME ; CON: device
DEFW RDNAME ; RDR: device
DEFW PUNAME ; PUN: device
DEFW LSNAME ; LST: device
; Physical console pointers
CONAME: DEFW NAMDEC ; DEC Console (xon/xoff handshake).
DEFW NAMCRT ; ISR Console.
DEFW NAMPOL ; Polled Console.
DEFW NAMREM ; ASCI0 serial line.
DEFW NAMCRP ; DEC Console and Printer output.
DEFW NAM100 ; DEC w/ ANSI arrow key translation.
DEFW NAM52 ; DEC w/ VT52 arrow key translation.
DEFW NAMPAT ; Patchable console device.
CONSIZE EQU ($-CONAME)/2
; Physical reader pointers.
RDNAME: DEFW NAMNUL ; Null device
DEFW NAMMOD ; Modem.
DEFW NAMRDR ; SB-180 reader (returns status).
DEFW NAMPAT ; Patch device
RDRSIZE EQU ($-RDNAME)/2
; Physical punch pointers.
PUNAME: DEFW NAMNUL ; Null device
DEFW NAMMOD ; Modem.
DEFW NAMPUN ; SB-180 punch (retuns status).
DEFW NAMPAT ; Patch device
PUNSIZE EQU ($-PUNAME)/2
; Physical list pointers
LSNAME: DEFW NAMNUL ; Null device.
DEFW NAMDEC ; DEC (xon/xoff) console.
DEFW NAMSER ; Serial printer on ASCI-0.
DEFW NAMPRT ; Centronics printer.
DEFW NAM80 ; MX80 set for 80 Columns.
DEFW NAM132 ; MX80 set for 132 Columns.
LSTSIZE EQU ($-LSNAME)/2
;+
; Device Name Strings.
;-
NAMCRT: DEFZ 'CRT console (ISR)' ; 1
NAMPOL: DEFZ 'CRTP polled I/O' ; 2
NAMDEC: DEFZ 'DEC (xon/xoff) console' ; 3
NAM100: DEFZ 'VT100 DEC console' ; 4
NAM52: DEFZ 'VT52 DEC console' ; 5
NAMCRP: DEFZ 'COPY to LST: device' ; 6
NAMREM: DEFZ 'REMOTE console on ASCI0' ; 7
NAMPAT: DEFZ 'PATCH test harness' ; 8
NAM80: DEFZ 'MX80 printer' ; 9
NAM132: DEFZ 'MX132 printer' ; 10
NAMNUL: DEFZ 'NULL device' ; 11
NAMMOD: DEFZ 'MODEM on ASCI0' ; 12
NAMPUN: DEFZ 'PUN ASCI0 w/status' ; 13
NAMRDR: DEFZ 'RDR ASCI0 w/status' ; 14
NAMPRT: DEFZ 'LIST Centronics printer' ; 15
NAMSER: DEFZ 'SERIAL printer on ASCI0' ; 16
;+
; Console input table
;-
CITBLE: DEFW CIDEC ; 0 Input from DEC (xon/xoff) device.
DEFW CICRT ; 1 Input from CRT via ISR.
DEFW CIPOL ; 2 Input from CRT via polled I/O.
DEFW CIRMT ; 3 Input from ASCI-0 port.
DEFW CIDEC ; 4 Input from DEC: - Output to LST:
DEFW CI100 ; 5 Input from DEC w/ ANSI arrow keys.
DEFW CI52 ; 6 Input from DEC w/ VT52 arrow keys.
DEFW CIPAT ; 7 Input from patched device (8-bit).
;+
; Console status table
;-
CSTBLE: DEFW CSDEC ; 0 Status from DEC device.
DEFW CSCRT ; 1 Status from CRT ISR.
DEFW CSPOL ; 2 Status from CRT via polled I/O.
DEFW CSMOD ; 3 Status from ASCI-0 port.
DEFW CSDEC ; 4 Status for CRT and Printer.
DEFW CSDEC ; 5 Status from ANSI device.
DEFW CSDEC ; 6 Status from VT52 device.
DEFW CSPAT ; 7 Status from patched device.
;+
; Console output table
;-
COTBLE: DEFW CODEC ; 0 Output to DEC (xon/xoff) device.
DEFW COCRT ; 1 Output to CRT (ISR input).
DEFW COCRT ; 2 Output to CRT (Polled input).
DEFW COMOD ; 3 Output to ASCI-0 port.
DEFW COCRTP ; 4 Output to CRT and Printer.
DEFW CODEC ; 5 Output to ANSI (xon/xoff) device.
DEFW CODEC ; 6 Output to VT52 (xon/xoff) device.
DEFW COPAT ; 7 Output to patched device.
;+
; Punch device table
;-
PTBLE: DEFW CONULL ; 0 Output to null device
DEFW COMOD ; 1 Modem port
DEFW COPUN ; 2 SB-180 status checking punch.
DEFW COPAT ; 3 Patch device
;+
; Reader device table
;-
RTBLE: DEFW CINULL ; 0 Input from null device.
DEFW CIMOD ; 1 Modem port.
DEFW CIRDR ; 2 SB-180 status checking reader.
DEFW CIPAT ; 3 Patch device
;+
; List device table
;-
LTBLE: DEFW CONULL ; 0 Output to null device.
DEFW CODEC ; 1 Output to DEC device.
DEFW COMOD ; 2 Output to ASCI-0 for serial printer.
DEFW MXOUT ; 3 Any Centronics printer.
DEFW COM80 ; 4 Output to 80 column EPSON printer.
DEFW COM132 ; 5 Output to 132 column EPSON printer.
;+
; Status from List device
;-
LSTBLE: DEFW CSNULL ; 0 Status from null device.
DEFW CSDEC ; 1 Status from DEC (xon/xoff) device.
DEFW COSMOD ; 2 Status from serial line (ASCI-0).
DEFW COSMX ; 3 Status from Centronics printer.
DEFW COSMX ; 4 Status from EPSON 80 col printer.
DEFW COSMX ; 5 Status from EPSON 132 col printer.
;**************************************************************************
;*** Initialise all I/O devices. ***
;**************************************************************************
;+
; This routine is called when the IOP is loaded. It is intended to
; initialise the I/O device registers for devices used by the package. Since
; SB-180 is an interrupt driven machine we also need to reset the interrupt
; vector table as well. The interrupt vector table location is now determined
; from the HD64180 registers and the BIOS entry point from the warm boot vector
; so that this initialisation should work for any system size.
; This means that any other IOP packages loaded AFTER this IOP must also
; re-patch the interrupt vector table. Once the IOP has been initialised this
; routine is redundant and it is overlayed by the console ISR buffer.
; As polled I/O is supported (in addition to interrupt driven I/O) for
; the console device it is possible to disable ASCI-1 (Console) interrupts.
; If the ASCI-1 interrupts are disabled and this IOP is replaced by one that
; does not specifically ENABLE the ASCI-1 interrupts then console I/O will
; cease.
; >>> YOU HAVE BEEN WARNED <<<
;-
TYPBUF: DEFB 00 ; Re-use initialisation area for buffer.
;
TINIT: DI ; Turn interrupts OFF.
; Load our interrupt service vectors into the HD64180 table.
LD A,I ; Get high byte...
LD H,A ; ...into Reg H.
IN0 A,(IL) ; Read low byte from HD64180...
AND 11100000B ; ...mask...
LD L,A ; ...Reg HL contains table address.
PUSH HL ; Load IX via stack.
POP IX ; Point IX to ASCI ISR entries.
;
; Centronics ISR...
LD (IX),LOW INTLPT
LD (IX+1),HIGH INTLPT
; Channel 1 ISR...
LD (IX+16),LOW INTASCI1
LD (IX+17),HIGH INTASCI1
;
LD HL,SELERR ; Reset the TINIT entry vector...
LD (IOP+10),HL ; ...to prevent accidents.
;
LD HL,(0001) ; Get bios warm boot page address.
LD L,40H+5 ; Calculate ASCI-1 Int location.
LD (ASCIINT),HL ; Save it for later.
;
LD DE,SIGNON ; Sign-on message in printer buffer...
LD C,09H ; ...will be displayed...
CALL BDOS ; ...via the BDOS.
;
TINDONE: IN0 A,(RDR0) ; Gobble any waiting characters...
IN0 A,(RDR1) ;...
; Done.
EI ; Restore interrupts.
RET ; Exit
BUFLEN EQU $-(TYPBUF+1) ; Type-ahead buffer length (2-255).
;**************************************************************************
;*** Interrupt control. ***
;**************************************************************************
;+
; This IOP supports a polled I/O console device in addition to the interrupt
; driver. INTOGGLE is called by ASCI-1 status check routines to ensure that
; the ASCI-1 interrupts are set correctly.
;-
INTOGGLE: DI ; Disable all interrupts.
JR Z,INTON ; Turn ASCI-1 interrupts ON
; Turn ASCI-1 interrupts OFF.
IN0 B,(STAT1) ; Read current CTS1 status.
RES 3,B ; Clear ASCI-1 interrupts, save CTS1.
XOR A ; Set acc to zero (no ints).
JR INTSAVE ; Branch to save interrupt status.
; Turn ASCI-1 interrupts ON.
INTON: IN0 B,(STAT1) ; Read CTS1 status...
SET 3,B ; Enable ASCI-1 interrupts...
DEC A ; Set acc to -1 (ints on).
;
INTSAVE: OUT0 (STAT1),B ; Write interrupt status to ASCI-1.
LD (TOGGLE),A ; Save current ASCI1 interrupt status...
; Update the BIOS configuration table...
LD HL,(ASCIINT) ; Point to ASCI-1 STAT1 entry...
LD (HL),B ; ...save new ASCI-1 status.
;
EI ; Enable interrupts.
RET ; Exit - done.
;**************************************************************************
;*** Set PAT to the Device whose jump table is pointed to by HL. ***
;**************************************************************************
;+
; This Jump Table is structured as follows:
; JMP ISTAT <-- Input Status (0=No Char, 0FFH=Char)
; JMP INPUT <-- Input Character
; JMP OUTPUT <-- Output Character in C
;
; The Base Address of this Jump Table (JBASE) is passed to NEWIO in the
; HL Register Pair.
;-
NEWIO: LD (CSPTCH),HL ; Load input status vector.
LD DE,3 ; Prepare for offset to next jump
ADD HL,DE ; HL points to next jump
LD (CIPTCH),HL ; Load input character vector.
ADD HL,DE ; HL points to next jump
LD (COPTCH),HL ; Load output character vector.
RET
;**************************************************************************
;**************************************************************************
;*** Input Status, Input Character, and Output Character Routines ***
;**************************************************************************
;**************************************************************************
;+
; Input Status --
; These routines return 00 in the A Register if no input data is available,
; 0FFH if input data is available. The Z flag will reflect the contents of
; the accumulator.
;
; Input Character --
; These routines return the character (byte) in the A Register. All console
; input (with the notable exception of the PATCH device) will be masked by
; the value IOMASK, thus console input may be either 8-bit or 7-bit depending
; on the value of IOMASK. Reader input is always 8-bit.
;
; Output Character --
; These routines output the character (byte) in the C Register.
;-
;**************************************************************************
;*** I/O device test via patchable external driver. ***
;**************************************************************************
;+
; Note that this version of the external driver will automatically quit and
; pass control back to the CRT if passed a set of null jumps (JP 0000).
;-
CIPAT: LD HL,(CIPTCH) ; Read current vector...
LD A,H ; ...test for 0000
OR L ; ...
JR Z,CICRT ; Input from console if not initialised.
JP (HL) ; Branch to patch driver.
CSPAT: LD HL,(CSPTCH) ; Read current vector...
LD A,H ; ...test for 0000
OR L ; ...
JR Z,CSCRT ; Get status from console if not initialised.
JP (HL) ; Branch to patch driver.
COPAT: LD HL,(COPTCH) ; Read current vector...
LD A,H ; ...test for 0000
OR L ; ...
JR Z,COCRT ; Output to console if not initialised.
JP (HL) ; Branch to patch driver.
;**************************************************************************
;*** Polled I/O driver for ASCI-1 (Console). ***
;**************************************************************************
CSPOL: LD A,(TOGGLE) ; Get current ASCI1 interrupt status...
AND A ; ...
CALL NZ,INTOGGLE ; ...and turn OFF if they're ON.
;
IN0 A,(STAT1) ; Read status...
AND RDRF ; ...test for character.
;
JR CSCRET ; Branch to return console status.
CIPOL: CALL CSPOL ; Wait for character...
JR Z,CIPOL ; ...
;
IN0 A,(RDR1) ; Read character
AND IOMASK ; Select 7/8 bit input...
RET ; ...and exit.
;**************************************************************************
;*** Interrupt driven console with buffer - no handshaking. ***
;**************************************************************************
; ASCI1 Input
CICRT: CALL CSCRT ; Test input status
JR Z,CICRT ; Loop if not ready
; Get char from type-ahead buffer...
CINPUT: DI ; Disable interrupts while buffer is rotated.
LD HL,TYPBUF+BUFLEN; Point to end of buffer.
LD B,BUFLEN ; Length of buffer
LD C,0 ; Null (to erase old char).
; Rotate buffer (6Mhz clock and we get carried away).
CIROTATE: LD A,(HL) ; Get a character...
LD (HL),C ; Write prior character.
LD C,A ; Rotate the buffer through Reg C.
DEC HL ; Adjust pointer...
DJNZ CIROTATE ; ..and loop through entire buffer.
; Finished rotating the buffer contents...
DEC (HL) ; Adjust the character pointer.
EI ; Done with buffer - interrupts OK.
; Common console input return.
CISELCT: AND IOMASK ; Select 7/8 bit input.
RET ; Exit w/ oldest char in Acc and Reg C.
; ASCI1 Input status
CSCRT: LD A,-1 ; Set Acc=-1
LD (XON_FLAG),A ; ...signal no handshake check.
; Common status check code.
CSTATUS: LD A,(TOGGLE) ; Get current ASCI1 interrupt status...
AND A ; ...
CALL Z,INTOGGLE ; ...and turn ON if they're OFF.
;
LD A,(TYPBUF) ; Read the "characters waiting" count.
AND A ; Set Z flags READY/NOT READY.
; Common console status return.
CSCRET: RET Z ; Not ready...
OR -1 ; Set Acc to -1...
RET ; Ready.
; ASCI1 Output status
COSCRT: IN0 A,(STAT1) ; Read the status byte
AND TDRE ; Mask out the buffer empty bit
;
JR CSCRET ; Branch to return console status.
; ASCI1 Output
COCRT: CALL COSCRT ; Test the output status
JR Z,COCRT ; Loop if not ready
;
OUT0 (TDR1),C ; Xmit the data
RET ; Return
; CRT and Printer output
COCRTP: CALL CODEC ; Send char to DEC (xon/xoff) device.
JP LIST ; Send char to printer.
;**************************************************************************
;*** Terminals requiring XON/XOFF support (ANSI, DEC VT1xx and VT52) ***
;**************************************************************************
; Common DEC status (flag xon/xoff handshaking).
CSDEC: XOR A ; Get a zero...
LD (XON_FLAG),A ; ...select xon/xoff handshake check.
; Check the input status
LD A,(XOFF_OUT) ; Have we tried to stop console input?
AND A ; ...
JR NZ,CSTATUS ; No, use standard status check.
; Yes, input buffer has been filling up...check low water-mark...
LD A,(TYPBUF) ; Get current buffer count...
CP BUFLEN*1/3 ; ...is it below the minimum count?
JR NC,CSTATUS ; No, use standard status check.
;
DI ; Disable interrupts...
LD A,-1 ; ...flag console on again...
LD (XOFF_OUT),A ; ...
EI ; ...enable interrupts...
LD C,XON ; ...and send an xon...
CALL CODEC ; ...to enable console.
JR CSTATUS ; Finally return console status.
; DEC VT1xx input with "Esc [ A/B/C/D" translation.
CI100: LD A,VT100 ; Flag VT1xx terminals...
LD (TERMTYP),A ; ...
JR CIDIN ; Branch to common input routine.
; DEC VT52 input with "Esc A/B/C/D" translation.
CI52: LD A,VT52 ; Flag VT52 and Heath terminals...
LD (TERMTYP),A ; ...
JR CIDIN ; Branch to common input routine.
CIDEC: LD A,FOREIGN ; Flag unknown terminals...
LD (TERMTYP),A ; ...(ie do NO key translation).
; Common DEC input.
CIDIN: CALL CSDEC ; Get status...
JR Z,CIDIN ; ...branch until ready.
CALL CINPUT ; Get character into Reg C and Acc.
; Now convert the arrow keys if nessesary, since the ZCPR
; termcap does not support standard ANSI escape sequences!
LD A,(TERMTYP) ; Get terminal type...
CP FOREIGN ; ...test for unknown terminal...
LD A,C ; ...restore character...
RET Z ; Exit if Foreign terminal (Char in A).
; Key translation is supported...
CP ESC ; All arrow sequences start with Esc...
JR Z,CI_ESC0 ; ...branch if escape.
; Not an ESC - so exit...
JR CISELCT ; ...branch to strip msb if required.
;+
; Start of escape sequence, wait for a character for a short time. This allows
; operator entered escape sequences to get through and not hang the system.
; Tweek DELAY_VALUE if your terminal is sending slow arrow keys sequences and
; they're not being recognised... the default (800) works fine at 600 baud or
; higher with a DEC VT100.
;-
CI_ESC0: LD HL,DELAY_VALUE ; Set a delay counter...
CI_ASCLP: PUSH HL ; ...save it.
CALL CSDEC ; Test for another character.
POP HL ; Restore counter
JR NZ,CI_ESC1 ; Return NZ if READY.
; Not ready... count down...
DEC HL ; Decrement counter
LD A,H ; Test for done...
OR L ; ...
JR NZ,CI_ASCLP ; Loop until counter times out.
; Nothing else, return a single ESC to the system.
LD A,C ; ESC character was saved in Reg C...
RET ; ...
; We have a sequence ESC <char>...
CI_ESC1: CALL CINPUT ; Get the next character (in Reg C).
LD B,0 ; B=0 flags 1st char in sequence.
;
LD A,(TERMTYP) ; Test for VT100 arrow keys...
CP VT100 ; ...
JR Z,CI_100 ; ...branch if VT100.
CP VT52 ; Test for VT52 (and Heath) arrow keys.
JR Z,CI_52 ; ...branch if VT52.
; Error exit.
; Not an recognisable escape sequence...
CI_ERROR: DI ; Disable ints while buffer active.
; Reg C contains current char, B may contain "["...
; ...we know that it's an ESC sequence...
PUSH BC ; Save current character.
LD A,B ; Copy possible 2nd character...
LD C,A ; ...
AND A ; Test for any 2nd character...
CALL NZ,PUTONE ; ...and buffer any 2nd character.
POP BC ; Retrive current character in reg C.
CALL PUTONE ; Put current character into buffer
EI ; Turn interrupts back on...
LD A,ESC ; Return an ESC to the O/S...
RET ; ...exit with chars back in buffer.
; ANSI VT100 terminal support.
CI_100: LD A,C ; Restore the character to acc.
CP '[' ; We're looking for "ESC [ (A,B,C,D)"
JR NZ,CI_ERROR ; Branch, not an "Esc [" sequence.
; We have sequence "ESC [", get next character. The fact that
; the first two arrived within the delay period means that we
; should have a machine generated sequence going so no need to
; time the next character.
CI_ESC2: CALL CSDEC ; Get status...
JR Z,CI_ESC2 ; ...branch until ready.
CALL CINPUT ; Get next char.
LD B,'[' ; B="[" flags 2nd char in esc sequence.
; Check range - (we expect A,B,C or D).
; This is the entry point for VT52 sequences.
CI_52: LD A,C ; Get ASCII character to test.
SUB 'A' ; Set range 0-3...
JR C,CI_ERROR ; Branch, range error.
CP 3+1 ; Test upper limit...
JR NC,CI_ERROR ; Branch, out of range.
; Index into key table for value...
LD HL,KEY_TABLE ; Point to table...
LD E,A ; Add offset...
LD D,0 ; ...
ADD HL,DE ; Index into table...
LD A,(HL) ; ...extract entry...
RET ; ...and done.
; DEC output (watch the XON/XOFF status).
CODEC: CALL COSCRT ; Wait for ASCI register to empty...
JR Z,CODEC ; ...
; ASCI is ready, check the terminal...
LD A,(XON_STATUS) ; Get XON/XOFF status...
CP XOFF ; ...
JR Z,CODEC ; Branch if terminal is busy.
OUT0 (TDR1),C ; Xmit the data
RET ; Return
;**************************************************************************
;*** Start of Printer I/O Area for EPSON using the Centronics port. ***
;**************************************************************************
;+
; Normal 80 column output.
;-
COM80: LD A,NORMAL ; 80 char/line
JR MXSEL ; Branch to common output routine.
;+
; Compressed 132 Column output
;-
COM132: LD A,COMPRS ; 132 char/line
JR MXSEL ; Branch to common output routine
;+
; Set-up the EPSON printer
;-
SETMX: PUSH BC ; Save the current character on stack
LD (HL),A ; Save the new column number
LD C,A ; Pass the set-up char in Reg C.
CALL MXOUT ; Set-up the Printer (send control char).
LD A,C ; Re-enter MXSEL and with correct selection.
POP BC ; Restore users character.
; Fall through to send Reg C (character) out to printer.
;+
; Interrupt driven LIST output with small buffer (uses unused space in IOP).
;-
MXSEL: LD HL,COLS ; Point to current printer selection
CP (HL) ; Check selection is correct.
JR NZ,SETMX ; Branch if re-selection is required.
; Printer is set correctly...
MXOUT: CALL COSMX ; Get status of list buffer.
JR Z,MXOUT ; Wait if buffer is full.
; Buffer is not full...
DI ; Disable ints while we access buffer.
CALL STUFBUF ; Put the character into the buffer.
LD A,(WAITFOR) ; Read the ISR active flag...
AND A ; ...and test it.
JP NZ,INTLPT ; Start Printer output if nessesary.
; Buffer is active...ISR will get around to it...
EI ; Finished with buffer - turn ints on.
RET ; Exit - done.
;+
; Write character to list device output buffer.
;-
STUFBUF: LD DE,(LPUT) ; Get "put" pointer...
LD A,C ; Get data...
LD (DE),A ; ...save the data.
INC DE ; Bump "put" pointer
;
LD HL,LPCNT ; Point to "put counter"
DEC (HL) ; ...adjust counter...
CALL Z,RESPTRS ; Reset pointers if time to wrap.
LD (LPUT),DE ; Save "put" pointer...
RET ; Exit, buffer updated.
;+
; Wrap buffer pointers, Reg HL points to counter, Reg DE is address pointer.
;-
RESPTRS: LD DE,LBUFER ; Wrap pointer...
LD (HL),LSTBLEN ; ...reset counter
RET ; Exit.
;+
; Buffered LIST status routine... will another character cause pointers
; to collide? If not then return READY (NZ), otherwise return NOT READY (Z).
;-
COSMX: DI ; Don't let the ISR interfere...
LD HL,(LPUT) ; Get the "put" pointer...
LD DE,(LGET) ; ...and the "get" pointer...
LD A,(LPCNT) ; ...plus "put" counter.
EI ; Done reading - enable interrupts.
;
INC HL ; Simulate another write to buffer...
DEC A ; ...adjust counter.
JR NZ,COSMX1 ; Branch if "put" pointer did NOT wrap.
LD HL,LBUFER ; Simulate a wrapped pointer...
;
COSMX1: XOR A ; Clear the carry flag and acc.
SBC HL,DE ; Will pointers collide ? (ie =0000).
RET Z ; Exit ZERO if buffer is full...
DEC A ; ...otherwise return NZ...
RET ; ...
;**************************************************************************
;*** Start of modem system polled I/O using ASCI-0 port. ***
;**************************************************************************
;+
; Note that if DCD0 pin is high then the ASCI-0 will be totally
; disabled. This will cause problems if your modem puts its carrier detect
; on the DCD pin. When the modem disconnects any OUTPUT to ASCI-0 will cause
; the system to hang. The quick fix is to hook RTS,CTS and DCD together.
; To aid in testing the serial interface the status test for the SB-180
; special devices "RDR" and "PUN" will abort with an error message if DCD0 is
; high when ASCI-0 is accessed.
;-
;+
; Modem input status.
;-
CSMOD: LD D,0 ; Return not ready if DCD0 is HIGH.
;
CSMOD1: LD E,RDRF ; Test ASCI receive buffer status.
JR CSMRET ; Return status.
;+
; Modem output status
;-
COSMOD: LD D,0 ; Return not ready if DCD0 is HIGH.
;
COSMOD1: LD E,TDRE ; Test transmit buffer status.
; Common modem status return - Reg B contains status mask.
CSMRET: IN0 A,(STAT0) ; Set DCD0* status...
IN0 A,(STAT0) ; ...Read ASCI0 status.
TST DCD0 ; Check for DCD0*
JR NZ,DCDERR ; Branch if DCD0* is high.
AND E ; DCD0* is low - test status.
RET Z ; Not ready
OR -1 ; Set Acc to -1
RET ; Ready.
DCDERR: LD A,D ; Get DCD0 action request flag...
AND A ; ...test it...
RET Z ; Return NOT READY if selected.
; Otherwise we abort to O/S...
LD DE,DCDMSG ; Display the message...
LD C,09H ; ...via BDOS...
CALL BDOS ; ...
RST 0 ; Re-boot.
;+
; Special SB-180 Reader input (returns status or aborts if DCD0 is HIGH).
;-
CIRDR: LD D,-1 ; Abort if DCD0 is HIGH.
JR C,CSMOD1 ; Branch, special status check.
; Not a special status check - fall through to get a character.
;+
; Modem input character
;-
CIMOD: CALL CSMOD ; Check status
JR Z,CIMOD ; Wait for it.
;
IN0 A,(RDR0) ; Read a character
RET
;+
; Remote ASCI-0 input (returns either 7 or 8 bit input)
;-
CIRMT: CALL CIMOD ; Get a character
AND IOMASK ; Select 7/8 bit input...
RET ; ...and exit.
;+
; Special SB-180 Punch status call (No output, returns status or aborts if
; DCD0 is HIGH thus disabling the ASCI).
;-
COPUN: LD D,-1 ; Abort if DCD0 is HIGH.
JR C,COSMOD1 ; Branch, special status check.
; Not a special status check - fall through to get a character.
;+
; Modem output
;-
COMOD: CALL COSMOD ; Check status
JR Z,COMOD ; Wait for transmit buffer to empty.
;
OUT0 (TDR0),C ; Send the character.
RET
;**************************************************************************
;*** Null Devices. ***
;**************************************************************************
CSNULL: OR -1 ; NULL status returns always READY
RET ; Ready
CINULL: LD A,1AH ; NULL input returns CP/M EOF.
CONULL: RET ; NULL output just returns.
;+
; Record Output Routines
;
; Console Record...
;-
COPEN: EQU CSNULL ; Not implemented...
CCLOSE: EQU CSNULL ; ...
;+
; List Record.
;-
LOPEN: EQU CSNULL ; Not implemented...
LCLOSE: EQU CSNULL ; ...
;**************************************************************************
;*** Console and Printer Interrupt Service routines. ***
;**************************************************************************
;+
; Note that neither of these ISRs preserve the state of the users stack
; below the stack pointer. I haven't seen any problems with this or the
; amount of stack space that the ISRs use. However if I wasn't so short
; of space in this IOP I would use a seperate stack space for both these
; routines as a matter of good coding practice.
;-
;+
; 8-bit Port ISR (Printer).
;-
INTLPT: PUSH HL ; Save Registers...
PUSH AF ; ...
LD HL,LGCNT ; Point to "get" count.
;
LD A,(LPCNT) ; Read the current "put" count...
SUB (HL) ; Test for equality w/ "get" count.
JR Z,LISTEMTY ; Branch, buffer empty.
; Get a char from the buffer and print it.
PUSH BC ; Save registers...
PUSH DE ; ...
LD DE,(LGET) ; Load pointer to get char.
LD A,(DE) ; Read the char...
;
OUT (CENTDC),A ; Latch to the Printer
OUT (CENTDS),A ; Set STB*
OUT (CENTDC),A ; Clear STB
;
INC DE ; Bump the "get" pointer...
DEC (HL) ; ...adjust the "get counter".
CALL Z,RESPTRS ; Wrap pointers if nessesary.
LD (LGET),DE ; Save "get" pointer
POP DE ; Restore DE and BC registers...
POP BC ; ...
;
XOR A ; Get a 00
;
LISTEX: LD (WAITFOR),A ; Flag ISR status.
POP AF ; Restore registers...
POP HL ; ...
EI ; Restore interrupts...
RET ; ...exit, done.
LISTEMTY: LD A,11111111B ; Set all lines high...
OUT (CENTDC),A ; ...and clear interrupt.
; Acc = -1 ie list buffer is empty.
JR LISTEX ; Branch to restore and quit.
;+
; Console Interrupt Service Routine. Interrupts generated by:-
; 1. Incoming character (RDRF).
; 2. Receiver overrun (OVRN).
; 3. Parity Error (PE).
; 4. Framing error (FE).
; BREAK generates both overrun and framing error (OVRN AND FE).
;-
INTASCI1: PUSH HL ; Save all the registers...
PUSH DE ; ...
PUSH BC ; ...
PUSH AF ; ...
; Test for errors first.
INTASCI10: IN0 A,(STAT1) ; Get status, check for errors...
AND OVRN+PE+FE ; ...overrun, parity, framing error.
JR NZ,BREAK ; Branch if ovrn, pe or fe.
; Get the character that woke us up...
IN0 A,(RDR1) ; Read ASCI1.
; Update the XON/XOFF buffer in case anyone's using it.
LD C,A ; Save the character in Reg C.
CP XOFF ; Is it XOFF?
CALL Z,UPDATE_FLG ; Update flag if XOFF
CP XON ; Is it XON?
CALL Z,UPDATE_FLG ; Update flag if XON
; Now save character (if we can)...
CALL PUTONE ; Save character and do buffer checks.
; Check for characters buffered in ASCI1...
TYPEX: IN0 A,(STAT1) ; Get ASCI1 status...
AND RDRF ; ...check for buffered chars...
JR NZ,INTASCI10 ; Branch if another char waiting.
; ASCI is empty - restore system state...
POP AF ; Get all the registers back...
POP BC ; ...
POP DE ; ...
POP HL ; ...
EI ; Turn the interrupts on...
RET ; ...go back to sleep.
; We detected an error flag SET, if ORVN and FE then it's
; a BREAK. Ignore all errors.
BREAK: IN0 A,(CNTLA1) ; Get ASCI1 control register contents.
AND A,NOT EFR ; Clear error flag...
OUT0 (CNTLA1),A ; ...
IN0 A,(RDR1) ; ...clear 1 character from buffer.
JR TYPEX ; Ignore BREAK (I do anyway).
; Acc and Reg C contain an xon or xoff character.
UPDATE_FLG: LD A,(XON_FLAG) ; Are we using xon/xoff?
AND A ; ...
RET NZ ; Quit if not.
; We're doing xon/xoff handshaking.
LD A,XOFF ; Test the current character...
CP C ; ...in Reg C for XOFF.
JR Z,SET_XOFF ; Branch and always SET if xoffs.
; It must be an XON...
LD A,(XON_STATUS) ; Determine if we are waiting...
CP C ; ...for an XON (in Reg C).
RET Z ; Exit, doesn't follow an XOFF.
; Status was XOFF, so we must clear it and flush this XON,
; thus we kill all XOFFs (^S), all XOFF/XON pairs, but allow
; single XONs to pass through (for WordStar).
SET_XOFF: LD A,C ; Restore Acc contents...
LD (XON_STATUS),A ; ...save the handshake status...
POP HL ; Flush the return address from stack
JR TYPEX ; Exit w/o updating the buffer.
;+
; Place character from Reg C into the interrupt buffer if there is room. Check
; to see if we're running out of room and if the terminal supports xon/xoff and
; the buffer is getting close to overflowing send an xoff to the terminal to
; try and stop it. We send an xoff for each character that arrives after the
; buffer high water mark has been reached. We can't assume that the other end
; will respond instantly so there is some headroom allowed in the buffer to
; avoid dropping characters if the sender takes a while to respond.
;-
PUTONE: LD HL,TYPBUF ; Get character count...
LD A,(HL) ; ...
INC A ; ...and bump it up.
CP BUFLEN*2/3 ; Check for plenty of room...
JR C,PUTONE2 ; ...branch if lots of room.
; Buffer is getting a bit full...
CP BUFLEN ; Test for no room at all...
RET NC ; ...and quit buffer overrun.
; Still some room in the buffer...
CALL PUTONE2 ; Save the character if we can.
; See what we can do about current buffer status...
LD A,(XON_FLAG) ; Does terminal support xon/xoff?...
AND A ; ...
RET NZ ; ...quit if no xon/xoff support.
; Terminal supports xon/xoff...
LD (XOFF_OUT),A ; Flag that we've stopped input...
LD C,XOFF ; ...and send an xoff to try and...
JP CODEC ; ...stop the console (returns to caller).
; Buffer has space for next character.
PUTONE2: LD (HL),A ; Save the new character total...
LD E,A ; ...and put the count in...
LD D,0 ; ...reg DE as 16 bit value.
ADD HL,DE ; Point to the next free position...
LD (HL),C ; ...and stash current character.
RET ; ...exit, done.
;**************************************************************************
;*** Data Storage ***
;**************************************************************************
; Key translation table.
KEY_TABLE: DEFB 05H,18H,04H,13H ; ^E ^X ^D ^S Arrow keys.
; Printer control flags.
WAITFOR DEFB -1 ; Printer ISR control.
COLS DEFS 1 ; Printer line length control.
; PATCH device addresses.
CSPTCH: DEFW 0000 ; Patchable status check pointer.
CIPTCH: DEFW 0000 ; Patchable input device pointer.
COPTCH: DEFW 0000 ; Patchable output device pointer.
; Console terminal control flags.
XON_FLAG DEFS 1 ; -1 for no checks, 0 checks xon/xoff
XON_STATUS DEFB 00 ; Input handshake status (^S/^Q).
XOFF_OUT DEFB -1 ; Output handshake status (^S/^Q).
TOGGLE DEFB 00 ; Current ASCI-1 interrupt status.
TERMTYP DEFS 1 ; Terminal type
ASCIINT DEFS 2 ; Adrs of ASCI0 int byte in CONFIG block.
; Printer ISR pointers.
LPUT: DEFW LBUFER ; Pointer to next free space in buffer.
LGET: DEFW LBUFER ; Pointer to next character in buffer.
LPCNT: DEFB LSTBLEN ; Chars left before write pointer wraps.
LGCNT: DEFB LSTBLEN ; Chars left before read pointer wraps.
; Error message.
ERRMSG: DEFZ 'Error ' ; Error message for name string error.
DCDMSG: DEFB 'DCD0* abort$' ; Error message if ASCI0 disabled.
; Use whatever's left for a printer buffer.
LBUFER EQU $ ; Start of List output buffer.
LSTBLEN EQU (IOPS*128)-($-IOP) ; Size of list output buffer (2-255).
;**************************************************************************
;*** One time notice buried in printer buffer. ***
;**************************************************************************
SIGNON: DEFB ' Version '
MVERSN
DEFB ' 3-Sep-1986$'
DEFB "Written by Edmund Cramp "
DEFB "for Synergy Concepts Inc. "
DEFB "Tampa, FL"
;**************************************************************************
;*** Module size display and check ***
;**************************************************************************
PRINTE < Space available for SYSIOP .........>,%(IOPS*128)
IF $-IOP GT IOPS*128
.PRINTX * SYSIOP module is too large *
ENDIF
PRINTE < Console type-ahead buffer size ..... >,%(BUFLEN)
PRINTE < Printer output buffer size ......... >,%(LSTBLEN)
.DEPHASE
END