; M4XFER/ASM ; ; FILE ROUTINES ; ; Output the characters in a packet ; PTCHR LD HL,PUTFILE CALL DECODE JP Z,RSKP RET ; ; Get a packets worth of data ; GTCHR LD A,(EOFLAG) ;Check for EOF OR A ;Set or reset Z RET NZ ;Return if EOF occured CALL GETPKT ;Get a packets worth JP RSKP ;Return saying that something is there ; ; Put a character to a file ; PUTFILE LD DE,(RFIDCB) ;Get the DCB address CALL XPUT ;Output the character RET Z ;Return if no error CALL XERROR0 ;Print an error message LD A,'X' ;Set EOT flag LD (CZSEEN),A RET ;Return to caller ; ; Put a character to the buffer ; PUTDATA PUSH HL ;Save the pointer LD HL,(RMTPTR) ;Get the pointer to the start LD (HL),A ;Store the character INC HL ;Point to next LD (HL),0 ;Terminate the string LD (RMTPTR),HL ;Save the new pointer POP HL ;Restore the pointer CP A ;Set Z status RET ;Return ; ; Get a character from the packet, doing all necessary decoding ; GETDATA PUSH HL ;Save HL LD (RMTPTR),HL ;Store as the place to but the data LD HL,PUTDATA ;Get the address of the routine CALL DECODE ;Decode it POP HL ;Restore HL RET ;Return to caller ; ; Call this address to call the address in HL ; CALLHL JP (HL) RET ; ; Get the next file name pointed to by MFNPTR and put it in FCB. ; If no more names are available, then the Carry Flag will be ; set apon return. Otherwise, NC will exist, and FCB will ; contain a valid TRSDOS filename. ; MFNAME PUSH BC ;Save the registers PUSH DE PUSH HL LD B,32 ;Blank the FCB LD HL,MFREQ PUSH HL LD A,32 MFN0A LD (HL),A INC HL DJNZ MFN0A LD HL,(MFNPTR) ;Get the start of the next name POP DE ;Get the destination CALL XFSPEC ;Move and convert LD (MFNPTR),HL ;Save start of next name PUSH AF ;Save the returned flags LD HL,MFREQ ;Get the source PUSH HL ;Make a copy LD DE,TFILNAM ;Get the destination LD BC,32 ;Get the byte count LDIR ;Move them LD HL,TFILNAM ;Terminate the string with EOS LD A,3 ;Find the ETX LD BC,32 ;Only look this far CPIR ;Find it DEC HL ;Back up to the ETX LD (HL),EOS ;Put in an ETX POP HL ;Restore the source address LD DE,FCB ;Get the FCB destination CALL XFSPEC ;Move a copy into FCB POP AF ;Restore the return flags SCF ;Set initial return flag JR NZ,MFFIX1 ;Abort on error CCF ;Reset Carry to return valid name MFFIX1 POP HL ;Restore the registers POP DE POP BC RET ;Return to the caller ; ; Open the filename in FCB for output ; GETFIL LD A,0FFH LD (FILFLG),A ;No file open XOR A ;Get zero LD (EOFLAG),A ;Not the end of file LD (LSTCHR),A ;No previous character PUSH HL LD DE,FCB ;Get the FCB LD HL,BUFF ;Get the data buffer LD B,0 ;Select LRL=256 CALL XOPEN ;Open the file (at least try) POP HL ;Restore old HL JR Z,GETFIL1 ;Return if normal open ; ; The following code handles files with LRL's different then ; 256. The LRL open fault can be ignored in this case. ; CP 42 ;Check for different LRL ERROR JP NZ,ERRORD ;If not, then error GETFIL1 JP RSKP ;Ignore LRL open fault ; ; PACKET ROUTINES ; ; Send a packet out the comm port ; ; This routine assembles a packet from the arguments given and ; sends it out the communications port ; ; Arguments: ; ; A - TYPE OF PACKET (D,Y,N,S,R,E,F,Z,T) ; ARGBLK - PACKET SEQUENCE NUMBER ; ARGBLK+1 - NUMBER OF DATA CHARACTERS ; SPACK LD (ARGBLK+2),A ;Save data for resend to use LD HL,PACKET ;GET ADDRESS OF THE SEND PACKET. LD A,(SSOHCH) ;GET THE START OF HEADER CHAR. PUTHL A ;PUT IN THE PACKET. LD A,(CURCHK) ;GET CURRENT CHECKSUM TYPE SUB '1' ;DETERMINE EXTRA LENGTH OF CHECKSUM LD B,A ;COPY LENGTH LD A,(ARGBLK+1) ;GET THE NUMBER OF DATA CHARS. ADD A,' '+3 ;Real packet length made printable ADD A,B ;DETERMINE OVERALL LENGTH PUTHL A ;Put in the packet LD B,0 ;ZERO THE CHECKSUM AC. LD C,A ;START THE CHECKSUM. LD A,(ARGBLK) ;GET THE PACKET NUMBER. TOCHAR ;ADD A SPACE SO THE NUMBER IS PRINTABLE. PUTHL A ;Put in the packet CALL NXTSUM ;Get next checksum value LD A,(ARGBLK+2) ;GET THE PACKET TYPE. PUTHL A ;Put in the packet CALL NXTSUM SPACK2 LD A,(ARGBLK+1) ;GET THE PACKET SIZE. IFZ SPACK3 DEC A ;DECREMENT THE CHAR COUNT. LD (ARGBLK+1),A ;PUT IT BACK. LD A,(HL) ;GET THE NEXT CHAR. INC HL ;POINT TO NEXT CHAR. CALL NXTSUM ;Compute next checksum JR SPACK2 ;GO TRY AGAIN. SPACK3 LD A,(CURCHK) ;GET THE CURRENT CHECKSUM TYPE IFA '2',SPACK4 JR NC,SPACK5 ;Go do CRC if '3' LD A,C ;GET THE CHARACTER TOTAL. AND 0C0H ;TURN OFF ALL BUT THE TWO HIGH ORDER BITS RLCA ;TWO LEFT ROTATES SAME AS 6 RIGHTS RLCA ;. . . ADD A,C ;ADD IT TO THE OLD BITS. AND 3FH ;TURN OFF THE TWO HIGH ORDER BITS. TOCHAR ;ADD A SPACE SO THE NUMBER IS PRINTABLE. PUTHL A ;Put in the packet JP SPACK7 ;GO STORE EOL CHARACTER ; ;HERE FOR 3 CHARACTER CRC-CCITT ; SPACK5 LD (HL),0 ;STORE A NULL FOR CURRENT END PUSH HL ;SAVE H LD HL,PACKET+1 ;POINT TO FIRST CHECKSUMED CHARACTER CALL CRCCLC ;CALCULATE THE CRC POP HL ;RESTORE THE POINTER LD C,E ;GET LOW ORDER HALF FOR LATER LD B,D ;COPY THE HIGH ORDER LD A,D ;GET THE HIGH ORDER PORTION RLCA ;SHIFT OFF LOW 4 BITS RLCA ;. . . RLCA ;. . . RLCA ;. . . AND 0FH ;KEEP ONLY LOW 4 BITS TOCHAR ;PUT INTO PRINTING RANGE LD (HL),A ;STORE THE CHARACTER INC HL ;POINT TO NEXT POSITION ; ;HERE FOR TWO CHARACTER CHECKSUM ; SPACK4 LD A,B ;GET HIGH ORDER PORTION AND 0FH ;ONLY KEEP LAST FOUR BITS RLCA ;SHIFT UP TWO BITS RLCA ;. . . LD B,A ;COPY BACK INTO SAFE PLACE LD A,C ;GET LOW ORDER HALF RLCA ;SHIFT HIGH TWO BITS RLCA ;TO LOW TWO BITS AND 03H ;KEEP ONLY TWO LOW BITS OR B ;GET HIGH ORDER PORTION IN TOCHAR ;CONVERT TO PRINTING CHARACTER RANGE PUTHL A ;Store the character LD A,C ;GET LOW ORDER PORTION AND 3FH ;KEEP ONLY SIX BITS TOCHAR ;CONVERT TO PRINTING RANGE PUTHL A ;Store the character SPACK7 LD A,(SEOL) ;GET THE EOL THE OTHER HOST WANTS. PUTHL A ;Store the character PUTHL 0 ;End with a NULL LD A,(DBFLG) OR A JR Z,SPACK8 ;debug is off PUTHL EOS ;Add terminator SPACK8 CALL OUTPKT ;CALL THE SYSTEM DEPENDENT ROUTINE. JP QUIT JP RSKP ; ; WRITE OUT A PACKET. ; OUTPKT LD A,(SPAD) ;GET THE NUMBER OF PADDING CHARS. LD B,A OUTPK2 DEC B JP M,OUTPK4 LD A,(SPADCH) ;GET THE PADDING CHAR. LD E,A ;PUT THE CHAR IN RIGHT AC. CALL OUTCHR ;OUTPUT IT. JR OUTPK2 OUTPK4 LD A,(DBFLG) IFZ OUTPK5 ;If not on, then check for logfile STROUT SPPOS ;Print the SPACK=> message STROUT PACKET+1 ;Print the data OUTPK5 LD A,(DEBLOG) ;See if logging in effect IFZ OUTPK7 ;If not, then finish up LD DE,DFCB ;Get the debug FCB TRLOG SPPOS,OUTPK6 ;Log the SPACK=> message TRLOG PACKET,OUTPK6 ;Log the packet data JR OUTPK7 OUTPK6 XOR A LD (DEBLOG),A LD DE,DFCB CALL XCLOSE OUTPK7 LD HL,PACKET ;POINT TO THE PACKET. OUTPK10 LD A,(HL) ;GET THE NEXT CHARACTER. IFZ OUTPK11 ;Return success if EOS found LD E,A ;PUT THE CHAR IN RIGHT AC. CALL OUTCHR ;OUTPUT THE CHARACTER. INC HL ;INCREMENT THE CHAR POINTER. JR OUTPK10 OUTPK11 LD A,(STURN) ;Is turn around needed? IFZ OUTPK12 JUMP IF NOT NEEDED LD E,A ;Get the character CALL OUTCHR ;Output it OUTPK12 JP RSKP ;Return no error ; ; Compute next checksum ; NXTSUM ADD A,C LD C,A LD A,0 ;Must use load to preserve Carry flag ADC A,B LD B,A RET ; ;THIS ROUTINE WAITS FOR A PACKET TO ARRIVE FROM THE HOST. IT READS ;CHARACTERS UNTIL IT FINDS THE SOH. IT THEN READS THE PACKET INTO PACKET. ; ;RETURNS +1 FAILURE (IF THE CHECKSUM IS WRONG OR THE PACKET TRASHED) ; +3 SUCCESS WITH A - MESSAGE TYPE ; ARGBLK - MESSAGE NUMBER ; ARGBLK+1 - LENGTH OF DATA ; RPACK LD A,(RTIME) ;Get the timeout value LD HL,0 IFZ RPACK1 ;If zero, then no timeout LD L,A ;Get the value as 16 bits LD C,30 ;Get the factor to extend it by CALL XMUL16 ;Do the multiplication LD H,L ;Slide the 24 bit result down LD L,A RPACK1 LD (SVTIMER),HL ;Save it as the timer value RPACK2 CALL STARTTIMER ;Start the timer for receive timeout CALL INPKT ;READ UP TO A CARRIAGE RETURN. JP QUIT ;RETURN BAD. CALL STOPTIMER ;Stop the timeout countdown RPACK3 CALL GETCHR ;GET A CHARACTER. JP RPACK2 ;HIT A CR;NULL LINE; JUST START OVER. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JR NZ,RPACK3 ;NO, GO UNTIL IT IS. RPACK4 CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JR Z,RPACK4 ;YES, THEN GO START OVER. LD (PACKET+1),A ;STORE IN PACKET ALSO LD C,A ;START THE CHECKSUM. LD A,(CURCHK) ;GET BLOCK CHECK TYPE SUB '1' ;DETERMINE EXTRA LENGTH OF BLOCK CHECK LD B,A ;GET A COPY LD A,C ;GET BACK LENGTH CHARACTER SUB ' '+3 ;GET THE REAL DATA COUNT. SUB B ;GET TOTAL LENGTH LD (ARGBLK+1),A LD B,0 ;CLEAR HIGH ORDER HALF OF CHECKSUM CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JR Z,RPACK4 ;YES, THEN GO START OVER. LD (ARGBLK),A LD (PACKET+2),A ;SAVE ALSO IN PACKET CALL NXTSUM ;ADD THE CHARACTER TO THE CHECKSUM LD A,(ARGBLK) SUB ' ' ;GET THE REAL PACKET NUMBER. LD (ARGBLK),A CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JR Z,RPACK4 ;YES, THEN GO START OVER. LD (TEMP1),A ;SAVE THE MESSAGE TYPE. LD (PACKET+3),A ;SAVE IN PACKET LD (RECTYP),A CALL NXTSUM ;ADD THE CHARACTER TO THE CHECKSUM. LD A,(ARGBLK+1) ;GET THE NUMBER OF DATA CHARACTERS. LD (TEMP2),A LD HL,DATA ;POINT TO THE DATA BUFFER. LD (DATPTR),HL RPACK5 LD A,(TEMP2) DEC A ;ANY DATA CHARACTERS? JP M,RPACK6 ;IF NOT GO GET THE CHECKSUM. LD (TEMP2),A CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE END-OF-LINE, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JR Z,RPACK4 ;YES, THEN GO START OVER. LD HL,(DATPTR) PUTHL A ;Store the character LD (DATPTR),HL CALL NXTSUM ;ADD THE CHARACTER TO THE CHECKSUM. JR RPACK5 ;GO GET ANOTHER. RPACK6 CALL CHKECHO ;See if only echo of previous JP RPACK3 ;Yes, restart CALL GETCHR ;Get a character JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JP Z,RPACK4 ;YES, THEN GO START OVER. SUB ' ' ;TURN THE CHAR BACK INTO A NUMBER. LD (TEMP3),A ;DETERMINE TYPE OF CHECKSUM LD A,(CURCHK) ;GET THE CURRENT CHECKSUM TYPE IFA '2',RPACK9 ;Jump if 2 character JR NC,RPACK8 ;Jump if 3 character ; ; 1 character checksum ; LD A,C ;Get the character count AND 0C0H ;Keep 2 MSB's RLCA ;Move them to 2 LSB's RLCA ADD A,C ;Add the 2 low bits to bottom AND 3FH ;Remove 2 high bits after add LD B,A LD A,(TEMP3) ;GET THE REAL RECEIVED CHECKSUM. IFA B,RPACK10 ;Jump checksum OK RPACK7 CALL UPDRTR ;If checksum bad, update retries RET ;Return error ; ; Here for three character CRC-CCITT ; RPACK8 LD HL,(DATPTR) ;GET THE ADDRESS OF THE DATA LD (HL),0 ;Store a zero in the buffer as terminator LD HL,PACKET+1 ;POINT AT START OF CHECKSUMMED REGION CALL CRCCLC ;CALCULATE THE CRC LD C,E ;SAVE LOW ORDER HALF FOR LATER LD B,D ;ALSO COPY HIGH ORDER LD A,D ;GET HIGH BYTE RLCA ;WANT HIGH FOUR BITS RLCA ;. . . RLCA ;AND SHIFT TWO MORE RLCA ;. . . AND 0FH ;KEEP ONLY 4 BITS LD D,A ;BACK INTO D LD A,(TEMP3) ;GET FIRST VALUE BACK IFANOT D,RPACK7 ;Jump if not correct CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JP Z,RPACK4 ;YES, THEN GO START OVER. SUB ' ' ;REMOVE SPACE OFFSET LD (TEMP3),A ;STORE FOR LATER CHECK ; ; Here for a two character checksum and last two characters of CRC ; RPACK9 LD A,B ;GET HIGH ORDER PORTION AND 0FH ;ONLY FOUR BITS RLCA ;Shift up 2 bits RLCA LD B,A ;Save back into B LD A,C ;Get low order byte RLCA ;Move the 2 MSB's to 2 LSB's RLCA AND 03H ;Save only low 2 bits OR B ;Get other 4 bits LD B,A ;Save back into B LD A,(TEMP3) ;Get this portion of the checksum IFANOT B,RPACK7 ;If wrong, then give up CALL GETCHR ;GET A CHARACTER. JP QUIT ;HIT THE CARRIAGE RETURN, RETURN BAD. CALL CPRSOH ;IS THE CHAR THE START OF HEADER CHAR? JP Z,RPACK4 ;YES, THEN GO START OVER. SUB ' ' ;REMOVE SPACE OFFSET LD B,A ;SAVE IN SAFE PLACE LD A,C ;GET LOW 8 BITS OF CHECKSUM AND 3FH ;KEEP ONLY 6 BITS IFANOT B,RPACK7 ;Jump if bad value RPACK10 LD HL,(DATPTR) PUTHL 0 ;End with a NULL LD A,(TEMP1) ;GET THE TYPE. JP RSKP ; ; Input a packet ; INPKT LD HL,RECPKT ;POINT TO THE BEGINNING OF THE PACKET. LD (PKTPTR),HL INPKT2 CALL INCHR ;GET A CHARACTER. JP INPKT7 ;Skip out if key typed that is valid LD HL,(PKTPTR) ;Get the packet position PUTHL A ;Store the character LD (PKTPTR),HL ;Save the pointer CALL CPREOL ;IS IT THE EOL CHARACTER? JR NZ,INPKT2 PUTHL EOS ;Put in the terminator LD A,(DBFLG) IFZ INPKT3 ;Jump if debug off STROUT RPPOS ;Output RPACK=> message STROUT RECPKT+1 ;Print the received packet INPKT3 LD A,(DEBLOG) ;See if debug log in on IFZ INPKT6 ;Jump if not enabled LD DE,DFCB ;Get the FCB TRLOG RPPOS,OUTPK6 ;Log the RPACK=> message TRLOG RECPKT+1,OUTPK6 ;Log the packet INPKT6 LD HL,RECPKT LD (PKTPTR),HL ;SAVE THE PACKET POINTER. LD A,(RTURN) ;Get the turn around character CALL WAITT ;Go wait for it. JP RSKP ;Return no error ; ; Error return processing. This code deals with the keystrokes ; that are recognized in INCHR(). ; INPKT7 LD A,(CZSEEN) IFANOT 'A',INPKT8 ;Status CALL SHOTRANS ;Show the transfer status JR INPKT16 INPKT8 IFANOT 'B',INPKT9 ;Cancel Batch? LD A,'Z' ;Get the packet type LD (CZSEEN),A LD DE,CBATCH ;Get the cancel message CALL CONDIS ;Print it if not doing REMOTE commands JP INPKT2 INPKT9 IFANOT 'F',INPKT10 ;Cancel FILE? LD A,'X' ;Get the PACKET type LD (CZSEEN),A LD DE,CFILE ;Get the cancel message CALL CONDIS ;Print it if not doing REMOTE commands JP INPKT2 INPKT10 IFANOT 'E',INPKT12 ;Send error, and ABORT? XOR A LD (CZSEEN),A ;Reset the key pressed flag CALL STOPTIMER ;Stop the timer LD A,ABRTMSGLEN ;Get length of message LD (ARGBLK+1),A ;Save the length LD HL,ABRTMSG ;Get the message LD DE,DATA ;Where to put it LD C,A ;Get the length in BC LD B,0 LDIR ;Move the message LD A,'E' ;Get the packet type CALL SPACK ;Send the error packet JP ABORT ;Give up on an error JP KERMIT ;Give up completely INPKT12 IFANOT 'C',INPKT14 ;Cancel transfer, immediately XOR A LD (CZSEEN),A ;Zap the old key pressed CALL STOPTIMER ;Stop the timer JP KERMIT ;Jump to restart INPKT14 IFANOT 'D',INPKT18 ;Toggle debug mode? LD A,(DBFLG) ;Get the debug flag XOR 1 ;Toggle value LD (DBFLG),A ;Store it back INPKT16 XOR A ;Finish up handling, reset key pressed LD (CZSEEN),A ;Reset the flag JP INPKT2 ;Get the next character INPKT18 IFANOT 'H',INPKT20 ;Help? STROUT HELPMSG ;Print the message JR INPKT16 ;Finish up INPKT20 XOR A ;Otherwise, return no input to force LD (CZSEEN),A ;resend to occur... RET ;Return no input packet ; GETCHR LD HL,(PKTPTR) ;GET THE PACKET POINTER. LD A,(HL) ;GET THE CHAR. INC HL LD (PKTPTR),HL CALL CPREOL ;IS IT THE END OF LINE JP NZ,RSKP ;IF NOT RETURN RETSKP. RET ;IF SO RETURN FAILURE. ; ; Assorted comparison routines ; CPSSOH PUSH HL LD HL,SSOHCH CPSH10 CP (HL) POP HL RET CPRSOH PUSH HL LD HL,RSOHCH JR CPSH10 CPSEOL PUSH HL LD HL,SEOL JR CPSH10 CPREOL PUSH HL LD HL,REOL JR CPSH10 CPSPAD PUSH HL LD HL,SPADCH JR CPSH10 CPRPAD PUSH HL LD HL,RPADCH JR CPSH10 CPSTME PUSH HL LD HL,STIME JR CPSH10 CPRTME PUSH HL LD HL,RTIME JR CPSH10 CPSQTE PUSH HL LD HL,SQUOTE JR CPSH10 CPRQTE PUSH HL LD HL,RQUOTE JR CPSH10 ; ;THIS ROUTINE WILL CALCULATE A CRC USING THE CCITT POLYNOMIAL FOR ;A STRING. ; ;USAGE ; HL/ ADDRESS OF STRING ; A/ LENGTH OF STRING ; CALL CRCCLC ; ;16-BIT CRC VALUE IS RETURNED IN DE. ; ;REGISTERS BC AND HL ARE PRESERVED. ; CRCCLC PUSH HL ;SAVE HL PUSH BC ;AND BC LD DE,0 ;INITIAL CRC VALUE IS 0 CRCCL0 LD A,(HL) ;GET A CHARACTER OR A ;CHECK IF ZERO JP Z,CRCCL1 ;IF SO, ALL DONE PUSH HL ;SAVE THE POINTER XOR E ;ADD IN WITH PREVIOUS VALUE AND 0FH ;Keep only 4 bits LD B,0 GETCRCTAB CALL SRLDE4 ;Shift CRC right by 4 XORATHL E INC HL XORATHL D POP HL PUSH HL LD A,(HL) SRL A SRL A SRL A SRL A XOR E AND 0FH GETCRCTAB CALL SRLDE4 XORATHL E INC HL XORATHL D POP HL ;AND H INC HL ;POINT TO NEXT CHARACTER JP CRCCL0 ;GO GET NEXT CHARACTER CRCCL1 POP BC ;RESTORE B POP HL ;AND HL RET ;AND RETURN, DE=CRC-CCITT ; ; Shift DE right by 4 bits ; SRLDE4 SRL D RR E SRL D RR E SRL D RR E SRL D RR E RET ; CRCTAB DW 00000H DW 01081H DW 02102H DW 03183H DW 04204H DW 05285H DW 06306H DW 07387H DW 08408H DW 09489H DW 0A50AH DW 0B58BH DW 0C60CH DW 0D68DH DW 0E70EH DW 0F78FH ; GETNPNT LD A,(HL) INC HL LD (OUTPNT),HL RET ; ; Check if RFIDCB points at FCB. ; CHKFCB LD DE,(RFIDCB) ;Get the current FCB/DCB pointer LD HL,FCB ;Get the Address of FCB OR A ;Reset the carry SBC HL,DE ;Compute the difference RET ;Return the flags ; INCKTRANS PUSH HL ;Save the regs PUSH AF LD HL,(KTRANS) ;Get the current count INC HL ;Add one to it LD A,H ;Check for overflow OR L ;Set the flags LD A,1 ;Set the ok to change curtrans flag CALL Z,ADD64K ;Add 64K if overflow LD (KTRANS),HL ;Save the new counter LD (CURTRANS),HL ;Store as current count too POP AF ;Restore the regs POP HL RET ;Return to caller ; ; Add 64k to the current counter (RTRANS, or STRANS, as well as ; CURTRANS which is used for TRANSACTION logs). ; ADD64K EQU $ PUSH HL ;Save the regs LD L,(IX) ;Get the current Kbyte counter LD H,(IX+1) LD BC,64 ;Add 64 to it ADD HL,BC LD (IX),L ;Store it back LD (IX+1),H IFZ ADD64K_1 LD HL,(CURTRANS+2) ;Get the current value ADD HL,BC ;Add 64 LD (CURTRANS+2),HL ;Store new value ADD64K_1 POP HL ;Restore HL RET ;Return ; ; Wait for the turn around character in A ; TTURN DB 0 ; WAITT OR A ;Check for no turn around RET Z ;return on ZERO LD (TTURN),A ;Save the character WAITT1 CALL INCHR ;Get a character JP INPKT7 ;Process keyboard character LD C,A ;Save the character LD A,(TTURN) ;Check for turn around CP C ;Is the character received it? JR NZ,WAITT1 ;No, get another RET ; SHOTRANS EQU $ STROUT NPKTSTR ;Print number of packets LD HL,(NUMPKT) CALL NOUT STROUT NRTRSTR ;Print retries LD HL,(NUMRTR) CALL NOUT STROUT NCHRSTR ;Print number of characters LD HL,(KTRANS) CALL NOUT STROUT NRECCH ;Number K of characters recvd LD HL,(RTRANS) CALL NOUT LD A,'K' CALL CONOUT STROUT NSNDCH ;Print number of characters sent LD HL,(STRANS) CALL NOUT LD A,'K' CALL CONOUT JP NEWLIN ; CHKECHO PUSH BC LD A,(SNDTYP) LD C,A LD A,(RECTYP) CP C POP BC RET Z JP RSKP ; ; Convert KERMIT filename to TRSDOS filename ; GOFIL LD HL,RMTDATA ;Where to put the name LD A,(ARGBLK+1) ;Number of characters CALL GETDATA ;Get the name in RMTDATA (HL saved) LD DE,MFREQ ;Destination LD BC,8 ;Max characters for first field GOFIL1 EQU $ LD A,(HL) ;At end of field? IFA '.',GOFIL8 ;Jump if at separator IFALT ' ',GOFIL15 ;Stop if at end of string LD A,C ;Check range IFANOT 8,GOFIL2 ;If not first character, then skip LD A,(HL) ;Get the character CALL ISALPHA ;Is it alphabetic? JR Z,GOFIL5 ;Jump if it is LD (HL),'Z' ;Change name JR GOFIL5 ;Join code GOFIL2 EQU $ ;Second or later character... LD A,(HL) CALL ISALNUM ;Is it alphanumeric? JR Z,GOFIL5 ;Jump if so INC HL ;Skip this one JR GOFIL1 ;Go to the next character GOFIL5 EQU $ LDI ;Move the character LD A,B ;Check the remaining count OR C JR NZ,GOFIL1 ;Jump if still OK GOFIL7 EQU $ LD A,(HL) ;Are we at the end yet IFA '.',GOFIL8 ;Jump if at the separator IFALT ' ',GOFIL15 ;Stop it at the end INC HL ;Point to next source character JR GOFIL7 ;Loop GOFIL8 EQU $ LD A,C ;Check the count of characters moved IFANOT 8,GOFIL9 ;Jump if at least one moved LD A,'X' ;Use this as the first character LD (DE),A ;Put it in INC DE ;Point to next slot GOFIL9 LD (HL),'/' ;Put in separator LDI ;Move it too LD BC,3 ;Length of next field GOFIL10 EQU $ LD A,(HL) ;Get the character IFALT ' ',GOFIL15 ;Jump if at the end LD A,C ;Check ranges IFANOT 3,GOFIL12 ;Jump if not first character LD A,(HL) ;Get the character (Must be alphabetic) CALL ISALPHA ;Is it alphbetic? JR Z,GOFIL13 ;Jump if it is LD (HL),'Z' ;Make it alphabetic JR GOFIL13 ;Join other code GOFIL12 EQU $ ;Second or third character in extension LD A,(HL) ;Get the character back CALL ISALNUM ;Is it alphanumeric? JR Z,GOFIL13 ;Jump if so INC HL ;Skip it JR GOFIL10 ;Check the next one GOFIL13 EQU $ LDI ;Move a char LD A,B ;Check the count OR C JR NZ,GOFIL10 ;Loop if OK GOFIL15 EQU $ PUSH DE ;Put dest into HL POP HL PUTHL ':' ;Add the default drive LD A,(DEFDSK) PUTHL A ;Add the drive number LD (HL),EOS ;Add the end of string byte PUSH HL ;Save that address LD HL,MFREQ ;Move the string to the save area LD DE,TFILNAM ;Get the destination LD BC,32 LDIR ;Move the bytes POP HL LD (HL),3 ;Put in FSPEC terminator LD (FCBPTR),HL ;Save the end LD HL,MFREQ ;Validate the filespec LD DE,FCB CALL XFSPEC ;Call TRSDOS JR Z,GOFIL18 ;Jump if OK LD HL,(FCBPTR) ;Get end of string LD (HL),EOS ;Put in print terminator STROUT FCB ;Print the name JP XERROR0 ;Print system error message and return GOFIL18 LD HL,FCB ;Get start LD BC,40 ;Maximum to look LD A,':' ;Find drive spec to index off of CPIR ;Look for it. MUST be there INC HL ;Point after for terminator LD (FCBPTR),HL ;Save it DEC HL ;Back up to just after extension DEC HL LD (DATPTR),HL ;Save it for renaming LD A,(FLWFLG) ;Is file warning on? IFZ GOFIL30 ;Jump if not LD DE,FCB ;Get the file name LD HL,BUFF ;Buffer address LD B,0 ;LRL=256 CALL XOPEN ;Is it there? JR NZ,GOFIL30 ;Jump if not LD DE,INFMS5 ;Print renaming message CALL ERROR3 LD DE,FCB ;Close the file CALL XCLOSE ;Close restores the filename with @FNAME GOFIL20 LD HL,(DATPTR) ;Get the pointer to extension LD DE,FCB ;Get the start OR A ;Reset the carry PUSH HL ;Save it SBC HL,DE ;At the beginning yet POP HL ;Restore it JR NZ,GOFIL21 ;Jump if not LD DE,ERMS16 ;Oops, Can't rename it, stop JP PRTSTR ;Print, and return ; GOFIL21 DEC HL ;Point to previous character LD (DATPTR),HL ;Save the new pointer GOFIL24 LD HL,(DATPTR) ;Get the pointer LD A,(HL) ;Get the character IFALT 'B',GOFIL20 ;Jump if we can't change it DEC (HL) ;Change the file name LD HL,FCB ;Get the source address PUSH HL ;Save it for later LD DE,TFILNAM ;Get the destination LD BC,32 ;Number to move LDIR ;Move them POP DE ;Restore stack and get FCB address LD HL,BUFF LD B,0 CALL XOPEN ;Is it there? JR NZ,GOFIL27 ;Jump if not LD DE,FCB ;Close it up CALL XCLOSE JR GOFIL24 ;Try another name ; GOFIL27 LD HL,(FCBPTR) ;Get the end of the file name LD (HL),EOS ;Add the print terminator STROUT FCB ;Print the new name LD (HL),3 ;Put the @OPEN terminator back GOFIL30 LD DE,FCB ;Get the FCB LD HL,BUFF ;Get the buffer LD B,0 ;LRL=256 CALL XINIT ;Create it or zap old file JP Z,RSKP ;Return on success +4 PUSH AF ;Save error code LD DE,ERMS11 ;Print the error message CALL ERROR3 POP AF ;Get the error code back JP ERRORD ;Print a system error ; ; Restart timer for receive packet timeout ; STARTTIMER PUSH HL ;Save the clobbered regs PUSH DE PUSH BC LD C,0 ;Get no timer flag for next test LD HL,(SVTIMER) ;Get the timer value LD A,H ;Check if not timeout wanted OR L JR Z,STARTT3 ;Don't start timer if none needed LD (TIMER),HL ;Set the real counter LD C,8 ;Get the task slot number STARTT1 CALL XCKTSK ;Check is slot in use JR NZ,STARTT2 LD DE,RECTIME ;Get the TCB PUSH BC CALL XADTSK ;Try to add the task POP BC ;Restore the task slot JR STARTT3 ;Go save slot used STARTT2 INC C ;Get next possible slot IFANOT 11,STARTT1 ;Loop if not at max task slot STROUT NOTIMER ;Print error message LD HL,1 LD (SVTIMER),HL ;Zap timer LD C,0 ;Make sure no timer flag is on STARTT3 LD A,C ;Save task to stop LD (TASKSLOT),A POP BC ;Restore registers POP DE POP HL RET ; ; Stop the timeout task ; STOPTIMER PUSH HL ;Save the registers PUSH DE PUSH BC LD C,8 ;Get the task slot number TASKSLOT EQU $-1 CALL XRMTSK LD HL,0 ;Zero out the timer LD (TIMER),HL POP BC ;Restore the registers POP DE POP HL RET ; ; Check if character in A is alphabetic. Z status means YES, ; NZ status means NO ; ISALPHA CP 'A' ;Check upper case RET C ;Return if less than CP 'Z'+1 ;If less than or equal to Z, then A-Z JR C,ISAL_1 ;Jump to TRUE return CP 'a' ;Check lower case RET C ;Return less than CP 'z'+1 ;Check for a-z RET NC ;NC means greater than 'z' ISAL_1 CP A ;Set Z status RET ;Return ; ; Check if character in A is alphanumeric ; ISALNUM CP '0' ;Check digits RET C ;Return too small CP '9'+1 ;Check max+1 JR NC,ISALPHA ;If too big, go try alphabetic CP A ;Set Z status RET ;return it ; end of file