TITLE MULRPT - 'Multi-port AX.25 Repeater' .Z80 ; Multi-port AX.25 packet-radio repeater. ; ; This program is intended to run on most any computer which: ; 1) Has a Z80-SIO with external clock synchronization ; 2) Supports Z80 mode 2 interrupts. ; 3) Has a Z80-CTC with at least one channel capable of ; periodic interrupt generation. ; 4) Can support all of the above independently of the ; operating system, if any. ; The supplied version is for a Xerox 820 computer. The ; code and the initialized data are entirely contained in ; EPROM. ; Frames can be received on any channel and retransmitted ; on another channel or the same channel. When a frame is ; received, the program will examine the address field to ; determine the retransmission channel for that frame. ; There are three ways in which a retransmission channel ; can be specified, listed in order of priority: ; 1) Next repeater address - If the next repeater address ; following the address of this repeater is found in a ; table of repeaters for a given channel, the frame will ; be retransmitted on that channel. ; 2) Default SSID - If the next repeater address following ; the address of this repeater has the default SSID for ; a given channel, the frame will be retransmitted on ; that channel. ; 3) Destination station - If the destination address is ; found in a table of destination addresses for a given ; channel and the frame has been fully repeated, the ; frame will be retransmitted on that channel. ; Failing resolution of the destination channel by the above ; rules, the frame will be retransmitted on the default ; transmission channel for that reception channel. The ; default transmission channel may be the same as the ; reception channel, in which case the repeater will appear ; as a one-port machine to that frame. Clear? I bet. ; Any (reasonable) number of physical channels may be ; supported by this software. ; Number of channels. There must be a separate set of SIO ; driver routines for each channel. These routines are ; located in HDLSIO.MAC, which must be assembled once for ; each channel. SUBTTL 'Definitions and Data Structures' PAGE ; Frame buffer data structure: ; Link - two-byte link to next buffer in list, or 0 ; if last buffer ; Channel - one-byte received channel number ; Count - two-byte count of bytes in frame ; Address count - two-byte count of address bytes ; Note: Count does not include address bytes. ; Frame buffer offset equates FB.LNK EQU 0 FB.CHA EQU 2 FB.CNT EQU 3 FB.ACT EQU 5 FB.DAT EQU 6 ; Channel definition data structure: ; Status - one-byte channel status ; Root - two-byte transmission frame list root ; Sked - two-byte address of XSKED subroutine ; Cdstat - two-byte address of CD status routine ; Offsets into channel data structure CH.CHA EQU 0 ;Channel number CH.RXS EQU 1 ;Channel receive mode state CH.TXS EQU 2 ;Channel transmit mode state CH.ROT EQU 3 ;Transmission list root CH.SKD EQU 5 ;XSKED routine address CH.CDS EQU 7 ;CDS routine address CH.RXF EQU 9 ;Receive frame buffer address CH.RXP EQU 11 ;Receive data pointer CH.TXF EQU 13 ;Transmit frame buffer address CH.TXP EQU 15 ;Transmit data pointer CDSIZE EQU 17 ;Size of data structure SUBTTL 'Equates' PAGE INCLUDE RCONFIG.LIB ; AX.25 equates ADRLTH EQU 7 ;Length of a single address HBIT EQU 6 ;Position of H bit in SSID byte MAXRPT EQU 8 ;Maximum number of repeater addresses MAXADR EQU ADRLTH*(MAXRPT+2) MAXI EQU 256 ;Maximum I field length MAXD EQU MAXI+2 ;Max. data (non-address) count MAXFRM EQU MAXADR+MAXD ;Max frame length, addr + control + ;PID + I fields BUFSIZ EQU MAXFRM+FB.DAT ;Size of frame buffer ; RPTTAB (repeater tables) links EXT OURADR EXT NUMRPT,NUMDST EXT DEFSID,DEFCHA EXT RPTTAB SUBTTL 'Macro Definitions' PAGE ; Macro definitions ; Channel definition macro. DEFCH MACRO CHN EXT XSKED&CHN,CDS&CHN CSEG DEFB CHN ;Channel number DEFB 0,0 ;Channel states DEFW 0 ;Transmission frame list root DEFW XSKED&CHN ;XSKED address DEFW CDS&CHN ;CDS address DEFW 0,0 ;Receive pointers DEFW 0,0 ;Transmit pointers DSEG CH&CHN: DEFS CDSIZE ;;Reserve RAM area ENDM ; Macro to create entry points for SIO subroutines SUBS MACRO CHN ENTRY NXTHO&CHN,NXTHI&CHN,ODONE&CHN NXTHO&CHN: LD IX,CH&CHN JP NXTHO NXTHI&CHN: LD IX,CH&CHN JP NXTHI ODONE&CHN: LD IX,CH&CHN JP ODONE ENDM SUBTTL 'Main Program' PAGE ; Initialization - performed only at hardware reset, with ; interrupts disabled. EXT HDWINT PUBLIC $MEMRY DSEG ZSTART: CSEG START: DI ;Just in case... JR START1 SIZRAM: DEFW RAMSIZ ;Available RAM size $MEMRY: DEFS 2 ;End of allocated RAM ;(Supplied by Linker) ; Zero the RAM area START1: LD SP,STACK ;Init the stack first LD HL,ZSTART ;Zero the RAM LD BC,(SIZRAM) ;Number of bytes to zero ZLOOP: LD (HL),0 INC HL DEC BC LD A,B OR C JR NZ,ZLOOP PAGE ; Initialize the frame buffers LD HL,ZSTART ;Calculate end of RAM LD DE,(SIZRAM) ;Get RAM size ADD HL,DE ;End of available RAM LD DE,($MEMRY) ;Start of available memory OR A ;Clear carry SBC HL,DE ;Calculate usable buffer space LD DE,-BUFSIZ ;Buffer size LD B,0 BUFLOP: ADD HL,DE ;Subtract buffer size JR NC,INTFB ;No more buffer space INC B JR BUFLOP INTFB: LD DE,($MEMRY) ;Where the buffers are LD (FRELST),DE ;Init the free list root LD HL,BUFSIZ ;Buffer increment IFLOOP: PUSH HL ADD HL,DE ;Point to next frame EX DE,HL LD (HL),E ;Store link INC HL LD (HL),D POP HL ;Restore frame increment DJNZ IFLOOP ;Continue EX DE,HL LD (HL),0 ;Null pointer in last frame INC HL LD (HL),0 ; Inititialize channel data structures LD HL,CHDEFS ;Move initial channel data... LD DE,CH0 ;...to RAM LD BC,NUMCH*CDSIZE LDIR ; Initialize hardware CALL HDWINT ;Initialize the hardware EI ;Let 'er rip PAGE ; Main loop - call the received frame processor, PROCRX. ; Call the channel trnsmission routine once for each channel. ; This loop executes continuously. LOOP: CALL PROCRX LD A,0 ;Channel number LD B,NUMCH ;Number of channels CHLOOP: CALL GETCDS ;Get the chan. data struct. PUSH AF ;Save the regs PUSH BC CALL XMIT ;Transmit if needed POP BC ;Restore the regs POP AF INC A DJNZ CHLOOP ;Next channel JR LOOP ;Start over SUBTTL 'PROCRX - Received Frame Processing Subroutine' PAGE ; PROCRX - Get received frames from list and process. ; A received frame may be disposed of in one of two ways. ; Either it is discarded back onto the free list, or it is ; linked to a transmission list for a channel for subsequent ; transmission. ; ; Process: ; Examine address field length. If not a multiple of ; 7 bytes in length, discard frame. ; If address field contains fewer than three addresses, ; discard frame. ; Find first repeater address with H bit reset. If ; none, discard frame. ; If repeater address is not same as defined address, ; discard frame. ; Set H bit in repeater address. ; If repeater address is not last address, compare ; following address to repeater table entries. On a ; match, link frame to specified channel. ; If repeater address is not last address, compare ; following SSID to default SSID entries. On a ; match, link frame to specified channel. ; If repeater address IS last address, compare ; destination address to destination table entries. ; On a match, link frame to specified channel. ; No match found, link frame to default channel. ; ; This process is repeated until the received frame list ; is empty. ; Get frame from list or, if none, return. PROCRX: LD HL,RXLIST ;Get next received frame CALL FBGET RET Z ;List is empty LD (CURRXF),HL ;Save frame buffer pointer ; Test for address field length a multiple of ADRLTH LD DE,FB.ACT ;Point to address count ADD HL,DE LD A,(HL) ;Get address count LD B,-ADRLTH ;Must be multiple of ADRLTH LTHCHK: ADD A,B ;Subtract an address subfield JR Z,LTHOK ;Is a multiple, do it to it JR C,LTHCHK ;Keep checking JP DISCARD ;Not a legal address PAGE ; Test for address field length >= ADRLTH * 3. If OK, ; find first repeater address with H bit reset LTHOK: LD A,(HL) ;Get address length SUB ADRLTH*2 ;Calculate repeater addr lth JP Z,DISCARD ;Address too short LD HL,(CURRXF) ;Get buffer address LD DE,FB.DAT+(ADRLTH*3)-1 ADD HL,DE ;Point to first rptr addr SSID CHKH: LD B,A ;Save remaining length BIT HBIT,(HL) ;Is H bit reset? JR Z,ISITME ;Yes, go test for my address LD DE,ADRLTH ;Next address ADD HL,DE LD A,B ;Get remaining address length SUB ADRLTH ;Any address left? JR NZ,CHKH JP DISCARD ;Fully repeated frame ; Compare address with our own. ISITME: SET HBIT,(HL) ;Set the H bit LD DE,-(ADRLTH-1) ;Point to start of address ADD HL,DE LD DE,OURADR ;Our address string CALL ADRCMP ;Does it match? JR NZ,DISCARD ;No, toss it away ; Frame must be repeated. LD DE,ADRLTH ;Point to next address ADD HL,DE EX DE,HL ;DE = address pointer ; Determine if next repeater address matches any repeater ; table entry. LD A,B ;Get remaining length SUB ADRLTH ;Last address in field? LD B,A JR Z,CHKDST ;Yes, skip table search LD BC,NUMRPT ;Point to # of repeaters LD HL,RPTTAB ;Point to call table CALL SEARCH ;Check for address JR C,LINKRX ;Go link the frame PAGE ; Test for default SSID LD HL,ADRLTH-1 ;Point to SSID of next addr ADD HL,DE LD A,(HL) AND 0FH ;SSID bits only LD HL,DEFSID ;Get default SSID table LD C,0 ;Channel number LD B,NUMCH ;Number of table bytes PROC02: CP (HL) ;Is SSID = default? JR Z,PROC03 ;Yes, use this channel INC C INC HL ;Next channel SSID DJNZ PROC02 ;Next channel JR USEDEF ;Use default channel PROC03: LD A,C ;Get channel number JR LINKRX ;Link the frame ; If frame fully repeated, determine if destination address ; matches any destination table entry. ; First, form pointer to destination addresses. CHKDST: LD HL,RPTTAB ;Get address of call table LD DE,NUMRPT ;Point at # repeaters LD B,NUMCH ;Number of channels PROC04: LD A,(DE) ;Get # of entries for channel OR A ;None? JR Z,PROC06 ;Yes, skip offsetting PUSH DE LD DE,ADRLTH ;Offset per entry PROC05: ADD HL,DE ;Add offsets DEC A JR NZ,PROC05 POP DE ;Restore # pointer PROC06: INC DE ;Next channel DJNZ PROC04 EX DE,HL ;Table pointer to DE LD HL,(CURRXF) ;Get frame buffer address LD BC,FB.DAT ;Point to destination address ADD HL,BC EX DE,HL LD BC,NUMDST ;Point to # table CALL SEARCH JR C,LINKRX PAGE ; No routing determined. Use default channel. USEDEF: LD HL,(CURRXF) ;Frame buffer address REPT FB.CHA ;Point to receiving channel INC HL ENDM LD B,(HL) ;Get receiving channel # LD HL,DEFCHA-1 ;Point to defaults table INC B PROC07: INC HL ;Next channel DJNZ PROC07 LD A,(HL) ;Get default channel ; Link the frame to the transmission list LINKRX: CALL GETCDS ;Get chan. data struct. PUSH IX POP HL LD DE,CH.ROT ;Get address of list root ADD HL,DE LD DE,(CURRXF) ;Get frame buffer address CALL FBPUT ;Link to tx list JP PROCRX ;End of routine ; Discard frame. DISCARD: LD HL,(CURRXF) ;Get frame buffer address CALL FBDALC ;Deallocate frame JP PROCRX DSEG CURRXF: DEFS 2 ;RX frame in process CSEG SUBTTL 'XMIT - Transmission Subroutine' PAGE ; XMIT - Perform transmission if needed. ; Entry parameters: ; IX = Pointer to channel data structure. ; Return parameters: ; None ; Registers IX and IY preserved. All other registers trashed. XMIT: LD A,(IX+CH.TXS) ;Are we already xmitting? OR A RET NZ ;Yes, nothing to do LD A,(IX+CH.ROT) ;Is there a frame list? OR (IX+(CH.ROT+1)) RET Z ;No, nothing to do LD L,(IX+CH.CDS) ;Get address of CDS sub. LD H,(IX+(CH.CDS+1)) CALL VECTOR ;Is the channel busy? OR A RET NZ ;Yes, can't do it now LD (IX+CH.TXS),1 ;Show transmitter running LD L,(IX+CH.SKD) ;Get address of XSKED routine LD H,(IX+(CH.SKD+1)) CALL VECTOR ;Schedule transmission RET SUBTTL 'NXTHO - Frame Transmission Service Routine' PAGE ; NXTHO - Routine supplies each character for transmission. ; Entry parameters: ; IX = Address of channel data structure ; Return parameters: ; A = 0FFH if "next data byte" ; = 0 if end of frame with more to follow ; = 1 if end of transmission ; B = data byte to transmit (if A = 0FFH) ; ; The state of the transmitting "machine" represented by ; this subroutine is contained in the channel data ; structure element CX.TXS. The states are: ; 0 - No transmission in progress ; 1 - Inactive, no frame buffer ready ; 2 - Inactive, frame buffer ready. ; 3 - Transmitting address field ; 4 - Transmitting data field ; ; Action taken per state: ; 0 - Ignore call. ; 1 - Get frame buffer from transmission list. If ; none available, return 1, otherwise execute ; state 2 procedure. ; 2 - Initialize CH.TXP (transmit data pointer) to ; start of data. Set state = 3, Execute state ; 3 procedure. ; 3 - Get next address field byte from (CH.TXP), ; shift left one bit, increment CH.TXP, ; decrement FB.ACT, the address count. If ; FB.ACT is zero, state = 4, data byte LSB = 1. ; Return 0FFH and data byte. ; 4 - If FB.CNT is not zero, get next address field ; byte from (CH.TXP), increment CH.TXP, decrement ; FB.CNT, the data count, return 0FFH and data ; byte. Otherwise, get frame buffer from ; transmission list. If none available, set ; state = 1, return 1. Otherwise set state = 2, ; return 0. ; PAGE ; Entry. Pass to proper state routine. NXTHO: LD A,1 ;Hold interrupts LD (EIHOLD),A LD A,(IX+CH.TXS) ;Get transmit state INC A DEC A ;State 0? JP Z,NXTRET ;Yes, ignore the call DEC A ;State 1? JR NZ,NHO01 ;No ; State 1. PUSH IX ;Get channel data address POP HL LD DE,CH.ROT ;Form address of list root ADD HL,DE CALL FBGET ;Get next frame buffer LD A,1 ;Assume none available JP Z,NXTRET ;Nothing there LD (IX+CH.TXF),L ;Store frame buffer pointer LD (IX+(CH.TXF+1)),H JR NHOS2 ;Execute state 1 procedure ; State 2. NHO01: DEC A ;State 2? JR NZ,NHO02 ;No NHOS2: LD L,(IX+CH.TXF) ;Get frame buffer address LD H,(IX+(CH.TXF+1)) LD DE,FB.DAT ;Offset to data ADD HL,DE LD (IX+CH.TXP),L ;Store data pointer LD (IX+(CH.TXP+1)),H LD (IX+CH.TXS),3 ;Set state = 3 JR NHOS3 ;Execute state 2 procedure PAGE ; State 3. NHO02: DEC A ;State 3? JR NZ,NHO03 ;No NHOS3: LD L,(IX+CH.TXP) ;Get data pointer LD H,(IX+(CH.TXP+1)) LD B,(HL) ;Get next byte of address OR A ;Clear carry RL B INC HL ;Update data pointer LD (IX+CH.TXP),L LD (IX+(CH.TXP+1)),H LD L,(IX+CH.TXF) ;Get frame buffer address LD H,(IX+(CH.TXF+1)) LD DE,FB.ACT ;Offset to address count ADD HL,DE DEC (HL) ;Decrement address count LD A,0FFH JR NZ,NXTRET ;Not zero, return LD (IX+CH.TXS),4 ;State = 4 LD A,1 ;Set LSB of byte OR B LD B,A LD A,0FFH ;Return last address byte JP NXTRET PAGE ; State 4. NHO03: LD L,(IX+CH.TXF) ;Get frame buffer address LD H,(IX+(CH.TXF+1)) REPT FB.CNT ;Point to data count INC HL ENDM LD E,(HL) ;Get data count INC HL LD D,(HL) LD A,D ;Test for zero count OR E JR Z,NHO04 ;No more data to send DEC DE ;Decrement data count LD (HL),D ;Restore data count DEC HL LD (HL),E LD L,(IX+CH.TXP) ;Get data pointer LD H,(IX+(CH.TXP+1)) LD B,(HL) ;Get data byte INC HL ;Increment data pointer LD (IX+CH.TXP),L ;Restore data pointer LD (IX+(CH.TXP+1)),H LD A,0FFH ;Return data byte JR NXTRET NHO04: LD L,(IX+CH.TXF) ;Get frame buffer address LD H,(IX+(CH.TXF+1)) CALL FBDALC ;Deallocate frame buffer PUSH IX ;Get channel data address POP HL LD DE,CH.ROT ;Form address of list root ADD HL,DE CALL FBGET ;Get new frame buffer JR NZ,NHO05 ;Frame buffer found LD (IX+CH.TXS),1 ;State = 1 LD A,1 ;End of transmission JR NXTRET NHO05: LD (IX+CH.TXF),L ;Store new buffer address LD (IX+(CH.TXF+1)),H LD (IX+CH.TXS),2 ;State = 2 LD A,0 ;End of frame NXTRET: LD HL,EIHOLD ;Allow interrupt enables LD (HL),0 RET SUBTTL 'ODONE - Transmit Termination Service Routine' PAGE ; ODONE is called by the SIO handler when transmission is complete. ; CH.TXS is set to 0 to show transmission complete. ODONE: LD (IX+CH.TXS),0 ;Transmitter idle RET SUBTTL 'NXTHI - Frame Reception Service Routine' PAGE ; NXTHI - Routine processes each received character. ; Entry parameters: ; A = 0, 1 or 0FFH (See HDLSIO module) ; B = Received character (See HDLSIO module) ; IX = Address of channel data structure ; Return parameters: ; None ; ; The state of the receiving "machine" represented by this ; subroutine is contained in the channel data structure ; element CH.RXS. The states are: ; 0 - Inactive, no frame buffer allocated. ; 1 - Inactive, frame buffer allocated. ; 2 - Active, receiving address field data. ; 3 - Active, reciving non-address field data. NXTHI: OR A ;What type of entry is it? LD A,1 ;Hold interrupts LD (EIHOLD),A LD A,(IX+CH.RXS) ;Get rx state JP M,RXCHAR ;"Next received character" JP NZ,ENDRX ;"End of received frame" PAGE ; Here when entry is "start of new frame". ; Action taken per state: ; 0 - Allocate frame buffer. If no buffer ; available, return with state unchanged. ; Otherwise, set channel # (CH.CHA) in ; FB.CHA and same as state 1. ; 1 - Set frame buffer address count and data ; count (FB.CNT and FB.ACT) to zero. ; Set CH.RXP to start of frame buffer ; data (FB.DAT). Set state = 2. ; Go to address byte storage (ADRSTR). ; 2 - Same as state 1. ; 3 - Same as state 1. OR A ;State 0? JR NZ,NHI01 ;No CALL FBALOC ;Get a frame buffer JR Z,NXTRET ;None available, die LD (IX+CH.RXF),L ;Save buffer address LD (IX+(CH.RXF+1)),H LD A,(IX+CH.CHA) ;Init FB.CHA REPT FB.CHA INC HL ENDM LD (HL),A NHI01: LD L,(IX+CH.RXF) ;Get frame buffer address LD H,(IX+(CH.RXF+1)) REPT FB.CNT INC HL ENDM REPT 3 ;Set counts to zero LD (HL),0 INC HL ENDM LD (IX+CH.RXP),L ;Init data pointer LD (IX+(CH.RXP+1)),H LD (IX+CH.RXS),2 ;Set state to 2 JP ADRSTR ;Store the address byte PAGE ; Here when entry is "next received character". ; Action taken per state: ; 0 - Ignore call (return). ; 1 - Ignore call (return). ; 2 - Go to address byte storage (ADRSTR) ; 3 - If frame buffer full, state = 1. ; Otherwise, store data byte at (CH.RXP), ; increment data count (FB.CNT). RXCHAR: INC A DEC A ;State 0? JR Z,NXTRET ;Yes, ignore the call DEC A ;State 1? JR Z,NXTRET ;Yes, ignore the call DEC A ;State 2 JP Z,ADRSTR ;Yes, store address byte LD L,(IX+CH.RXF) ;Get buffer address LD H,(IX+(CH.RXF+1)) REPT FB.CNT ;Point to count INC HL ENDM LD E,(HL) ;Get data count INC HL LD D,(HL) PUSH HL ;Save pointer LD HL,-MAXD ADD HL,DE ;Is frame full? POP HL ;Restore pointer JR NC,NHI02 ;Frame is not full LD (IX+CH.RXS),1 ;State = 1 JR NXTRET ;Die NHI02: INC DE ;Count + 1 LD (HL),D ;Restore count DEC HL LD (HL),E LD L,(IX+CH.RXP) ;Get the data pointer LD H,(IX+(CH.RXP+1)) LD (HL),B ;Store the byte INC HL ;Update data pointer LD (IX+CH.RXP),L LD (IX+(CH.RXP+1)),H JP NXTRET PAGE ; Here to store an address byte. Shift the byte right ; one bit and store in frame buffer, then increment the ; frame buffer address count (FB.ACT). If the (unshifted) ; byte has its LSB set, set state to 3. (End of address). ADRSTR: LD L,(IX+CH.RXP) ;Get the data pointer LD H,(IX+(CH.RXP+1)) OR A ;Clear the carry RR B ;Shift the byte PUSH AF ;Save the address extension bit LD (HL),B ;Store the byte INC HL ;Increment the data pointer LD (IX+CH.RXP),L ;Restore the data pointer LD (IX+(CH.RXP+1)),H LD L,(IX+CH.RXF) ;Get the buffer address LD H,(IX+(CH.RXF+1)) LD DE,FB.ACT ;Point to address count ADD HL,DE LD A,(HL) ;Get address count INC (HL) ;Address count + 1 CP MAXADR ;Is address too long? JR NZ,ADRRET ;No, keep going POP AF ;Clean the stack LD (IX+CH.RXS),1 ;Kill this frame, state = 1 JP NXTRET ADRRET: POP AF ;Get the address extension bit JP NC,NXTRET ;Still address LD (IX+CH.RXS),3 ;Set state to 3 JP NXTRET PAGE ; Here when entry is "end of received frame" ; Action per state: ; 0 - Ignore call (return). ; 1 - Ignore call (return). ; 2 - Set state = 1; ; 3 - Link the frame buffer to the received frame ; list (root = RXLIST). Set state = 0; ENDRX: INC A DEC A ;State 0? JP Z,NXTRET ;Yes, ignore call DEC A ;State 1? JP Z,NXTRET ;Yes, ignore call DEC A ;State 2? JR NZ,NHI03 ;No, state 3 LD (IX+CH.RXS),1 ;Set state = 1 NHI03: LD E,(IX+CH.RXF) ;Get buffer address LD D,(IX+(CH.RXF+1)) LD HL,RXLIST ;Get rx frame list root CALL FBPUT ;Link frame to rx list LD (IX+CH.RXS),0 ;State = 0; JP NXTRET SUBTTL 'List Manipulation Subroutines' PAGE ; List manipulation subroutines ; FBALOC - Allocate a frame buffer from the free list. ; Entry parameters: ; None ; Return parameters: ; HL = Address of frame buffer or zero ; if no buffer available. ; Z flag set if HL is zero. ; Register A is trashed. FBALOC: DI ;Stop ints for the duration LD HL,(FRELST) ;Get the free list root LD A,H OR L ;Is the root null? JR Z,FBEXIT ;Yes, die LD E,(HL) ;Get the buffer's link INC HL LD D,(HL) DEC HL LD (FRELST),DE ;Store new root FBEXIT: LD A,H ;Set/reset Z flag OR L CALL EINT ;Enable int again RET ; FBDALC - Return a frame buffer to the free list. ; Entry parameters: ; HL = address of frame buffer ; Return parameters: ; None ; HL is trashed, all other regs preserved. FBDALC: DI ;Disable ints for now PUSH DE LD DE,(FRELST) ;Get free list root LD (HL),E ;Store link in buffer INC HL LD (HL),D DEC HL LD (FRELST),HL ;Store new free root CALL EINT ;Allow ints again POP DE RET PAGE ; FBGET - Gets a frame buffer from a list. ; Entry parameters: ; HL = Address of list root. ; Return parameters: ; HL = address of frame buffer or zero ; if list is empty. ; Z flag is set if HL is zero. ; Register AF trashed, all other registers preserved. FBGET: DI ;Disable ints for now PUSH DE ;Save caller's reg LD E,(HL) ;Get list root INC HL LD D,(HL) DEC HL EX DE,HL LD A,H ;Is root NULL? OR L JR Z,FGEXIT ;Yes, we are dead PUSH DE ;Save root address LD E,(HL) ;Get link from buffer INC HL LD D,(HL) DEC HL EX (SP),HL ;Root addr to HL, pointer to stack LD (HL), E ;Store link as new root INC HL LD (HL),D POP HL ;Restore buffer pointer FGEXIT: POP DE JR FBEXIT PAGE ; FBPUT - Put frame buffer at end of list. ; Entry parameters: ; HL = Address of list root ; DE = Address of frame buffer ; Return parameters: ; None ; Register AF trashed, all other regs preserved. FBPUT: DI ;Disable ints for now PUSH DE ;Save user's regs PUSH HL ; Set passed buffer link to NULL EX DE,HL ;Buffer addr to HL, root addr to DE LD (HL),0 ;Set link to NULL INC HL LD (HL),0 EX DE,HL ;Root addr to HL ; If root is NULL, set it to passed buffer addr LD E,(HL) ;Get list root to DE INC HL LD D,(HL) EX DE,HL ;Root to HL LD A,H ;Is root NULL? OR L JR NZ,FBPUT1 ;No, search for list end POP HL ;Root addr to HL POP DE ;Buffer addr to DE LD (HL),E ;Buffer pointer to root INC HL LD (HL),D DEC HL CALL EINT ;Enable interupts RET ; Follow the list links until a NULL link is found. ; That will be the end of the list. ; Enter here with list root in HL. FBPUT1: LD E,(HL) ;Get link INC HL LD D,(HL) EX DE,HL ;Current link to DE, next link to HL LD A,H ;Is next link NULL? OR L JR NZ,FBPUT1 ;No, keep searching PAGE ; End of list found. Update last link in list to point ; to passed buffer. DEC DE ;Adjust pointer POP HL ;Restore root address EX (SP),HL ;Root addr to stack, buffer addr to HL EX DE,HL ;Buffer addr to DE, link addr to HL LD (HL),E ;Update last link INC HL LD (HL),D POP HL ;Restore root address CALL EINT ;Enable ints again RET SUBTTL 'Subroutines' PAGE ; Channel data structure access subroutines ; ; GETCDS - Gets address of the specified channel data ; structure. ; Entry parameters: ; A = Channel number ; Return parameters: ; IX = Address of channel data structure ; All other registers preserved GETCDS: PUSH AF ;Save caller's regs PUSH DE PUSH HL LD DE,CDSIZE ;Size of data structure LD HL,CH0-CDSIZE ;Base of channel d.s. INC A GCSLOP: ADD HL,DE ;Next data structure DEC A JR NZ,GCSLOP EX (SP),HL ;Address to (SP) POP IX ;Address to IX POP DE POP AF RET ; EINT - Enable interrupts if not being held off. ; All registers preserved. EINT: DI ;Disabled for the moment PUSH AF ;Save user's regs LD A,(EIHOLD) ;Get hold flag OR A ;Allowed to enable? JR NZ,EIRET ;No POP AF EI ;Enable, INTCNT is 0 RET EIRET: POP AF RET DSEG EIHOLD: DEFS 1 ;EI hold flag CSEG ; VECTOR - Call subroutine address in HL VECTOR: JP (HL) ;Call it RET PAGE ; ADRCMP - Compare AX.25 address strings. ; Bits 4-8 of SSID byte are not compared. ; Entry parameters: ; DE = Pointer to string 1. ; HL = Pointer to string 2. ; Return parameters: ; Z flag set if strings match. ; Register AF trashed, all other registers preserved ADRCMP: PUSH BC ;Save regs PUSH DE PUSH HL LD B,ADRLTH-1 ACOMP: LD A,(DE) ;Get address string 1 byte CP (HL) ;Match with address string 2? JR NZ,ACRET ;No match INC DE ;Next byte INC HL DJNZ ACOMP ;Repeat it LD A,(HL) ;Get string 2 SSID byte AND 0FH ;Mask off other stuff LD B,A LD A,(DE) ;Get string 1 SSID byte AND 0FH CP B ;Matching SSID too? ACRET: POP HL ;Restore regs POP DE POP BC RET PAGE ; SEARCH - Search call table for match with address. ; Entry parameters: ; BC = address of # calls, channel 0 ; DE = pointer to call to search for ; HL = start of call table. ; Return parameters: ; If no match found: ; C flag reset. ; HL = end of call table ; If match found: ; C flag set ; HL = pointer to address in table ; A = channel number of matching address ; Registers AF, BC, HL trashed, all others preserved. SEARCH: LD A,0 ;Channel number = 0 LD (SCHCHN),A ; Channel loop SCHLOP: LD A,(BC) ;Get # calls, this channel OR A ;Any calls? JR Z,SNXTCH ;No, skip search PUSH BC ;Save # pointer LD B,A ;Number of calls to check ; Call (table entry) loop CALLOP: CALL ADRCMP ;Address match? JR Z,SMATCH ;Yes, return it PUSH DE ;Save compare pointer LD DE,ADRLTH ;Bump call table pointer ADD HL,DE POP DE DJNZ CALLOP ;Check next call POP BC ;Restore # pointer SNXTCH: INC BC ;Next channel LD A,(SCHCHN) ;Incrememt channel # INC A LD (SCHCHN),A CP NUMCH ;All channels checked? JR NZ,SCHLOP ;No, check another OR A ;Clear carry, no match RET SMATCH: POP BC ;Clean stack OR A ;Clear carry CCF ;Set carry LD A,(SCHCHN) ;Get match channel RET DSEG SCHCHN: DEFS 1 ;Channel # being searched CSEG SUBTTL 'SIO Service Subroutine Entry Points' PAGE ; Subroutines called by the SIO handlers. X DEFL 0 REPT NUMCH SUBS %X X DEFL X+1 ENDM SUBTTL 'Channel Definitions and RAM Allocation' PAGE ; Define channel data structures CHDEFS: X DEFL 0 REPT NUMCH DEFCH %X X DEFL X+1 ENDM DSEG FRELST: DEFS 2 ;Free buffer list root RXLIST: DEFS 2 ;Received frame list root DEFS 100 ;50 level stack STACK: SUBTTL 'Symbol Table' END