; M4GET/ASM ; RECEIVE COMMAND READ EQU $ CALL NEWLIN NSTATE 'R' ;Set initial protocol state LD DE,DATA ;WHERE TO PUT THE TEXT (IF ANY.) LD A,CMTXT CALL COMND ;GET EITHER SOME TEXT OR A CONFIRM. JP KERMT3 ;DIDN'T GET ANYTHING. OR A ;GET ANY CHARS? JR Z,READ1 ;NOPE, JUST A REGULAR SEND. LD (ARGBLK+1),A ;STORE THE NUMBER OF CHARS. LD (TEMP4),A ;Save the length EX DE,HL ;GET POINTER INTO HL. LD (HL),EOS ;Put in the print terminator NSTATE 'r' ;Set state to receive init with file READ1 CALL INIT ;Clear input line and init buffers LD HL,0 ;Reset all the flags LD (NUMPKT),HL ;SET THE NUMBER OF PACKETS TO ZERO. LD (NUMRTR),HL ;SET THE NUMBER OF RETRIES TO ZERO. LD (KTRANS),HL XOR A LD (PKTNUM),A ;SET THE PACKET NUMBER TO ZERO. LD (NUMTRY),A ;SET THE NUMBER OF TRIES TO ZERO. LD (CZSEEN),A ;Reset the control-Z seen flag LD A,'R' ;Get the state character LD (DISFLG),A ;Set the display flag CALL CONDCHR ;Display it as well CALL CLRPRT ;CLEAR OUT THE COMMUNICATIONS PORT STROUT HELPMSG CALL PROTO JP KERMIT ; ; This is the complete state ; COMP EQU $ LD DE,INFMS3 ;PUT IN "COMPLETE" MESSAGE. LD A,(CZSEEN) OR A ;... JR Z,COMP1 XOR A ;YES, CLEAR FLAG. LD (CZSEEN),A LD DE,INMS13 ;ISSUE "INTERRUPTED" MESSAGE. COMP1 LD A,(DISFLG) ;But only if we are supposed to OR A CALL NZ,FINMES ;PRINT COMPLETION MESSAGE JP KERMIT ; ; This is the abort state ; SABORT EQU $ LD DE,INFMS4 ;Message to print JR COMP1 ;Go print it conditionally ; ; Initialize the buffers, and clear the line ; INIT XOR A ;BUFFER SIZE. LD (CHRCNT),A ;NUMBER OF CHARS LEFT. LD HL,BUFF ;ADDR FOR BEGINNING. LD (BUFPNT),HL ;STORE ADDR FOR BEGINNING. CALL CLRPRT RET ; ; RECEIVE ROUTINES ; ; RECEIVE INIT with no previous file header ; RINIT CALL CHKTRYS ;Check retry threshold LD A,'1' ;RESET BLOCK CHECK TYPE TO SINGLE CHAR LD (CURCHK),A ;STORE AS CURRENT TYPE FOR INITIALIZATION CALL RPACK ;GET A PACKET. JP NAK ;TRASHED PACKET NAK, RETRY. JR RINIT_1 ; ; This entry point is for GET's. The file name is in DATA, and ; and 'R' packet will be sent out to ask for the file. ; RINITF CALL CHKTRYS ;Check retry threshold LD A,'1' ;START WITH SINGLE CHARACTER CHECKSUM LD (CURCHK),A ;SAVE THE TYPE LD A,(TEMP4) ;Get the length LD (ARGBLK+1),A ;Put it in the packet XOR A ;Start at packet zero LD (ARGBLK),A LD A,'R' ;Send RECV INIT CALL SPACK JP RECABORT ;Die if SEND fails LD A,'1' ;Reset the blk check type to 1 LD (CURCHK),A ;Store it CALL RPACK ;Get a packet JP QUIT ;Trashed, return to protocol JR RINIT_1 ;Join other code ; ; Common receive init code ; RINIT_1 EQU $ IFANOT 'S',RINIT3 ;Send initiate packet? LD A,(NUMTRY) ;GET THE NUMBER OF TRIES. LD (OLDTRY),A ;SAVE IT. XOR A LD (NUMTRY),A ;RESET THE NUMBER OF TRIES. LD A,(ARGBLK) ;RETURNED PACKET NUMBER. (SYNC THEM.) CALL INCPKT ;Increment the packet number CALL INCDISPKT LD A,(ARGBLK+1) ;GET THE NUMBER OF ARGUMENTS RECEIVED. LD HL,DATA ;GET A POINTER TO THE DATA. CALL SPAR ;GET THE DATA INTO THE PROPER VARIABLES. LD HL,DATA ;GET A POINTER TO OUR DATA BLOCK. CALL RPAR ;SET UP THE RECEIVE PARAMETERS. LD (ARGBLK+1),A ;STORE THE RETURNED NUMBER OF ARGUMENTS. LD A,'Y' ;ACKNOWLEDGE PACKET. CALL SPACK ;SEND THE PACKET. JP RECABORT ;FAILED, ABORT. LD A,(INICHK) LD (CURCHK),A ;FOR ALL FUTURE PACKETS NSTATE 'f' LD A,'F' CALL CONDCHR ;Display which packet RET RINIT3 IFANOT 'E',NAK_0 ;Is it a NAK ? CALL ERROR JP RECABORT ; ; THESE ARE SOME UTILITY ROUTINES. ; ; RECABORT ; RECABORT EQU $ LD IX,RTRANS ;Get the receive data area CALL UPDTRANS ;Update the transfer statics ABORT NSTATE 'A' ;Set state to abort ABORT_1 LD A,(LOGTRAN) ;Check if logging active CP 1 ;Is it on? RET NZ ;Return if not LD DE,TRFCB ;Get the FCB TRLOG TRANABRT,ABORT_2;Log the aborted message RET ;Return ; ; Close up after a tranaction log error ; ABORT_2 XOR A ;Reset the logging active flag LD (LOGTRAN),A LD DE,TRFCB ;Close the log file CALL XCLOSE RET ; ; SNDABORT ; SNDABORT NSTATE 'A' LD IX,STRANS CALL UPDTRANS JP ABORT_1 ; ; Nack a packet. ; NAK_0 XOR A ;Reset to first packet LD (PKTNUM),A ;Set the packet number JR NAK ;Join NAK code ; NAK_RTR CALL UPDRTR ;Update retries ; NAK LD A,(PKTNUM) ;GET THE PACKET NUMBER WE'RE WAITING FOR. LD (ARGBLK),A XOR A ;NO DATA. LD (ARGBLK+1),A LD A,'N' ;NAK THAT PACKET. CALL SPACK JP RECABORT ;GIVE UP. LD A,'N' ;Display NAKed character CALL CONDCHR RET ;GO AROUND AGAIN. ; ; Update the retry count ; UPDRTR EQU $ LD HL,(NUMRTR) INC HL ;INCREMENT THE NUMBER OF RETRIES LD (NUMRTR),HL RET ; ; THIS ROUTINE SETS UP THE DATA FOR INIT PACKET (EITHER THE ; SEND_INIT OR ACK PACKET). ; RPAR ADDPUT RPSIZ ;GET THE RECEIVE PACKET SIZE. ADDPUT STIME ;Add send timeout ADDPUT RPAD ;Add padding amount LD A,(RPADCH) ;Get the pad character ADD A,100O ;UNCONTROL IT. PUTHL A ;Put the pad character in ADDPUT REOL ;Put the end of line character LD A,(RQUOTE) ;GET THE QUOTE CHAR. PUTHL A LD A,(EBQFLG) ;Is eighth bit quoting on? IFZ RPAR1 ;If not, then say no PUTHL 'Y' ;Say yes to anything JR RPAR2 RPAR1 PUTHL 'N' ;Say no eighth bit quoting RPAR2 LD A,(INICHK) ;Check type PUTHL A LD A,(RPTQ) ;Get the repeat quote PUTHL A LD A,9 ;Nine pieces of data RET ; ; Tochar() A, and store indirect HL, then increment HL ; TCHPUT ADD A,' ' ;Tochar(A) PUTHL A ;Store it, and increment RET ;Return ; ; THIS ROUTINE READS IN ALL THE SEND_INIT PACKET INFORMATION. ; SPAR LD (TEMP4),A ;Save the number of arguments PUSH BC XOR A LD B,A LD (RPTFLG),A ;Set everything to default CALL CHKSPAR ;Check number of characters in packet LD A,(HL) ;Get THEIR Max packet size SUB 20H ;Make it real LD (SPSIZ),A ;Save the value CALL CHKSPAR ;Check the count GETHL A SUB 20H ;Make it real LD (RTIME),A ;Send packet timeout value CALL CHKSPAR ;Check the count GETHL A SUB 20H ;Make it real LD (SPAD),A ;Save the padding character CALL CHKSPAR ;Check the count of characters GETHL A ADD A,100O ;RE-CONTROLIFY IT. AND 7FH ;Keep us honest LD (SPADCH),A ;Save the padding character CALL CHKSPAR ;Check the count GETHL A SUB 20H ;Make it the real value LD (SEOL),A ;Save the value CALL CHKSPAR ;Check the count GETHL A LD (SQUOTE),A ;Save it CALL CHKSPAR ;Check the count INC HL LD A,(EBQFLG) IFZ SPAR7 LD A,(HL) IFA 'Y',SPAR4 IFANOT 'N',SPAR5 XOR A JR SPAR6 SPAR4 LD A,'&' SPAR5 LD (EBQ),A SPAR6 LD (EBQFLG),A SPAR7 CALL CHKSPAR ;Check the count GETHL A LD C,A ;COPY VALUE LD A,(CHKTYP) ;GET OUR TYPE IFA C,SPAR8 LD A,'1' ;NO, USE SINGLE CHARACTER SPAR8 LD (INICHK),A CALL CHKSPAR ;Check the count GETHL A IFA ' ',SPAR10 LD C,A LD (RPTQ),A ;Save it LD (RPTFLG),A SPAR10 EQU $ POP BC RET ;AND RETURN ; ; Check the count of characters left in the packet. ; CHKSPAR EQU $ LD A,(TEMP4) INC B CP B RET P POP HL ;Remove return address POP BC ;Restore original BC RET ;Return to caller ; ; RECEIVE FILE ; RFILE CALL CHKTRYS ;Check retry threshold CALL RPACK ;GET A PACKET. JP NAK ;TRASHED PACKET NAK, RETRY. IFANOT 'S',RFILE2 ;If not send init, then jump CALL CHKOLD ;Make sure we have not surpassed retries CALL CHKBLKDEC ;Check if previous packet number JP NZ,NAK_RTR ;No, NAK it, and try again CALL UPDRTR ;Update the retry count. LD HL,DATA ;Get the data address CALL RPAR ;Set up the parameter information LD (ARGBLK+1),A ;Save the number of bytes in the packet LD A,'Y' ;Acknowledge with parameters CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort LD A,'S' ;Show the state as still send init CALL CONDCHR RET ; RFILE2 IFANOT 'Z',RFILE3 ;EOF packet? Jump if not CALL CHKOLD ;Check retry treshold CALL CHKBLKDEC ;Was it previous packet in sequence? JP NZ,NAK_RTR ;No, NAK it and try again CALL UPDRTR ;Update the number of retries XOR A ;Set length to zero LD (ARGBLK+1),A ;No data LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort LD A,'Z' ;Show state as EOF CALL CONDCHR RET RFILE3 IFANOT 'F',RFILE4 ;Jump if not FILE header packet CALL CHKBLK ;Check packet number against current JP NZ,NAK_RTR ;If not the same, then NAK and try again CALL INCPKT ;Increment the packet number CALL INCDISPKT ;Increment the real packet count LD A,'F' LD (DISFLG),A ;Set the non-generic mode flag CALL CONDCHR ;Print the state character CALL GOFIL ;Get the file JP RECABORT ;Abort on an error CALL INIT ;Initialize everything else CALL NUM2OLD ;Reset the retry number LD (ARGBLK+1),A ;On return, A is zero, so NO DATA LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort NSTATE 't' ;Set the state to receive transition LD A,(CZSEEN) ;Check if user requested EOF or EOT CP 'Z' ;Was it EOF? RET Z ;If it was EOF, then not yet XOR A ;Otherwise, must be EOT, so reset LD (CZSEEN),A ;Reset the flag RET ;And return, ignoring other states RFILE4 IFANOT 'B',RFILE5 ;Jump if not EOT CALL CONDCHR ;Display the state CALL CHKBLK ;Check packet number against current JP NZ,NAK_RTR ;If not right, then NAK and try again XOR A ;Set data length to zero LD (ARGBLK+1),A ;Store it for later LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort NSTATE 'C' ;Set state to complete RET ;Return to caller RFILE5 CP 'X' ;Type on tty packet? JP NZ,BADERROR ;Bad packet if not CALL CHKBLK ;Make sure the packet number is right RET NZ ;Return if not CALL SETUPDIS ;Set up to type on terminal CALL PRTPKTOUT ;Print the packet contents CALL NEWLIN ;Get a newline CALL NUM2OLD ;Get new retry count LD (ARGBLK+1),A ;Zero length (A is zero on return) LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Quit if send fails LD A,(PKTNUM) ;Get the packet number CALL INCPKT ;Add one CALL INCDISPKT ;Increment count for display NSTATE 'd' ;Set the state to receive data RET ;Return to protocol switch ; ; Transition between receive file, and receive data ; RECTRAN EQU $ STROUT KERREC ;Print the receiving message STROUT TFILNAM ;Print the name of the file LD A,(TRANLOG) ;Get the flag IFZ RTRAN_1 ;Test the flag and jump if not set LD DE,TRFCB ;Get the FCB TRLOG KERREC,RTRAN_3 ;Log the string TRLOG TFILNAM,RTRAN_3 ;Log the file name TRLOG TIMEMES,RTRAN_3 ;Log the time message CALL PRTTIME ;Print the current time RTRAN_1 EQU $ LD DE,FCB ;Get the file FCB address LD (RFIDCB),DE ;Save it as the output FCB CALL RSETPKT ;Reset the packet coding routines NSTATE 'd' ;Set the state to receive data RET ; ; Clean up on log file failure ; RTRAN_3 XOR A ;Clear A LD (TRANLOG),A ;Reset the logging flag LD DE,TRFCB ;Get the FCB CALL XCLOSE JR RTRAN_1 ;Ignore rest of logging code ; ; RECEIVE DATA ; RDATA CALL CHKTRYS ;Check the retry threshold CALL RPACK ;Get a packet JP NAK ;NAK it if bad packet IFANOT 'D',RDATA2 ;If not data check others RDAT11 CALL CHKBLK ;Check packet number against current JR Z,RDAT14 ;Jump if current packet CALL CHKOLD ;Check tries CALL CHKBLKDEC ;Check packet number against previous JP NZ,NAK_RTR ;Was not previous, so NAK it and retry CALL UPDRTR ;Update the number of retries XOR A ;Clear A LD (NUMTRY),A ;Reset the number of tries LD (ARGBLK+1),A ;Set the data length to zero LD A,'Y' ;Send ACK packet CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort LD A,'%' ;Say we already saw this packet CALL CONDCHR ;and just stay in the same state RET ;Next packet RDAT14 CALL INCPKT ;Increment the packet number CALL INCDISPKT ;Increment the real packet count LD A,(NUMTRY) ;Get the number of retries LD (OLDTRY),A ;Save it LD A,(ARGBLK+1) ;Get the length of the data CALL PTCHR ;Decode the data packet and write it out JP RECABORT ;Can't write to output, abort XOR A ;Clear A LD (NUMTRY),A ;Reset the number of tries LD (ARGBLK+1),A ;Set data length to zero LD C,A ;Make C zero LD A,(CZSEEN) ;Check the flag IFZ RDAT15 ;If nothing, then skip LD C,A ;Get the character typed LD A,1 ;One data character LD (ARGBLK+1),A ;Set the length LD A,C ;Get the data character LD (DATA),A ;Store the character RDAT15 LD A,'Y' ;Send an ACK (Possibly with data) CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort LD A,(NUMPKT) ;Time to log the progress? AND 3 ;Only every 4 packets RET NZ ;Return if not time LD A,'.' ;Get the character CALL CONDCHR ;Log it if not doing 'X' packet RET RDATA2 IFANOT 'F',RDATA3 ;File header? Jump if not CALL CHKOLD ;Check against previous retries CALL CHKBLKDEC ;Check packet number against previous JP NZ,NAK_RTR ;If not previous, then NAK and try again CALL UPDRTR ;Update the number of retries XOR A ;Clear A LD (NUMTRY),A ;Reset the number of retries LD (ARGBLK+1),A ;Set the length to zero LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort LD A,'%' ;Already saw this one. CALL CONDCHR ;Tell the user RET RDATA3 CP 'Z' ;If not EOF then jump JP NZ,RDATA4 CALL CONDCHR ;Display the new state CALL CHKBLK ;Check packet number against current JP NZ,NAK_RTR ;If not, then NAK and try again CALL INCPKT ;Increment the packet number CALL INCDISPKT ;Increment the real packet count LD A,(ARGBLK+1) ;Get the length of the data IFANOT 1,RDAT35 ;Jump if packet length not 1 LD A,(DATA) ;Just one, get the data IFANOT 'D',RDAT36 ;Is it discard? Jump if not LD A,(TRANLOG) ;Check if loggin active IFZ RDAT31 LD DE,TRFCB ;Get the log file FCB TRLOG TRANCANC,RDAT39 ;Print canceled message RDAT31 LD A,(DISCARD) ;Check users preference for incompletes IFZ RDAT35 ;Jump if no discard CALL CHKFCB ;Is this FCB or *SO? JR NZ,RDAT36 ;Jump if no remove, and don't close either CALL XREMOVE ;Remove it JR Z,RDAT32 ;Jump if remove succeeded CALL XERROR0 ;Print system error message JR RDAT36 ;Join other code RDAT32 STROUT RMMES ;Print the message LD A,(TRANLOG) ;Check if loggin active IFZ RDAT36 LD DE,TRFCB TRLOG RMMES,RDAT39 JR RDAT36 ;Join the other code RDAT35 CALL CHKFCB ;Check for file FCB, don't close *SO CALL Z,XCLOSE ;Conditionally close the FILE RDAT36 XOR A ;Reset the EOF seen flag LD (CZSEEN),A CALL NUM2OLD ;Reset the number of retries LD (ARGBLK+1),A ;Set the length to zero LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort NSTATE 'f' ;Set state to receive file LD IX,RTRANS ;Get the receive statistics address CALL UPDTRANS ;Update the transfer statistics RET ; ; Close up on a transaction log error ; RDAT39 XOR A ;Reset the logging flag LD (TRANLOG),A LD DE,TRFCB ;Close the file CALL XCLOSE JR RDAT36 ;Rejoin code ; RDATA4 CP 'X' ;Is it End Of Transmission? JP NZ,BADERROR ;If not, then bad packet CALL CHKBLKDEC ;Check if previous sequence number RET NZ ;Return if not XOR A ;Clear A LD (ARGBLK+1),A ;Set the length to zero LD A,'Y' ;Send an ACK CALL SPACK ;Send the packet JP RECABORT ;Send failed, abort RET ;Return to protocol ; ; Check received packet number against previous ; CHKBLKDEC EQU $ LD A,(PKTNUM) ;Get the current packet number DEC A ;Minus one for previous JR CHKBLK_1 ;Join other code ; ; Check the current packet number against that received ; CHKBLK EQU $ LD A,(PKTNUM) ;Get the current number CHKBLK_1 LD B,A ;Copy it to B LD A,(ARGBLK) ;Get the received packet number CP B ;Are they the same RET ;Return the condition codes ; ; Check for too many retries based on previous knowledge ; CHKOLD EQU $ LD A,(MAXTRY) ;Get the max number of tries LD B,A ;Save it LD A,(OLDTRY) ;Check against old max CP B ;Set the condition bits JR C,CHKOLD1 ;Jump if less than POP DE ;Remove the return address LD DE,ERMS10 ;Get the message CALL ERROR3 ;Display the error message JP RECABORT ;Change the state to abort CHKOLD1 INC A ;Increment the number of tries LD (OLDTRY),A ;Save the updated number of tries. RET ;Return normally ; ; Set up for a REMOTE command. The RFILE FCB is pointed at ; the *SO device, so that data received goes to the screen, ; rather than to a file. ; SETUPDIS EQU $ LD DE,(TMODCB) ;Get the current output DCB address LD (RFIDCB),DE ;Make it the current received file output XOR A ;Reset the 'display' flag LD (DISFLG),A CALL NEWLIN ;Get a fresh line RET ;Return to caller ; ; Conditionally display the string pointed to by DE based on the ; DISFLG which is active only during non REMOTE transactions. This ; makes REMOTE command pleasingly silent so that only the output ; of the requested operation is seen. ; CONDIS EQU $ PUSH AF ;Save A and the flags LD A,(DISFLG) ;Get the 'display' flag OR A ;Is it set? CALL NZ,PRTSTR ;If so, then print the string POP AF ;Restore the flags and A RET ;Return to caller ; ; Print the contents of the PACKET data area to the ; screen. ; PRTPKTOUT EQU $ LD HL,DATA ;Get the start of the string LD A,(ARGBLK+1) ;Get the length OR A RET Z ;Return if no data LD C,A ;Get the LSB into C LD B,0 ;Make BC a 16 bit offset ADD HL,BC ;HL is now the address past the end LD (HL),EOS ;Terminator for printing STROUT DATA JP NEWLIN ;Print a new line and return ; ; Update byte counters, IX MUST point to send or receive ; counter. We mod HL with 1K to get the remainder, and use ; the rest to sum into the current total. The remainder of ; HL mod 1024 is tucked away, but not forgotten. ; UPDTRANS EQU $ LD HL,(KTRANS) ;Calculate new total transfered LD C,(IX+2) ;Get the overflow counter LD B,(IX+3) ADD HL,BC ;Compute the total XOR A ;Reset the falg CALL C,ADD64K ;Add 64k if addition overflows LD A,H ;Get the high byte AND 3 ;Save the 2 lower order bits for mod 1024 LD B,A ;Put them in B LD C,L ;Put the other 8 bits into C LD (IX+2),C ;Store the new overflow (HL mod 1024) LD (IX+3),B LD A,H ;Trim to 1K multiple AND 0FCH ;A is now 4 times the number of Kbytes LD L,A ;Put it into L LD H,0 ;Make H zero SRL L ;Divide by 4 to align SRL L LD C,(IX) ;Get the total so far LD B,(IX+1) ADD HL,BC ;Compute the new total Kbyte LD (IX),L ;Put it back LD (IX+1),H ;ignoring any overflow CALL TRANSCNT ;Log the transaction size if logging LD HL,0 ;Set the counter to zero LD (KTRANS),HL LD (CURTRANS),HL ;Reset current counters LD (CURTRANS+2),HL RET ;Return to the caller ; ; Log the size of the last transaction to the logfile ; TRANSCNT EQU $ PUSH AF ;Save A and the FLAGS LD A,(TRANLOG) ;Is tranaction logging in progress? IFZ TRANSC_10 ;Jump if not active PUSH HL PUSH DE PUSH BC LD HL,(CURTRANS+2) ;Get the number of K transfered LD A,H OR L ;Is it zero? JR Z,TRANSC_3 ;Jump if it is CALL NUM2BUFF ;Put the number in the buffer LD DE,TRFCB ;Get the FCB address CALL OUTLOG ;Log the number of K transfered JP TRANSC_20 ;Close up on an error TRLOG KPLUS,TRANSC_20 ;Log the 'K + ' string TRANSC_3 EQU $ LD HL,(CURTRANS) ;Get the value CALL NUM2BUFF ;Make it printable LD DE,TRFCB ;Get the output FCB CALL OUTLOG ;Log the number of left over bytes JP TRANSC_20 ;Close up on an error TRLOG BYTESMES,TRANSC_20;Log the 'bytes transferred' message TRLOG TIMEMES,TRANSC_20; Log the time message CALL PRTTIME ;Print the current time TRANSC_9 EQU $ POP BC ;Restore the registers POP DE POP HL TRANSC_10 EQU $ POP AF ;Restore A and flags RET ;Return to caller TRANSC_20 EQU $ LD DE,TRFCB CALL XCLOSE XOR A LD (TRANLOG),A JP TRANSC_9 ; ; Convert binary to ascii, NO leading spaces ; NUM2BUFF EQU $ PUSH DE ;Save DE PUSH BC ;and BC LD DE,NBUFF ;Get the data buffer PUSH DE ;Save it for later CALL XHEXDEC EX DE,HL LD (HL),EOS ;Terminate the buffer POP HL ;Get the start back LD A,' ' ;Character to skip over N2B_1 EQU $ IFANOT (HL),N2B_2 ;Jump if passed last INC HL ;Point to next JR N2B_1 ;Back to test N2B_2 EQU $ POP BC ;Restore the registers POP DE RET ;Return to caller ;end of file