|
DataMuseum.dkPresents historical artifacts from the history of: DKUUG/EUUG Conference tapes |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about DKUUG/EUUG Conference tapes Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - downloadIndex: ┃ T s ┃
Length: 19313 (0x4b71) Types: TextFile Names: »serial.z«
└─⟦a0efdde77⟧ Bits:30001252 EUUGD11 Tape, 1987 Spring Conference Helsinki └─ ⟦this⟧ »EUUGD11/euug-87hel/sec1/zmac/serial.z«
; SCCS flags: serial.z 1.8 9/21/82 ; ; This program is a quick and dirty controller program ; for the simple Z80 serial interface card for the Red ; display controller. ; ; It uses two 256 byte buffers to buffer data to and from the ; host. This helps make up for the obnoxiously slow rs232. ; ; History: ; jrp 3-18-82 v1.0 Initial version by John Providenza. ; ; jrp 3-22-82 v1.1 Added code to send a Xon (Cntrlq) at reset ; if the dip switch is set to Xon/Xoff mode. ; ; jrp 4-20-82 v1.2 Added SCCS flags as comment in header and ; as a "ascii" block after a reset jmp. ; ; jrp 4-20-82 v1.3 Changed crt modem flags to RLSD = Out Buf Full, ; RI = In Buf Full. ; ; jrp 4-21-82 v1.4 Added diagnostic code to test ram, switches, and ; uart. ; ; jrp 4-30-82 v1.5 Cleaned up some code, added some more comments. ; ; jrp 5-27-82 v1.6 Fixed bug that caused output buffer to overflow ; in Hex mode. ; ; jrp 6-22-82 v1.7 Added 'end of message' command in hex mode. ; This is active only in hex mode and only if a ; non 0 byte count is specified (0 is default) ; 'l' is used to specify byte count, 'm' specifies ; the eom char. Both expect 2 hex digits following ; to specify the apropriate parameter. ; ; jrp 8-23-82 v1.8 Added code to allow send/recv in different modes. ; Thus the host can send in raw mode and receive in hex ; mode, allowing CntrlS/Q flow control. ; Also added 's' command in 'hex' mode to reset the SWTCH ; settings. ; Also added break detect to reset the mode/baud to the ; switch settings. ; switch dIN dOUT Flow Control. ; 7 6 5 ; 0 0 0 raw raw No flow control. ; 0 0 1 raw hex Xon/Xoff sent to host. ; 0 1 0 hex raw Xon/Xoff received from host. ; 0 1 1 hex hex Full Xon/Xoff. ; 1 0 0 raw raw Full modem flow control. ; 1 0 1 raw hex Full modem flow control. ; 1 1 0 hex raw Full modem flow control. ; 1 1 1 hex hex Full modem flow control. ; ; SCCS flags: serial.z 1.8 9/21/82 eject 1 ; Serial port equates. Serial equ 00H ; base address of 8250 controller. Ier equ 01H ; Interrupt Enable Reg Iir equ 02H ; Interrupt Ident Reg Lcr equ 03H ; Line Control Reg Mcr equ 04H ; Modem Control Reg Lsr equ 05H ; Line Status Reg Msr equ 06H ; Modem Status Reg ; These equates define bits in the Msr. DsrIn equ 05 ; Data Set Ready input CtsIn equ 04 ; Clear to Send input InMt equ 06 ; No data from display controller = 1 (Ring In) OutMt equ 07 ; Crt ready for next byte = 1 (Rcvd Line Signal Detct) ; These equates define bits in the Lsr DataRdy equ 00 ; Input data ready. Break equ 04 ; Break condition. XmitMt equ 05 ; Xmitter buffer empty. ; These equates define bits in the Mcr DtrOut equ 00 ; Data terminal ready output. RtsOut equ 01 ; Request to send output. ; Misc definitions. Crt equ 80H ; Parallel port to display controller. Baud equ 40H ; Switches port. Stack equ 0FFFFH ; Mailbox equates. Head equ 0 Tail equ 1 Count equ 2 Base equ 3 Status equ 4 UnChar equ 5 ; Should be used only for CntrlS and CntrlQ ; Equates for the Queue status byte XmitOff equ 00 ; xmitter is disabled. ; Baud/Switch equates. Bmask equ 0FH Rawout equ 020H RObit equ 5 Rawin equ 040H RIbit equ 6 Xon equ 080H Xonbit equ 7 ; Some ASCII character equates. CntrlS equ 19 ; Xoff CntrlQ equ 17 ; Xon Cr equ 13 ; Carriage return. eject 1 ORG 0FC00H RAM_START: ; Variable declarations ; Ram is in the top 1K of memory. ; Queues. ; These are the actual data buffers. The only routine that should use ; these labels re INIT_V to set the mailbox data pointers up. ; All I/O is via GETQ and PUTQ routines. INBUF: block 256 ; input buffer q. OUTBUF: block 256 ; output buffer q. UNUSED: block 256 ; unused ram ; Now the ram for variables and stack. SWTCH: block 1 ; Current baud/switches ; Variable for the H_to_Q routine ; It holds the upper nibble of hex until the lower one arrives. ; Bit 0 = 1 for empty, 0 for upper nibble full. H_to_QV: block 1 ; End of message variables. MESS_LEN: block 1 ; How long messages are. MESS_CNT: block 1 ; Number of chars in current message. EOM_CHAR: block 1 ; The end of message char. ; In and Out queues variables. INBOX: block 6 OUTBOX: block 6 eject 1 ; Mainline loop. ORG 0 JP RESET ; Jmp to the code ; Put in ID string ascii 'serial.z 1.8' RESET: LD SP, Stack CALL CHECK ; Check the hardware out. CALL INIT_HW ; Init the hardware devices. CALL INIT_V ; Init the variables. LD IX,OUTBOX ; Point to the outbox. LD A,(SWTCH) ; Check if we're in Xon/Xoff mode. AND Xon LD A,Cntrlq ; Send a Xon to host if we're in that mode CALL NZ,PUTQ ; Now loop checking for data available from host or display controller. ; Also check if we can send data to them. LOOP: IN A,(Lsr) ; Get the line status. LD C,A IN A,(Msr) ; Get the modem status. LD B,A ; and save it ; B = Msr, C = Lsr. ; Check for break condition. BIT Break,C ; test the bit in the Lsr JR Z,LOOP1 CALL SETBAUD ; reset the SWTCH variable. CALL INIT_V ; reset all the variables JR LOOP LOOP1: CALL HOST_IN CALL DISP_IN CALL DISP_OUT CALL HOST_OUT JR LOOP eject 1 ; Check if data is ready from host. HOST_IN: BIT DataRdy,C ; Data ready? RET Z ; Ret if no. ; Handle a byte from the Host. LD IX,INBOX ; data will go into the Input Q. LD A,(SWTCH) ; check for Raw or encoded mode. LD H,A AND Rawin ; NZ for Raw mode IN A,(Serial) ; get the data byte. JR Z,HEX_IN ; Jmp if hex data in. RAW_IN: ; Process Raw data CALL PUTQ JP STOP_IN ; stop the input if needed. HEX_IN: AND 7FH ; Kill any parity bit. CP ' ' ; Printable ASCII? JR NC,PRINT ; Jmp if yes ; Control character. CP Cr ; Carriage Ret? JR NZ,IN_FLOW ; Jp if no. LD A,1 ; Set the H_to_Q variable to empty. LD (H_to_QV),A ; This flushes any partially assembled byte. RET ; Done ; Test for Xon/Xoff commands. IN_FLOW: BIT Xonbit,H ; Are we sensitive to them? RET Z ; Ret if no. LD HL,OUTBOX+Status ; Get a pointer to our outbox status. CP CntrlS ; Xoff our transmitter? JR NZ,NOT_XOFF ; Jmp if no. OFF: SET XmitOff,(HL) RET NOT_XOFF: CP CntrlQ ; Xon our xmitter? RET NZ ; ret if no. ON: RES XmitOff,(HL) RET ; Printable char received from host. PRINT: ; Printable character received in hex mode. SET 5,A ; Convert to lower case. CP 'l' ; Message length command? JR NZ,PRINT1 ; Jmp if no. CALL GET_HEX ; Get byte from UART LD (MESS_LEN),A ; Set the message length. LD (MESS_CNT),A ; Reset the number of chars sent so far. RET PRINT1: CP 'm' ; EOM char set command? JR NZ,PRINT2 CALL GET_HEX ; Get byte from UART LD (EOM_CHAR),A RET PRINT2: CP 's' ; change SWTCH command? JR NZ,PRINT3 CALL GET_HEX ; Get byte from UART CPL ; Toggle them. LD (SWTCH),A RET PRINT3: CALL H_to_Q ; Pack the encoded data into bytes. JP STOP_IN ; stop the input if needed. eject 1 ; Data ready from controller? DISP_IN: BIT InMt,B ; data from controller? RET NZ ; ret if no. LD IX,OUTBOX LD A,(IX+Count) ; Get the Q count. ADD A,3 ; Check if Q has room for 3 more bytes. RET C ; ret if no LD A,(SWTCH) ; check if we need to encode the data. AND Rawout IN A,(Crt) ; get the data from the crt. JP NZ,PUTQ ; send the raw data and return. ; hex data out to host. CALL B_to_H ; convert byte to hex format and stick in Q. ; Check if we need to stick an EOM char in. LD A,(MESS_LEN) ; Get the length. AND A RET Z ; Zero means no EOM character to be sent. LD HL,MESS_CNT ; Point to the counter. DEC (HL) ; Time to send a EOM char? RET NZ ; Ret if no. LD (HL),A ; reset the length. LD A,(EOM_CHAR) ; Get the char and stick it in the Q. JP PUTQ ; and return when done eject 1 ; Controller ready for data? DISP_OUT: BIT OutMt,B ; controller ready for data? RET Z ; Jmp if no LD IX,INBOX CALL GETQ ; get a byte for controller. RET C ; ret if no byte available. OUT (Crt),A ; send char to display. JP STRT_IN ; re-enable host xmitter if needed. eject 1 ; Host ready for data? HOST_OUT: BIT XmitMt,C ; Uart xmitter empty? RET Z ; ret if no. LD IX,OUTBOX ; Get OutBox pointer. LD A,(SWTCH) ; Check for Xon mode AND Xon JR NZ,H_O_Xon ; Jp if Xon mode. BIT CtsIn,B ; Clear to send? RET Z ; ret if no. JR H_O_Send ; We are clear to send. H_O_Xon: LD A,(OUTBOX+UnChar) AND A JR NZ,H_O_Send ; Always send an 'UnChar' BIT XmitOff,(IX+Status) RET NZ ; ret if xmitter is disabled. H_O_Send: CALL GETQ RET C ; Ret if no character available. OUT (Serial),A RET eject 1 ; Check the hardware out. ; Call this routine only after a external reset!!!! CHECK: ; Check the baud switch (really crude). IN A,(BAUD) ; Get the baud switch. LD B,A ; Save it. IN A,(BAUD) CP B ; Same as last time? BAD_B: ; Switch ERROR - Can't read switches twice in a row. JR NZ,BAD_B ; Loop if no. ; Check the ram. ; Write the complement of the low byte of address out to all ram, ; then check if it stayed the same. ; Note that this destroys all ram contents. POP DE ; Save the return address in a register. LD HL,RAM_START ; Get the first address of ram. LD B, NOT [RAM_START & 0FFH] LD C,B ; Get complement of low address byte. ; Load the ram with the pattern. RAM1: LD (HL),B DEC B INC HL LD A,H ; Test for done. OR L JR NZ,RAM1 ; Loop till all locations written. LD HL,RAM_START ; Get the first address of ram. ; Check if ram agrees with what should be there. RAM2: LD A,(HL) ; Get the byte. XOR C ; Same as its low address byte? JR Z,RAM6 ; Jmp if yes. ; Ram error. We have three loops: low bad, high bad, both bad. LD B,A ; Save the symptom. AND 0FH ; Low nibble bad? RAM3: ; Ram ERROR - bad high nibble. JR Z,RAM3 ; Jmp if no. LD A,B ; get the symptom back. AND 0F0H ; High nibble bad too? RAM4: ; Ram ERROR - bad low nibble. JR Z,RAM4 ; Loop if error. RAM5: ; Ram ERROR - both nibbles bad. JR RAM5 RAM6: DEC C INC HL LD A,H ; Done? OR L JR NZ,RAM2 ; Jmp if no. PUSH DE ; Fix the stack back up. ; Check out the National Semi INS8250 Uart. ; Since we were reset, Lcr should be zero. IN A,(Lcr) ; Get the Line Control reg AND A U0: ; Uart ERROR - Lcr not reset properly. JR NZ,U0 ; Loop if error. LD A,80H OUT (Lcr),A ; And set the Divisor access bit. IN A,(Lcr) ; Check that it got set. CP 80H ; Still set? U1: ; Uart ERROR - Lcr won't hold divisor access bit. JR NZ,U1 ; Loop if error. LD A,3 ; Try to set 38.4K baud OUT (Serial),A ; Ld the divisor. IN A,(Serial) ; Test that it loaded OK. SUB 3 ; Check if same (also set A to zero) U2: ; Uart ERROR - unexpected low divisor. JR NZ,U2 ; Loop if error. OUT (Ier),A ; Set high byte to zero IN A,(Ier) AND A ; Still zero? U3: ; Uart ERROR - unexpected high divisor. JR NZ,U3 ; Loop if no (ie, error). IN A,(Lcr) ; Get the Line reg back. SUB 80H ; Is it the same as before? U4: ; Uart ERROR - unexpected Lcr value after setting divisor. JR NZ,U4 ; loop if error. OUT (Lcr),A ; Turn off divisor access bit. IN A,(Lcr) ; Check it. AND A U5: ; Uart ERROR - Lcr won't reset after setting divisor. JR NZ,U5 LD A,7 OUT (Lcr),A ; 8 bits, no parity, 2 stop bits IN A,(Lcr) SUB 7 ; Test if the same (also set A to zero) U6: ; Uart ERROR - Can't set proper operating Lcr. JR NZ,U6 ; If we succeed, assume Lcr is Ok. OUT (Ier),A ; Disable all 8250 interrupt conditions (set to 0). IN A,(Ier) AND A U7: ; Uart ERROR - Can't reset Ier. JR NZ,U7 RET eject 1 ; Init the hardware. INIT_HW: CALL SETBAUD ; Set the Uart baud LD A,7 OUT (Lcr),A ; 8 bits, no parity, 2 stop bits XOR A ; Disable all 8250 interrupt conditions. OUT (Ier),A LD A,3 ; Dtr, Rts on. OUT (Mcr),A ; Perform the I/O diagnostic with the controller. ; Wait for data from controller, then echo it back. INITH1: IN A,(Msr) ; Check if controller data ready. BIT InMt,A ; Ready? JR NZ,INITH1 ; Jmp if no. IN A,(Crt) ; Get the data. OUT (Crt),A ; And send it back to controller. RET ; Init the variables. INIT_V: XOR A ; zero A ; Init the Q's LD IX,INBOX ; Init the inbox. LD (IX + Head),A LD (IX + Tail),A LD (IX + Count),A LD HL,INBUF LD (IX + Base),H LD (IX + Status),A LD (IX + UnChar),A LD IX,OUTBOX ; Init the outbox. LD (IX + Head),A LD (IX + Tail),A LD (IX + Count),A LD HL,OUTBUF LD (IX + Base),H LD (IX + Status),A LD (IX + UnChar),A ; Init the H_to_Q variable. LD A,1 LD (H_to_QV),A ; init the 'end of message' stuff LD A,Cr ; default r is a carriage return. LD (EOM_CHAR),A XOR A LD (MESS_LEN),A LD (MESS_CNT),A RET eject 1 ; These routines handle the input and output queues. ; The Q pointer is passed in IX, result/source in A. ; Queues must be 256 bytes long. We use only 8 bit ; arithmetic for Q manipulation. ; A Q is defined as 6 bytes of status: ; Tail Offset for getting next char ; Head Offset for putting next char ; Count Number of chars in q ; Base High byte of the q origin ; Status Status of Q ; UnChar The 'un_get' char if non-zero ; and 256 bytes of storage. ; GETQ: ; Get an element from the Q. ; entry ix = Q pointer ; exit a = result ; ca = set for empty Q, cleared for full Q. ; bc & de are unchanged. ; hl = garbage ; LD A,(IX + UnChar) ; Get the unget char LD (IX + UnChar),0 ; Set the byte to 0 (empty). AND A RET NZ ; Ret if we got an unget char. ; A == 0 here. CP (IX + Count) ; Get the q count SCF RET Z ; empty Q return (Count == 0). DEC (IX + Count) ; one less item in the Q. LD L,(IX + Tail) ; get a pointer to the element in the Q. LD H,(IX + Base) INC (IX + Tail) ; bump the pointer to the next char. OR (HL) ; Get the element, and clear the carry. RET PUTQ: ; Routine to put a char in a Q. ;entry ix = pointer to Q structure. ; a = char to put. ;exit hl = garbage ; a, bc & de unchanged. ; Ca = 1 for Q full, character discarded. ; INC (IX + Count) ; Bump the Q count. QPUT_ERR: JR Z,QPUT_ERR QPUT1: LD H,(IX + Base) LD L,(IX + Head) LD (HL),A ; Put the char in the Q INC (IX + Head) AND A ; Clear the carry bit RET eject 1 ; These routines pack and unpack bytes into Hex ; suitable for sending as ASCII over a serial line. ; H_to_Q takes Hex characters ; and packs them into 8 bit bytes to send to the display. ; B_to_H takes bytes from the display and converts them into ; the Hex character stream. ; ; Both routines use Q calls. IX must be set up with the proper ; Q address. ; ; H_to_Q: ; ; entry A = Ascii Hex char (0-9, a-f) ; IX = Q pointer ; exit A, Hl = Garbage ; bc, de = unchanged. ; Ca = 1 if Q too full. ; CALL H_to_B ; convert the character to binary. LD HL,H_to_QV ; Point hl to our variable BIT 0,(HL) ; check if the upper nibble is full. JR Z,H_SEND ; Jmp if yes. ADD A,A ; Move the nibble to the high 4 bits. ADD A,A ADD A,A ADD A,A LD (HL),A ; Save away the high nibble with low nibble = 0. RET H_SEND: OR (HL) ; Merge in the upper nibble from ram. LD (HL),1 ; Set the variable to empty. JP PUTQ ; Send the byte and return. eject 1 B_to_H: ; B_to_H takes the byte in A and splits it into two hex characters ; to be sent to the Q specified in IX. ; ; Entry A = byte of data to convert to Hex. ; IX = Q address. ; Exit A E Hl = garbage ; D Bc Ix = unchanged. ; LD E,A ; Save the byte RRA ; Move the upper nibble to low nibble. RRA RRA RRA AND 0Fh ; Get only the upper nibble. CP 10 ; 0 thru 9? JR C,B_to_H1 ; Jmp if yes. ADD A,'A'-'0'-10 B_to_H1: ADD A,'0' CALL PUTQ LD A,E ; Get the byte back AND 0Fh ; Mask for only low nibble. CP 10 ; 0 thru 9? JR C,B_to_H2 ; Jmp if yes. ADD A,'A'-'0'-10 B_to_H2: ADD A,'0' JP PUTQ ; Send and return. eject 1 GET_HEX: ; This routine gets two hex characters from the UART and ; munches them into a byte in A. ; Entry: No Params. ; Exit: A=byte H = trash ; all others unchanged (except for flags) IN A,(Lsr) ; Get the line status BIT DataRdy,A ; Data ready from host? JR Z,GET_HEX ; Jmp if no. IN A,(Serial) ; get the data. CALL H_to_B ; convert to binary. ADD A,A ; Shift up 4 bits ADD A,A ADD A,A ADD A,A LD H,A ; Save in B GET_HX1: IN A,(Lsr) ; Get the line status BIT DataRdy,A ; Data ready from host? JR Z,GET_HX1 ; Jmp if no. IN A,(Serial) ; get the data. CALL H_to_B ; convert to binary. OR H RET ; A = 2 input chars munched together. ; Convert hex char to binary. H_to_B: SET 5,A ; convert to lower case. SUB '0' ; less than 0? JR C,HB_ERR ; Jmp if out of bounds. CP 10 ; bigger than 9? RET C ; Ret if no (0..9) SUB 'a'-'0'-10 ; try to make it range 10-15 CP 10 JR C,HB_ERR ; Jmp if out of bounds. CP 16 RET C ; Ret if hex. HB_ERR: XOR A ; Set to zero. RET eject 1 SETBAUD: ; This routine reads the BAUD switches and looks the code ; up in the BTABLE to set the baudrate of the 8250 serial chip. ; ; Entry No parameters ; exit A Hl De = garbage. IN A,(Lcr) ; Set the divisor access bit on OR 80H OUT (Lcr),A IN A,(Baud) ; Get the baud rate code LD (SWTCH),A AND Bmask ; Get only the baud specifier bits. ADD A,A ; Double it to index into table. LD HL,BTABLE ; Index into table to get the divisor LD E,A LD D,0 ADD HL,DE LD A,(HL) ; Get the low order divisor byte OUT (Serial),A INC HL LD A,(HL) ; Get the high divisor byte OUT (Serial+1),A IN A,(Lcr) ; Set the divisor access bit off AND 7FH OUT (Lcr),A RET ; Baud rate look up table ; Only allow 16 entries. BTABLE: WORD 5 ; 38.4 Kbaud WORD 10 ; 19.2 WORD 20 ; 9600 WORD 27 ; 7200 WORD 40 ; 4800 WORD 53 ; 3600 WORD 80 ; 2400 WORD 107 ; 1800 WORD 160 ; 1200 WORD 320 ; 600 WORD 640 ; 300 WORD 1280 ; 150 WORD 1428 ; 134.5 WORD 1745 ; 110 WORD 2560 ; 75 WORD 3840 ; 50 eject 1 ; STRT_IN and STOP_IN are called when the Input Q is may be too full/empty. ; They check and enable/disable the host xmitter apropriately. ; STRT_IN: ; Entry No registers set. ; Exit A Ix Hl = garbage. ; Bc De = unchanged. ; LD IX,INBOX ; Point to the Q. BIT XmitOff,(IX + Status) ; Is it off? RET Z ; ret if no. LD A,40 ; Check if we've gone below low water mark. CP (IX + Count) RET C ; Ret if no, Q still too full. LD A,(SWTCH) ; get the switch settings. BIT Xonbit,A JR Z,STRT_DTR ; Jmp if rs232 modem mode flow control. ; Try to use Xon/Xoff control flow methods. BIT RObit,A ; Raw Output mode? RET NZ ; No way to start/stop host xmitter. LD HL,OUTBOX+UnChar LD A,(HL) ; Anything in unget spot? AND A RET NZ ; Ret if yes. LD (HL),CntrlQ ; 'unget' a control Q. JR STRT_END ; Set DTR bit on. STRT_DTR: IN A,(Mcr) ; get the modem controls. SET DtrOut,A OUT (Mcr),A STRT_END: RES XmitOff,(IX + Status) ; Mark as enabled. RET STOP_IN: ; Entry No registers set. ; Exit A Ix Hl = garbage. ; Bc De = unchanged. ; LD IX,INBOX ; Point to the Q. BIT XmitOff,(IX + Status) ; Already disabled? RET NZ ; ret if yes. LD A,256-40 ; Check if we've gone above high water mark. CP (IX + Count) RET NC ; Ret if no, Q still too empty. LD A,(SWTCH) BIT Xonbit,A ; test for Xon/Xoff vs. modem flow cntrl. JR Z,STP_DTR ; jmp if rs232 modem mode ; try to send an Xoff to the host. BIT RObit,A ; Are we in raw out? RET NZ ; Can't control the host xmitter. LD HL,OUTBOX+UnChar LD A,(HL) ; Anything in unget spot? AND A RET NZ ; Ret if yes. LD (HL),CntrlS ; 'unget' a control S. JR STP_END ; Modem mode flow control, set DTR bit off. STP_DTR: IN A,(Mcr) ; get the modem controls. RES DtrOut,A OUT (Mcr),A STP_END: SET XmitOff,(IX + Status) ; Mark as disabled. RET END