Category : Files from Magazines
Archive   : VOL11N02.ZIP
Filename : ZCOPY.ASM

 
Output of file : ZCOPY.ASM contained in archive : VOL11N02.ZIP
PAGE 75,132
;----------------------------------------------------------------------
; ZCOPY - Transfer files via the COM port. Syntax is
;----------------------------------------------------------------------
CSEG SEGMENT PARA PUBLIC 'CODE'
ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
ORG 100H
START: JMP BEGINNING ; go to start of program
JMP ZCXFER ; transfer self

DW OFFSET CONFIG - $ ;configuration for pcremote
COPYRIGHT DB "ZCOPY 1.4 (c) Copyright 1989, 1991 Ziff Communications Co."
DB 13,10,"PC Magazine ",254," Bob Flanders",13,10,"$",26
;version 1.4 modified by Terry Lahman and Kevin Sims to
;support PCREMOT2 version 1.0 and comm3/comm4.
BIOS_DATA EQU 40H ; bios data segment
TIMER_LOW EQU WORD PTR 6CH ; offset of low word
TIMER_HI EQU WORD PTR 6EH ; ... high word
LSR EQU 5 ; lsr register offset
LSR_DRDY EQU 00000001B ; data ready
LSR_ORUN EQU 00000010B ; overrun error
LSR_PRTY EQU 00000100B ; parity error
LSR_FRM EQU 00001000B ; framing error
LSR_BRK EQU 00010000B ; break interrupt
LSR_THRE EQU 00100000B ; transmit holding reg empty
LSR_TSRE EQU 01000000B ; transmit shift register emtpy
LSR_ERR EQU LSR_FRM+LSR_PRTY+LSR_ORUN ; error conditions
LCR_SETUP EQU 00000111B ; set 8 bits, no parity, 2 stop
LCR_DLAB EQU 10000000B ; divisor latch access bit
MCR EQU 4 ; mcr register offset
MCR_DTR EQU 00000001B ; data terminal ready enable
MCR_RTS EQU 00000010B ; request to send enable
MCR_OUT2 EQU 00001000B ; out2 control bit
I8259 EQU 20H ; 8259 control register addr
EOI EQU 20H ; 8259 end of interrupt command
I8259M EQU 21H ; 8259 mask register
FLG DB 0 ; system operation flag
FLGR EQU 80H ; receiver mode
FLGO EQU 40H ; /o overwrite
FLGU EQU 20H ; /u update
FLGD EQU 10H ; /d set current date
FLGA EQU 08H ; /a abort on full
FLGP EQU 04H ; /p pause for diskette
FLGW EQU 02H ; wait forever for other system
FLGPCR DB 0 ; PCREMOTE activated zcopy
FLG_SET EQU 07EH ; flag mask on flg_set
FLG1 DB 0 ; second flag
FLG1I EQU 80H ; system interrupts init'd
FLG1O EQU 40H ; output file is open
FLG1B EQU 20H ; break requested
FLG1S EQU 10H ; shutdown sent ok
XBUF_LTS DW 0 ; left to send
XBUFL EQU 4000H ; buffer length
XBUF_WL EQU XBUFL-WBUFL-1 ; write when over this value
IO_LEN EQU 512
XBUF_RBL EQU (XBUFL/IO_LEN)*IO_LEN ; number of bytes to read
ERRORS DW 8 ; errors so far
MAX_ERRORS EQU 3 ; max retries before resync
SYNC_BYTE EQU 08H ; first byte to sync on
SYNC_END EQU 04H ; end of sync bytes
SYNC_LEN EQU 128
SYNC_INC EQU 11
CRC_VAL EQU 01021H ; value for CRC
FNDOP DB 4EH ; find first/find next op
; Note: ** ZCPARM requires PARM_TBL to be in "OUDAPW" order
PARM_TBL DB 'OUDAPW' ; parameter specifications
ARG1 DW 0 ; pointer to arg1
ARG2 DW 0 ; pointer to arg2
WAIT_COUNT DW 0 ; timer tick counter
TIME_COUNT DW 0 ; timer inc amount
COM_STR DB "COM" ; com definition
BAUD_CNTR DB 0 ; baud rate counter
BAUD_TABLE DB 1,'115k $',2,'57.6k$',3,'38.4k$',6,'19.2k$',12,'9600 $'
DB 24,'4800 $',48,'2400 $',96,'1200 $'
LSR_VAL DB 0 ; lsr value after interrupt
LSR_NEW DB 0 ; lsr value is new flag
SEND_BLKNO DW 0 ; next block number to send
RCV_BLKNO DW 0 ; next block to receive
DFLDIR DB '.',0 ; default receive directory
CURDIR DB ".\" ; current directory
FILENAME DB 13 DUP (0) ; work area for send filename
;-------message process table--------
MSG_P_TBL:
CRE_FILE EQU 1 ; create requested file
OPR_PROMPT EQU 2 ; display a prompt
SHUTDOWN EQU 3 ; end the program
MSG_ACK EQU 4 ; previous message ok
DATA_BLK EQU 5 ; block of data
EOF_MARK EQU 6 ; end of file mark
MSG_NAK EQU 7 ; previous message not ok
QRY_FLE EQU 8 ; query file existence
SET_FLG EQU 9 ; set flag bits
RESYNC EQU 10 ; resync
OPR_REPLY EQU 11 ; reply from oper
DIENOW EQU 0FFH ; die immediately
DW OFFSET CRE_FILE_P,OFFSET ZCPPROMPT,OFFSET SHUTDOWN_P,OFFSET MSG_ACK_P
DW OFFSET DATA_BLK_P,OFFSET EOF_MARK_P,OFFSET MSG_NAK_P,OFFSET QRY_FLE_P
DW OFFSET SET_FLG_P,OFFSET RESYNC_P
SOH EQU 01H ; start of header
STX EQU 02H ; start of text
ETX EQU 03H ; end of text
ACK EQU 06H ; acknowledge
NAK EQU 15H ; non-acknowledge
RLR EQU 1DH ; request last response
LAST_RESP DB NAK ; last response holder
SEC_30 EQU (18*30)+(2*3) ; 30 seconds in ticks
SEC_10 EQU (18*10)+(2*1) ; 10 seconds in ticks
SEC_5 EQU (18*5)+1 ; 5 seconds in ticks
SEC_3 EQU (18*3)+1 ; 3 seconds in ticks
SEC_1 EQU (18*1)+1 ; 1 second in ticks
DSRWAIT DW SEC_30 ; tics to wait for dsr
RETRIES EQU 3 ; number of retries
; message structure
MSTX EQU 0 ; start of message
MCRC EQU MSTX+1 ; CRC value
MLEN EQU MCRC+2 ; length of remainder less etx
MBLKNO EQU MLEN+2 ; number of this block
MCMD EQU MBLKNO+2 ; command
MDATA EQU MCMD+1 ; data area
; ; etx address based on data len
MOHEAD EQU 6 ; overhead bytes not in len
; ; stx + crc + len + etx
; DTA structure for DOS "find matching" call
DTA EQU 80H ; dta offset
DTA_ATTR EQU BYTE PTR DTA+21 ; file attribute
DTA_TIME EQU WORD PTR DTA_ATTR+1 ; file time
DTA_DATE EQU WORD PTR DTA_TIME+2 ; file date
DTA_LSIZ EQU WORD PTR DTA_DATE+2 ; file lsw of size
DTA_HSIZ EQU WORD PTR DTA_LSIZ+2 ; file msw of size
DTA_NAME EQU BYTE PTR DTA_HSIZ+2 ; file name of file
DTA_LEN EQU DTA_NAME+15-DTA ; length of dta find entry
; messages to user
PARMERR DB "Usage: ZCOPY source [target] [/w][/u][/o][/a][/p][/d][/#]"
DB 13,10
DB "/w-wait",13,10
DB "/u-newer files only",13,10
DB "/o-overwrite",13,10
DB "/a-abort if target full",13,10
DB "/p-pause before copy",13,10
DB "/d-use current date",13,10
DB "/#-starting bps rate: /1 thru /6",13,10
DB " /1=115K, /2=57.6K, /3=38.4K",13,10
DB " /4=19.2K, /5=9600, /6=4800",13,10
DB " /7=2400, /8=1200",13,10,"$"
BADDIR DB "Invalid directory.",13,10,'$'
FILERR DB "No files specified.",13,10,'$'
FILENOPEN DB "Unable to create, skipping.",13,10,'$'
INVFIL DB "Invalid filename.",13,10,'$'
DISKFULL DB "Disk full .. press a key ..",13,10,'$'
BSENT DB " being sent.",13,10,'$'
BRECVD DB " being received.",13,10,'$'
TOOMANY DB "Resyncing ... ",13,10,'$'
FILEXISTS DB ": exists. Overwrite?",13,10,'$'
TOOBIG DB ": won't fit, skipped.", 13, 10, '$'
WAITING DB "Press a key to continue ..",13,10,'$'
SHUTDOWN_R1 DB 13,10
SHUTDOWN_R DB "ZCOPY is done."
CRLF DB 13,10,'$'
TRYING DB 13,"Baud rate $"
SPDERROR DB 13,10,"Link not established.",13,10,'$'
SPDSET DB 13,10,"Link established.",13,10,'$'
NOTUP DB 13,10,"Other node not detected.",13,10,'$'
DB '.....'
B_LEFT DB '.h blocks left. ',13,'$'
CONFIG: ; used by PCREMOTE to reconfigure comm3/4 if necessary
COMM_PORT3 DW 02E8H ; comm port 3 address used by pcremote
COMM_PORT4 DW 02E0H ; comm port 4 address used by pcremote
COMM3_INT DB 4 ; interrupt used by comm 3
COMM4_INT DB 3 ; interrupt used by comm 4

BEGINNING PROC NEAR ; start of program
MOV DX,OFFSET COPYRIGHT
MOV AH,9
INT 21H
MOV BX, OFFSET BUF_START ; bx -> start of buffer space
MOV RBUF, BX ; set offset of the receive buffer
MOV RBUF_RPTR, BX ; .. for receive
MOV RBUF_GPTR, BX ; .. and get
ADD BX, RBUFL ; bx -> start of send buffer
MOV RBUF_HI, BX ; .. save for int handler
MOV SBUF, BX ; set offset of the send buffer
ADD BX, SBUFL ; bx -> start of work buffer
MOV WBUF, BX ; set offset of the work buffer
ADD BX, WBUFL ; bx -> star to file build buffer
MOV XBUF, BX ; set pointer to buffer
MOV XBUF_PTR, BX ; .. and write pointer
ADD BX, XBUFL ; bx -> entry directory area
MOV EDIR, BX ; .. save pointer
MOV AH, 19H ; ah = get current drive
INT 21H ; al = current drive
MOV EDRV, AL ; save entry drive
MOV SI, EDIR ; si -> current directory area
MOV BYTE PTR [SI], '\' ; .. start with backslash
INC SI ; si -> next byte
XOR DL, DL ; dl = default drive
MOV AH, 47H ; ah = get current dir
INT 21H ; .. save in area
CALL ZCPARM ; set up parameters
CALL ZCINIT ; init interrupts
CALL ZCSPEED ; setup transfer speed
TEST FLG, FLGR ; Q. receiver?
JNZ MAINRCV ; A. yes .. rcv
MOV AL, SET_FLG ; al = set flags command
MOV SI, OFFSET FLG ; si -> flags byte
MOV CX, 1 ; .. len to send
CALL ZCBLKSND ; .. send set flags
MOV BX, WAIT_COUNT ; bx = wait_count
ADD BX, SEC_10 ; .. max 10 secs
MAIN10: CALL ZCTRYRCV ; Q. block available?
JNC MAIN15 ; A. yes .. continue
CMP WAIT_COUNT, BX ; Q. timeout?
JB MAIN10 ; A. no .. continue
MOV DX, OFFSET NOTUP ; dx -> error message
CALL ZCDIE ; .. die of old age
MAIN15: OR FLG, AL ; save flags
TEST FLG, FLGP ; Q. pause before starting?
JZ MAIN20 ; A. no .. wait
MOV DI, OFFSET WAITING ; di -> waiting prompt
CALL ZCSPROMPT ; .. wait for response
MAIN20: JMP ZCSF ; send the files requested
MAINRCV: CALL ZCRECV ; start receive mode
JMP MAINRCV ; .. continuously
BEGINNING ENDP
; ---------------------------------------------------------------------
; This routine initializes the system interrupts.
; ---------------------------------------------------------------------
ZCINIT PROC NEAR
MOV DX, IO_BASE ; dx = base io port
IN AL, DX ; .. clear any character
INC DX ; dx = ier
XOR AL, AL ; al = zero
OUT DX, AL ; no ints for now
ADD DX, 3 ; dx = mcr
MOV AL, MCR_DTR+MCR_RTS ; set DTR and RTS on
OUT DX, AL ; .. set off all other stats
ADD DX, 2 ; dx = msr
IN AL, DX ; .. reset msr now
MOV AL, INT_VECTOR ; al = com interupt to set
ADD AL, 8 ; .. set to actual interrupt
MOV SI, OFFSET OLD_COM ; si -> save area for old
MOV DX, OFFSET ZCINT ; dx -> com int routine
CALL ZCSETINT ; set up the interrupt
MOV AL, 08H ; al = timer interrupt to set
MOV SI, OFFSET OLD_TIMER ; si -> save area for old
MOV DX, OFFSET ZCTIMER ; dx -> timer int routine
CALL ZCSETINT ; set up the interrupt
MOV AL, 1BH ; al = control break interrupt
MOV SI, OFFSET OLD_CTLBRK ; si -> save area for old
MOV DX, OFFSET ZCCTLBRK ; dx -> timer int routine
CALL ZCSETINT ; set up the interrupt
MOV AL, 23H ; al = control break interrupt
MOV SI, OFFSET OLD_DOSCTLB ; si -> save area for old
MOV DX, OFFSET ZCCTLBRK ; dx -> timer int routine
CALL ZCSETINT ; set up the interrupt
MOV AL, 24H ; ax = doserr interrupt to set
MOV SI, OFFSET OLD_DOSERR ; si -> save area for old
MOV DX, OFFSET ZCDOSERR ; dx -> dos error routine
CALL ZCSETINT ; set up the interrupt
MOV DX, IO_BASE ; dx -> base of com port
ADD DX, 2 ; dx -> Int id register
MOV ZCINTIIR1, DX ; modify int rtn instruction
MOV ZCINTIIR2, DX ; modify int rtn instruction
INC DX ; dx -> line control reg
MOV AL, LCR_SETUP ; al = com parm setup
OUT DX, AL ; .. set line characteristics
INC DX ; dx -> modem control reg
MOV AL, MCR_DTR+MCR_RTS+MCR_OUT2 ; al = set DTR, RTS, &OUT2
OUT DX, AL ; .. set MCR value
SUB DX, 3 ; dx -> interrupt enable reg
MOV AL, 05H ; al = allow lsr & rx ints
OUT DX, AL ; .. set int enable register
IN AL, 21H ; al = current int mask
MOV CL, INT_VECTOR ; cl = interrupt to use
MOV AH, 1 ; ah = 1 ..
SHL AH, CL ; .. shift bit to mask pos
NOT AH ; .. and invert mask
AND AL, AH ; .. set off mask bit
OUT 21H, AL ; .. allow com interrupts
OR FLG1, FLG1I ; show initialized
MOV AL, INT_VECTOR ; al = int vector
DEC AL ; al -> lower vector
OR AL, 0C0H ; al = set 8259 priority cmd
OUT 20H, AL ; .. reset priority
RET ; .. return to caller
ZCINIT ENDP
; ---------------------------------------------------------------------
; This routine resets the system to pre-runtime settings.
; ---------------------------------------------------------------------
ZCRESET PROC NEAR
MOV AL, 0C7H ; al = set priority command
OUT 20H, AL ; reset normal 8259 priority
TEST FLG1, FLG1O ; Q. file open?
JZ ZCRESET10 ; A. no .. continue
MOV BX, HANDLE ; bx = file handle
MOV AH, 3EH ; ah = close
INT 21H ; .. close that file
ZCRESET10: MOV CL, INT_VECTOR ; cl = interrupt to use
IN AL, 21H ; al = current int mask
MOV AH, 1 ; ah = 1 ..
SHL AH, CL ; .. shift bit to mask pos
OR AL, AH ; .. set on mask bit
OUT 21H, AL ; .. disallow com interrupts
MOV DX, IO_BASE ; dx -> base of com port
INC DX ; dx -> interrupt enable reg
XOR AL, AL ; al = all interrupts off
OUT DX, AL ; .. disallow all interrupts
ADD DX, 3 ; dx -> modem control reg
MOV AL, MCR_DTR+MCR_RTS ; leave DTR and RTS on and
OUT DX, AL ; .. set OUT2 off
MOV AL, INT_VECTOR ; al = com interupt to reset
ADD AL, 8 ; .. set to actual interrupt
MOV SI, OFFSET OLD_COM ; si -> save area for old
CALL ZCRESINT ; reset the interrupt
MOV AL, 1BH ; al = ctlbreak interrupt
MOV SI, OFFSET OLD_CTLBRK ; si -> save area for old
CALL ZCRESINT ; reset the interrupt
MOV AL, 23H ; al = ctlbreak interrupt
MOV SI, OFFSET OLD_DOSCTLB ; si -> save area for old

CALL ZCRESINT ; reset the interrupt
MOV AL, 08H ; al = timer interrupt to reset
MOV SI, OFFSET OLD_TIMER ; si -> save area for old
CALL ZCRESINT ; reset the interrupt
CALL ZCTIMUP ; assure timer fully reset
MOV AL, 24H ; ax = doserr interrupt to reset
MOV SI, OFFSET OLD_DOSERR ; si -> save area for old
CALL ZCRESINT ; reset the interrupt
MOV AH, 0EH ; ah = DOS setdrive
MOV DL, EDRV ; dl = drive to set
INT 21H ; reset original drive
MOV AH, 3BH ; ah = DOS set directory
MOV DX, EDIR ; dx -> original directory
INT 21H ; reset original directory
RET ; .. return to caller
ZCRESET ENDP
; ---------------------------------------------------------------------
; This routine initializes an interrupt vector.
; Entry:al = interrupt to setup,si -> save area for old,dx -> routine to call
; ---------------------------------------------------------------------
ZCSETINT PROC NEAR
PUSH BX ; save caller's bx
PUSH ES ; .. and es
MOV AH, 35H ; ah = get int vector
INT 21H ; es:bx -> current vector
MOV WORD PTR [SI], BX ; save offset
MOV WORD PTR [SI+2], ES ; .. and segment
MOV AH, 25H ; ah = set int vector
INT 21H ; .. set up the interrupt
POP ES ; restore regs
POP BX
RET ; .. return to caller
ZCSETINT ENDP
; ---------------------------------------------------------------------
; This routine restores the original interrupt vector.
; Entry:al = interrupt to setup,si -> save area for old
; ---------------------------------------------------------------------
ZCRESINT PROC NEAR
PUSH DS ; save ds
PUSH DX ; .. and dx
LDS DX, [SI] ; ds:dx -> original vector
MOV AH, 25H ; ah = set int vector
INT 21H ; .. set up the interrupt
POP DX ; restore regs
POP DS
RET ; .. return to caller
ZCRESINT ENDP
; ---------------------------------------------------------------------
; This routine intercepts control-breaks and handles them gracefully.
; ---------------------------------------------------------------------
ZCCTLBRK PROC NEAR
OR CS:FLG1, FLG1B ; show break issued
IRET ; return to caller
ZCCTLBRK ENDP
; ---------------------------------------------------------------------
; This routine increments a local timer variable when called.
; ---------------------------------------------------------------------
ZCTIMER PROC NEAR
STI ; allow ints
PUSH AX ; save ax
MOV AL, 20H ; al = reset interrupt
OUT 20H, AL ; .. reset it
POP AX ; restore ax
INC CS:WAIT_COUNT ; increment # ticks
INC CS:TIME_COUNT ; .. and timer ticks
IRET ; return from interrupt
ZCTIMER ENDP
; ---------------------------------------------------------------------
; This routine updates the system timer.
; ---------------------------------------------------------------------
ZCTIMUP PROC NEAR
OR TIME_COUNT, 0 ; Q. any update?
JZ ZCTIMUP90 ; A. no .. return
PUSH DS ; save ds
MOV AX, 40H ; ax -> bios low memory seg
MOV DS, AX ; ds -> bios low memory seg
XOR AX, AX ; ax = zero
XCHG AX, CS:TIME_COUNT ; ax = ticks since update
ADD DS:[TIMER_LOW], AX ; .. add to timer value
ADC DS:[TIMER_HI], 0 ; .. and the overflow
POP DS ; restore ds
ZCTIMUP90: RET
ZCTIMUP ENDP
; ---------------------------------------------------------------------
; This routine intercepts and handles DOS critical errors.
; Entry: Standard INT 24h entry; Exit: Only allows retries and aborts.
; ---------------------------------------------------------------------
ZCDOSERR PROC NEAR
PUSHF ; save the flags
AND AH, NOT 28H ; allow retry, abort only
CALL CS:OLD_DOSERR ; .. call old routine
CMP AL, 1 ; Q. retry?
JE ZCDOSERR90 ; A. yes .. continue
OR CS:FLG1, FLG1B ; turn on die flag
MOV AL, 0 ; .. and ignore error
ZCDOSERR90: IRET
ZCDOSERR ENDP
; ---------------------------------------------------------------------
; Communications interrupt handler. Handled from the com port
; specified by the user on the command line.
; ---------------------------------------------------------------------
ZCINT PROC NEAR ; interrupt handler entry point
PUSH AX ; save entry registers
PUSH BX ; ...
PUSH DX ; ...
MOV AL, EOI ; al = EOI instruction
OUT I8259, AL ; .. reset the 8259
ZCINT05: MOV DX, 0FFFFH ; dx = int ID register addr
ZCINTIIR1 EQU WORD PTR ZCINT05+1 ; .. address to mod for iir
IN AL, DX ; al = int id
JMP SHORT ZCINT17 ; .. process interrupt
ZCINT10: MOV DX, 0FFFFH ; dx = int ID register addr
ZCINTIIR2 EQU WORD PTR ZCINT10+1 ; .. address to mod for iir
ZCINT15: IN AL, DX ; al = interrupt ID
TEST AL, 00000001B ; Q. any interrupt?
JNZ ZCINT90 ; A. no .. exit now.
ZCINT17: CMP AL, 4 ; Q. received data int?
JNE ZCINT50 ; A. no .. process stat regs
SUB DX, 2 ; dx = base reg
IN AL, DX ; al = next receive character
ZCINT_RPTR: MOV BX, 0F1F2H ; bx -> receive buffer
MOV CS:[BX], AL ; .. save received character
INC BX ; bx -> next receive char pos
ZCINT_RHI: CMP BX, 0F1F2H ; Q. end of receive buffer?
JNB ZCINT_RBUF ; A. yes .. set to rbuf
ZCINT20: MOV CS:RBUF_RPTR, BX ; save receive pointer
JMP ZCINT10 ; see if another int occurred
ZCINT_RBUF: MOV BX, 0F1F2H ; bx -> start of buffer
JMP ZCINT20 ; .. and continue
ZCINT50: ADD DX, 3 ; dx -> lsr
IN AL, DX ; .. get value
MOV CS:LSR_VAL, AL ; save lsr value
MOV CS:LSR_NEW, 0FFH ; .. show value is new
SUB DX, 3 ; dx -> int ID reg
JMP ZCINT15 ; See if done
ZCINT90: STI ; allow interrupt
POP DX ; Restore entry registers
POP BX ; ...
POP AX ; ...
IRET ; return from interrupt
RBUF_RPTR EQU WORD PTR ZCINT_RPTR+1 ; rptr word
RBUF EQU WORD PTR ZCINT_RBUF+1 ; rbuf word
RBUF_HI EQU WORD PTR ZCINT_RHI+2 ; hi word
ZCINT ENDP
; ---------------------------------------------------------------------
; This routine sends the requested character.
; Entry: al = character to send
; ---------------------------------------------------------------------
ZCPUTC PROC NEAR
PUSH BX ; save registers
PUSH CX
PUSH DX
PUSH SI
PUSH AX
MOV DX, IO_BASE ; dx -> base io address
ADD DX, LSR ; dx = line status addr
ZCPUTC10: IN AL, DX ; al = lsr
AND AL, LSR_THRE ; leave tsre & thre on
CMP AL, LSR_THRE ; Q. all empty?
JNE ZCPUTC10 ; A. no .. retry
POP AX ; get character
MOV DX, IO_BASE ; .. and base register
OUT DX, AL ; .. put the char
POP SI ; restore registers
POP DX
POP CX
POP BX
RET ; ..and return to caller
ZCPUTC ENDP
; ---------------------------------------------------------------------
; This routine gets a character from the receive buffer if one is available.
; Exit: al = character; carry flag set indicates no character available
; ---------------------------------------------------------------------
ZCGETC PROC NEAR ; get a received char, if any
CALL ZCCLA ; Q. anything to get?
JNC ZCGETC80 ; A. yes .. update pointers
RET ; .. else .. return to caller
ZCGETC80: PUSH BX ; save caller's bx
MOV BX, RBUF_GPTR ; bx = next get pointer
INC BX ; bx -> next position
CMP BX, RBUF_HI ; Q. end of buffer?
JB ZCGETC90 ; A. no .. store as it
MOV BX, RBUF ; bx -> start of buffer
ZCGETC90: MOV RBUF_GPTR, BX ; save get pointer
POP BX ; restore caller's bx
CLC ; .. show char available
RET ; return to caller
ZCGETC ENDP
; ---------------------------------------------------------------------
; This routine reads one character from the receive buffer
; without adjusting the read buffer pointers.
; Exit: al = character; carry flag set indicates no character available
; ---------------------------------------------------------------------
ZCCLA PROC NEAR
PUSH BX ; save registers
MOV BX, RBUF_GPTR ; bx = next get offset
CMP BX, RBUF_RPTR ; Q. anything to get?
JNE ZCCLA10 ; A. yes .. continue
STC ; show no char found
JMP SHORT ZCCLA90 ; .. and return to caller
ZCCLA10: MOV AL, [BX] ; al = char
CLC ; .. set carry to char found
ZCCLA90: POP BX ; restore registers
RET ; .. and return to caller
ZCCLA ENDP
; ---------------------------------------------------------------------
; This routine parses the command line.
; Exit: Returns to DOS if error else argument bits and values are set.
; ---------------------------------------------------------------------
ZCPARM PROC NEAR
CALL ZCUC ; upper case the parm area
MOV SI, 81H ; si -> parms area
ZCPARM10: CALL ZCPARMC ; get parameter character
CMP AL, '/' ; Q. option?
JE ZCPARM80 ; A. yes .. check option
CMP AL, 13 ; Q. end of line?
JE ZCPARM50 ; A. yes .. exit
CMP AL, ' ' ; Q. blank?
JNA ZCPARM10 ; A. yes .. skip
CALL ZCARG ; set the argument
JC ZCPARMERR ; .. die on an error
ZCPARM30: CALL ZCPARMC ; get next character
CMP AL, 13 ; Q. end of line?
JE ZCPARM50 ; A. yes .. process
CMP AL, '/' ; Q. start of option?
JE ZCPARM80 ; A. yes .. process
CMP AL, ' ' ; Q. end of parm?
JA ZCPARM30 ; A. no .. next char
MOV BYTE PTR [SI-1], 0 ; end the parm
JMP ZCPARM10 ; .. look for next
ZCPARM50: MOV BYTE PTR [SI-1], 0 ; zero out the
CMP ARG1, 0 ; Q. parm 1 available?
JE ZCPARMERR ; A. no .. error
CMP ARG2, 0 ; Q. Parm 2 available?
JNE ZCPARM60 ; A. yes .. continue
MOV ARG2, OFFSET DFLDIR ; set up for current directory
ZCPARM60: CALL ZCCOM ; check the com parameter
CALL ZCFLSET ; set up file parameters
RET ; return to caller
ZCPARM80: MOV BYTE PTR [SI-1], 0 ; end the parm
CALL ZCPARMC ; al = option character
CMP AL, '1' ; Q. < 1?
JB ZCPARM82 ; A. yes .. continue
CMP AL, '8' ; Greater than 8 ?
JA ZCPARM82 ; A. yes .. continue
SUB AL, '1' ; .. adjust the value
MOV BAUD_CNTR, AL ; .. save as starting baud
JMP ZCPARM10 ; .. continue
ZCPARM82: LEA DI, PARM_TBL ; di -> table to search
MOV CX, 6 ; cx = max entries
REPNE SCASB ; Q. entry found?
JNE ZCPARM85 ; A. no .. check for /r option
MOV AL, 2 ; al = "W" flag
SHL AL, CL ; .. do it
OR FLG, AL ; .. or in the flag
JMP ZCPARM10 ; .. continue scanning
ZCPARM85: CMP AL, 'R' ; Q. pcremote flag
JNE ZCPARMERR ; A. no .. parameter in error
INC BYTE PTR FLGPCR ; A. yes.. set the pcremote flag
MOV BYTE PTR ZCPCR10+2,SEC_3 ; change the delay for modems
MOV BYTE PTR ZCPCR20+2,SEC_3 ; change the delay for modems
MOV BYTE PTR ZCPCR30+2,SEC_3 ; change the delay for modems
JMP ZCPARM10 ; .. continue scanning
ZCPARMERR: LEA DX, PARMERR ; dx -> invalid number of parms
CALL ZCDIE ; abort
ZCPARM ENDP
; ---------------------------------------------------------------------
; This routine gets the next character from the parm area in the DOS PSP.
; Entry: si -> next char to get.
; Exit: Char translated to upper case. al = character; si -> next character
; ---------------------------------------------------------------------
ZCPARMC PROC NEAR
CMP BYTE PTR [SI], 'a' ; Q. below lower case a?
JB ZCPARMC10 ; A. yes .. do not upcase
CMP BYTE PTR [SI], 'z' ; Q. above lower case z?
JA ZCPARMC10 ; A. yes .. same
AND BYTE PTR [SI], NOT 20H ; .. translate to upper case
ZCPARMC10: LODSB ; load the character in AL
RET ; .. and return to caller
ZCPARMC ENDP
; ---------------------------------------------------------------------
; This routine sets the appropriate argument pointer.
; Entry: si -> second character in argument.
; Exit: arg1 or arg2 pointer filled in. Carry set if more than 2 arguments
; ---------------------------------------------------------------------
ZCARG PROC NEAR
LEA BX, [SI-1] ; bx -> argument
CMP ARG1, 0 ; Q. arg1 filled in?
JNE ZCARG10 ; A. yes .. check 2
MOV ARG1, BX ; save arg1 pointer
JMP SHORT ZCARG90 ; .. exit ok!
ZCARG10: CMP ARG2, 0 ; Q. arg2 filled in?
JE ZCARG20 ; A. no .. fill it in
STC ; else .. error
RET ; .. and return to caller
ZCARG20: MOV ARG2, BX ; save arg2 pointer
ZCARG90: CLC ; show no error
RET ; return to caller
ZCARG ENDP
; ---------------------------------------------------------------------
; This routine determines whether we are the sender or receiver
; and which communication port is to be used.
; Entry: ARG1, ARG2 must be set, one pointing to COMx with an optional colon
; Exit: Send/receive flag is set properly. IO_BASE and INT_VECTOR are set.
; Exits to DOS if no COM port or 2 COM ports specified.
; ---------------------------------------------------------------------
ZCCOM PROC NEAR
MOV SI, ARG1 ; si -> parm1
CALL ZCCOMP ; Q. receiver?
JC ZCCOM10 ; A. no .. check parm2
OR FLG, FLGR ; else .. set receiver mode
ZCCOM10: MOV BL, FLG ; bx = flags
MOV SI, ARG2 ; si -> parm2
CALL ZCCOMP ; Q. sender?
JC ZCCOM20 ; A. no .. assure receiver
TEST BL, FLGR ; Q. Are we receiver?
JZ ZCCOM80 ; A. No .. parms ok
ZCCOM15: LEA DX, PARMERR ; dx -> parameter error
CALL ZCDIE ; .. die gracefully
ZCCOM20: TEST BL, FLGR ; Q. Are we a receiver?
JZ ZCCOM15 ; A. no .. issue error
ZCCOM80: CMP AL, 1 ; Q. COM1?
JNE ZCCOM85 ; A. no .. set up for COM2.
MOV IO_BASE, 3F8H ; set base port address
MOV INT_VECTOR, 4 ; .. and interrupt number
RET ; return to caller
ZCCOM85: CMP AL, 2 ; Q. COM2?
JNE ZCCOM90 ; A. no .. check for COM3.
MOV IO_BASE, 2F8H ; set base port address
MOV INT_VECTOR, 3 ; .. and interrupt number
RET ; return to caller
ZCCOM90: CMP AL, 3 ; Q. COM3?
JNE ZCCOM95 ; A. no .. check for COM4.
MOV AX,COMM_PORT3
MOV IO_BASE, AX ; set base port address
MOV AL, BYTE PTR COMM3_INT
MOV INT_VECTOR, AL ; .. and interrupt number
RET ; return to caller
ZCCOM95: MOV AX,COMM_PORT3
MOV IO_BASE, AX ; set base port address COM4
MOV AL, BYTE PTR COMM4_INT
MOV INT_VECTOR, AL ; .. and interrupt number
RET ; return to caller
ZCCOM ENDP
; ---------------------------------------------------------------------
; This routine looks for a valid COMx: in the passed parameter.
; Entry: si -> string to check
; Exit: Carry set if not COMx: string; al = 1 or 2 for COM1: or COM2:
; ---------------------------------------------------------------------
ZCCOMP PROC NEAR
PUSH BX ; save bx
MOV BX, SI ; bx -> argument
CLD ; set direction
LEA DI, COM_STR ; di -> 'COM'
MOV CX, 3 ; cx = length of string
REPE CMPSB ; Q. 'COM' start the string?
JE ZCCOMP10 ; A. yes.. continue
ZCCOMP05: STC ; show not a com port
POP BX ; restore bx
RET ; .. return to caller
ZCCOMP10: CMP BYTE PTR [BX+4], ':' ; Q. end in colon?
JE ZCCOMP30 ; A. yes .. check which port
CMP BYTE PTR [BX+4], 0 ; Q. non-colon end?
JNE ZCCOMP05 ; A. no .. not a com parameter
ZCCOMP30: MOV AL, [BX+3] ; ah = ascii com port number.
SUB AL, 30H ; ah = binary com port number.
CMP AL, 1 ; Q. below COM1?
JB ZCCOMP05 ; A. yes .. invalid com port
CMP AL, 4 ; Q. above com4?
JA ZCCOMP05 ; A. yes .. invalid com port
CLC ; else .. good com port
POP BX ; restore bx
RET ; .. return to caller
ZCCOMP ENDP
; ---------------------------------------------------------------------
; This routine displays an error message and terminates.
; Entry: dx -> error message ended in dollar sign.
; Exit: Exits to DOS
; ---------------------------------------------------------------------
ZCDIE PROC NEAR
TEST FLG1, FLG1I ; Q. initialized?
JZ ZCDIE10 ; A. no .. print & return
PUSH DX ; else .. save message address
CALL ZCRESET ; .. reset system
POP DX ; .. restore message address
ZCDIE10: MOV AH, 9 ; ah = print string
INT 21H ; .. call dos to print error
MOV AX, 4C01H ; ax = exit
INT 21H ; .. terminate routine
ZCDIE ENDP
; ---------------------------------------------------------------------
; This routine changes all arguments on the command line to upper case
; ---------------------------------------------------------------------
ZCUC PROC NEAR
PUSH SI ; save caller regs
PUSH DI
MOV SI, 81H ; si -> start of parm area
MOV DI, SI ; .. same for di
ZCUC10: LODSB ; al = char
CMP AL, 13 ; Q. end of line?
JE ZCUC90 ; A. yes .. end of line!
CMP AL, 'a' ; Q. is it below 'a'?
JB ZCUC20 ; A. yes .. continue
CMP AL, 'z' ; Q. is it above 'z'?
JA ZCUC20 ; A. yes .. continue
SUB AL, 20H ; set to upper case
ZCUC20: STOSB ; save the byte
JMP ZCUC10 ; .. and continue
ZCUC90: POP DI ; restore caller regs
POP SI
RET ; .. and return to caller
ZCUC ENDP
; ---------------------------------------------------------------------
; This routine sets the default drive and path.
; On the sending machine, the file name is also set up.
; ---------------------------------------------------------------------
ZCFLSET PROC NEAR
MOV DI, ARG1 ; di -> first arg
TEST FLG, FLGR ; Q. receiver?
JZ ZCFLSET10 ; A. no .. continue
MOV DI, ARG2 ; di -> second arg
ZCFLSET10: CMP BYTE PTR [DI+1], ':' ; Q. drive specified?
JNE ZCFLSET20 ; A. no .. use current drive
MOV DL, [DI] ; dl = drive to use
SUB DL, 'A' ; get requested drive number
MOV AH, 0EH ; set requested drive
INT 21H ; .. via dos
ADD DI, 2 ; di -> next part
ZCFLSET20: TEST FLG, FLGR ; Q. receiver?
JNZ ZCFLSET50 ; A. yes .. filename not used
PUSH DI ; save pointer
MOV BX, DI ; bx -> start of area
XOR AL, AL ; al = search for null
MOV CX, 128 ; very max to search
CLD
REPNE SCASB ; find end of arg
LEA SI, [DI-1] ; si -> nul
MOV CX, 0 ; cx = # chars to move
CMP SI, BX ; Q. any file name
JE ZCFLSET80 ; A. no .. error
ZCFLSET30: DEC SI ; si -> prev char
CMP BYTE PTR [SI], '\' ; Q. dir?
JE ZCFLSET35 ; A. yes .. end of file name.
INC CX ; cx = char count
CMP SI, BX ; Q. done?
JE ZCFLSET37 ; A. yes .. move file name
JMP ZCFLSET30 ; .. continue
ZCFLSET35: INC SI ; si -> start of file name
ZCFLSET37: OR CX, CX ; Q. file name spec'd?
JZ ZCFLSET80 ; A. no .. error
CMP CX, 12 ; Q. too long?
JA ZCFLSET85 ; A. yes .. error
PUSH SI ; save start pointer
MOV DI, OFFSET FILENAME ; di -> file name
REP MOVSB ; .. move in the file name
POP SI ; restore start pointer
POP DI ; .. and dir pointer
CMP SI, BX ; Q. at start of parm?
JE ZCFLSET90 ; A. yes .. return
INC BX ; bx -> next char
CMP SI, BX ; Q. root only given?
JE ZCFLSET40 ; A. yes .. continue
DEC SI ; si -> last \
ZCFLSET40: MOV BYTE PTR [SI], 0 ; make dir ASCIIZ
ZCFLSET50: MOV DX, DI ; dx -> directory
MOV AH, 3BH ; ah = CHDIR opcode
INT 21H ; .. change directory
JNC ZCFLSET90 ; if ok .. continue
MOV DX, OFFSET BADDIR ; dx -> baddir request
CALL ZCDIE ; .. die now
ZCFLSET80: MOV DX, OFFSET FILERR ; dx -> no file specified
CALL ZCDIE
ZCFLSET85: MOV DX, OFFSET INVFIL ; dx -> invalid filename spec'd
CALL ZCDIE
ZCFLSET90: RET ; return to caller
ZCFLSET ENDP
; ---------------------------------------------------------------------
; This routine waits for n nbr of timer ticks to transpire.
; Entry: ax = nbr of timer ticks to wait
; ---------------------------------------------------------------------
ZCWAIT PROC NEAR
ADD AX, WAIT_COUNT ; ax = count to wait till
ZCWAIT10: CMP WAIT_COUNT, AX ; Q. enough time elapsed?
JNA ZCWAIT10 ; A. no .. loop
CALL ZCTIMUP ; .. update system timer
RET ; finally, return to caller
ZCWAIT ENDP
; ---------------------------------------------------------------------
; This routine retrieves the most recent LSR value.
; Exit: carry set if new value is found.; al = last LSR value detected.
; ---------------------------------------------------------------------
ZCLSRGET PROC NEAR
CLI ; no interrupts
MOV AL, LSR_VAL ; al = last known LSR value
OR LSR_NEW, 0 ; check if value is new
MOV LSR_NEW, 0 ; .. reset it
STI ; .. allow interrupts
JNZ ZCLSRGET90 ; .. jump if new value
CLC ; show no new value
RET ; .. and return to caller
ZCLSRGET90: STC ; show new value
RET ; .. and return to caller
ZCLSRGET ENDP
; ---------------------------------------------------------------------
; This routine sends a break .2 seconds long.
; ---------------------------------------------------------------------
ZCBREAK PROC NEAR
PUSH AX ; save caller regs
PUSH BX
PUSH DX
MOV DX, IO_BASE ; dx -> comm base register
ADD DX, 3 ; dx = line control reg addr
IN AL, DX ; al = LCR contents
MOV BL, AL ; bl = LCR
OR AL, 40H ; .. turn on break bit
OUT DX, AL ; .. send a break
MOV AX, 4 ; wait 4 ticks (~ .2 secs)
CALL ZCWAIT ; .. wait ...
AND AL,NOT 40H ; assure no break bit
MOV AL,BL ; al = old LSR contents
OUT DX, AL ; end the break
POP DX ; restore registers
POP BX
POP AX
RET ; return to caller
ZCBREAK ENDP
; ---------------------------------------------------------------------
; This routine clears the incomming buffer by resetting the buffer pointers.
; ---------------------------------------------------------------------
ZCCLRCOM PROC NEAR
PUSH RBUF_RPTR ; push the receive pointer
POP RBUF_GPTR ; .. and pop get pointer
RET ; .. and return to caller
ZCCLRCOM ENDP
; ---------------------------------------------------------------------
; This routine tests if a break was recently detected.
; Exit: returns NZ if break found, zero if not.
; ---------------------------------------------------------------------
ZCTSTBRK PROC NEAR
PUSH AX ; save caller registers
CALL ZCLSRGET ; get LSR value
JC ZCTSTBRK80 ; .. test value if found
SUB AH, AH ; assure zero flag set
JMP SHORT ZCTSTBRK90 ; .. return to caller
ZCTSTBRK80: TEST AL, LSR_BRK ; Q. BREAK occur?
ZCTSTBRK90: POP AX ; restore ax
RET ; return to caller
ZCTSTBRK ENDP
; ---------------------------------------------------------------------
; This routine will setup the baud rate for the com port.
; Entry: ax = baud rate index
; 0=115.2kb, 1=57.6kb, 2=38.4kb, 3=19.2kb, 4=9600, 5=4800
; 6=2400, 7=1200
; ---------------------------------------------------------------------
ZCBAUD PROC NEAR
PUSH AX ; save registers
PUSH BX
PUSH DX
PUSH AX ; save ax
MOV DX, OFFSET TRYING ; dx -> baud message
MOV AH, 9 ; ah = print "$" message
INT 21H ; .. tell 'em what we're doing
POP AX ; restore baud request
MOV BX, AX ; bx = baud index
MOV CL, 3 ; .. shift for * 8
SHL BX, CL ; bx = baud index * 8
SUB BX, AX ; .. make that * 7
LEA DX, BAUD_TABLE+1[BX] ; dx -> $ message
MOV BL, BAUD_TABLE[BX] ; bl = divisor
XOR BH, BH ; .. upper byte off
MOV AH, 9H ; ah = print '$' message
INT 21H ; .. display baud rate
TEST FLG1, FLG1B ; Q. ctl-break?
JZ ZCBAUD10 ; A. no .. continue
MOV DX, OFFSET SHUTDOWN_R1 ; dx -> shutdown msg
CALL ZCDIE ; .. end it all
ZCBAUD10: CMP BYTE PTR FLGPCR, 0 ; Q. pcremote active?
JNZ ZCBAUD20 ; A. yes.. don't change baud
MOV DX, IO_BASE ; dx = io port base addr
ADD DX, 3 ; dx = line control register
IN AL, DX ; al = lcr
OR AL, LCR_DLAB ; al = divisor latch enable
CLI ; stop interrupts, then ..
OUT DX, AL ; enable the setting of the dlab
SUB DX, 3 ; dx = LSB port of divisor latch
MOV AL, BL ; al = LSB of new divisor
OUT DX, AL ; output the LSB portion
INC DX ; dx = MSB port of divisor latch
MOV AL, BH ; al = MSB of new divisor
OUT DX, AL ; output the MSB portion
ADD DX, 2 ; dx = line control register
IN AL, DX ; al = lcr
AND AL, NOT LCR_DLAB ; .. set off dlab
OUT DX, AL ; .. restore line control register
STI ; .. and re-enable interrupts
ZCBAUD20: POP DX ; restore caller's registers
POP BX
POP AX
RET ; ..and return to caller
ZCBAUD ENDP
; ---------------------------------------------------------------------
; This routine tests for the highest possible baud rate.
; ---------------------------------------------------------------------
ZCSPEED PROC NEAR
PUSH AX ; save register
CMP BYTE PTR FLGPCR, 0 ; Q. PCREMOTE active
JZ ZCSPEED05 ; A. no
MOV AL, BAUD_CNTR ; al = baud rate counter
CBW ; ax = baud rate counter
CALL ZCBAUD ; .. setup baud rate
JMP ZCSPEED90 ; A. yes, assume bauds match
ZCSPEED05: CMP BAUD_CNTR, 8 ; Comm attempts done ?
JB ZCSPEED10 ; A. no .. try again
MOV DX, OFFSET SPDERROR ; dx -> Comm not possible
CALL ZCDIE ; die now
ZCSPEED10: MOV AL, BAUD_CNTR ; al = baud rate counter
CBW ; ax = baud rate counter
CALL ZCBAUD ; .. setup baud rate
MOV AX, 2 ; wait .1 sec
CALL ZCWAIT ; .. for all to calm down
MOV WAIT_COUNT, 0 ; .. and wait counter
CALL ZCCLRCOM ; .. clear out receive buffer
ZCSPEED11: MOV AL, STX ; al = send stx
CALL ZCPUTC ; .. send char
MOV AX, 1 ; wait 1 tick
CALL ZCWAIT ; .. wait
CALL ZCGETC ; Q. char available?
JC ZCSPEED15 ; A. no .. try again
CMP AL, STX ; Q. stx?
JE ZCSPEED17 ; A. yes .. continue
ZCSPEED15: TEST FLG1, FLG1B ; Q. ctl-break?
JNZ ZCSPEED16 ; A. yes .. end it now
TEST FLG, FLGW ; Q. wait forever?
JNZ ZCSPEED11 ; A. yes .. do so.
MOV AX, DSRWAIT ; ax = current wait count
CMP WAIT_COUNT, AX ; Q. time expire?
JNA ZCSPEED11 ; A. no.. try again
MOV DX, OFFSET NOTUP ; dx -> error message
CALL ZCDIE ; .. die gracefully
ZCSPEED16: MOV DX, OFFSET SHUTDOWN_R1 ; dx -> ZCOPY done msg
CALL ZCDIE ; .. end gracefully
ZCSPEED17: CALL ZCCLRCOM ; clear receive buffer
CALL ZCLSRGET ; assure old lsr killed
MOV DSRWAIT, SEC_3 ; reset dsrwait
TEST FLG,FLGR ; Q. are we the receiver?
JNZ ZCSPEED50 ; A. yes .. sync as such
; SENDING NODE
CALL ZCSPDA ; Q. first part ok?
JC ZCSPEED80 ; A. no .. try next baud
CALL ZCSPDB ; Q. second part ok?
JC ZCSPEED80 ; A. no .. try next baud
JMP SHORT ZCSPEED90 ; else.. exit ok
; RECEIVING NODE
ZCSPEED50: CALL ZCSPDB ; Q. answer to first part ok?
JC ZCSPEED80 ; A. no .. try next baud
CALL ZCSPDA ; Q. answer to second ok?
JNC ZCSPEED90 ; A. no .. try next baud
ZCSPEED80: INC BAUD_CNTR ; next baud rate
CMP BYTE PTR FLGPCR, 0 ; Q. PCREMOTE active
JZ ZCSPEED85 ; A. no .. try next baud
DEC BAUD_CNTR ; A. yes.. don't change baud
ZCSPEED85: JMP ZCSPEED05 ; .. try re-sync
ZCSPEED90: CALL ZCCLRCOM ; assure all bytes cleared
MOV DX, OFFSET SPDSET ; dx -> ok message
MOV AH, 9 ; ah = print to "$"
INT 21H ; display message
POP AX ; restore caller's regs
RET ; .. and return to caller
ZCSPEED ENDP
; ---------------------------------------------------------------------
; This routine is one side of the set baud rate routine -- sender.
; Exit: Carry set if unsuccessful.
; ---------------------------------------------------------------------
ZCSPDA PROC NEAR
MOV DX, WAIT_COUNT ; dx = current wait count
ADD DX, 6 ; dx = future wait count
ZCSPDA12: MOV AL, SYNC_BYTE ; al = start signature byte
CALL ZCPUTC ; .. put it out
MOV AX, 1 ; ax = wait 1 tick
CALL ZCWAIT ; .. wait 1 tick
CALL ZCGETC ; Q. char available?
JC ZCSPDA17 ; A. no .. continue
CMP AL, STX ; Q. stx?
JNE ZCSPDA15 ; A. no .. continue
CALL ZCPUTC ; .. send STX back
JMP ZCSPDA12 ; .. and do it again
ZCSPDA15: CMP AL, ACK ; Q. ack?
JE ZCSPDA20 ; A. yes .. send sync string
ZCSPDA17: CMP DX, WAIT_COUNT ; Q. time up?
JA ZCSPDA12 ; A. no .. try again
JMP SHORT ZCSPDA80 ; return unsuccessful
; SYNC BYTE RECEIVED .. SEND STRING
ZCSPDA20: MOV AL, SYNC_END ; al = end of sync sequence
CALL ZCPUTC ; .. write it
MOV CX, SYNC_LEN ; Length of sync string
XOR AL, AL ; al = sync char
ZCSPDA25: CALL ZCPUTC ; put out sync string char
ADD AL, SYNC_INC ; .. calc next char
LOOP ZCSPDA25 ; .. continue until done
MOV AX, 9 ; ax = .5 sec
CALL ZCWAIT ; .. wait .5 secs
CALL ZCTSTBRK ; Q. did break occur?
JNZ ZCSPDA90 ; A. yes .. return successful
ZCSPDA80: STC ; return unsuccessful
RET ; .. return to caller
ZCSPDA90: CLC ; return successful
RET ; .. return to caller
ZCSPDA ENDP
; ---------------------------------------------------------------------
; This routine is one side of the set baud rate routine -- receiver.
; Exit: Carry set if unsuccessful.
; ---------------------------------------------------------------------
ZCSPDB PROC NEAR
MOV WAIT_COUNT, 0 ; set wait counter to 0
ZCSPDB10: CALL ZCGETC ; Q. char available?
JNC ZCSPDB20 ; A. yes .. check it.
CMP WAIT_COUNT, 19 ; Q. 1 second?
JB ZCSPDB10 ; A. no .. keep trying.
JMP SHORT ZCSPDB80 ; else .. return unsuccessful
ZCSPDB20: CMP AL, SYNC_BYTE ; Q. sync byte received?
JNE ZCSPDB25 ; A. yes .. answer it.
MOV AL, ACK ; al = ack
CALL ZCPUTC ; .. tell 'em wt got it.
JMP ZCSPDB10 ; .. try for sync_end
ZCSPDB25: CMP AL, SYNC_END ; Q. end of sync bytes?
JE ZCSPDB30 ; A. yes .. expect sync string.
CMP AL, STX ; Q. still stxing?
JNE ZCSPDB10 ; A. no .. continue
CALL ZCPUTC ; else .. tell 'em we got it
JMP ZCSPDB10 ; .. and try again
ZCSPDB30: CALL ZCSPDCHK ; Q. block receive ok?
JC ZCSPDB80 ; A. no .. return unsuccessful
CALL ZCBREAK ; else .. tell 'em we're talking
JMP SHORT ZCSPDB90 ; .. and return to caller
ZCSPDB80: MOV AX, SEC_1 ; wait 1 second ...
CALL ZCWAIT ; .. wait
STC ; return unsuccessful
RET ; .. return to caller
ZCSPDB90: CLC ; return successful
RET ; .. return to caller
ZCSPDB ENDP
; ---------------------------------------------------------------------
; This routine calculates a CRC for a block of characters.
; Entry: si -> character block; cx = # characters to include in calc
; Exit: ax = CRC
; ---------------------------------------------------------------------
ZCCRC PROC NEAR
PUSH SI ; save caller regs
PUSH BX
PUSH CX
XOR AX, AX ; ax = start value (0)
ADD CX, 2 ; do 2 "additional" bytes
ZCCRC05: PUSH CX ; save cx
MOV BL, BYTE PTR [SI] ; bl = next byte
INC SI ; si -> next character
CMP CX, 2 ; Q. more than 2 chars left?
JA ZCCRC08 ; A. yes .. continue
MOV BL, 0FFH ; .. set to 0ffh
ZCCRC08: MOV CX, 8 ; 8 bits ..
ZCCRC10: XOR BH, BH ; clear bh
SHL BX, 1 ; shift the next char
SHL AX, 1 ; Q. high bit on?
JNC ZCCRC20 ; A. no .. do not xor CRC value
OR AL, BH ; .. include the next bit
XOR AX, CRC_VAL ; .. xor the CRC value
LOOP ZCCRC10 ; loop 'til done
JMP SHORT ZCCRC30 ; .. continue when done
ZCCRC20: OR AL, BH ; include the next bit
LOOP ZCCRC10 ; loop 'til done
ZCCRC30: POP CX ; restore char count
LOOP ZCCRC05 ; .. continue until done
POP CX ; restore caller's regs
POP BX
POP SI
RET
ZCCRC ENDP
; ---------------------------------------------------------------------
; This routine builds a block and sends it to the other machine.
; Block Format: STX crc(2) len(2) blk#(2) cmd(1) data(n) ETX
; where: STX=02h, crc=16 bit error check value, len=length of block (i.e.
; data length+3), blk#=number of this block, 0 thru 65535, wrapping
; cmd=command/identifier for this block, data=send characters, ETX=03h
; Entry: al=command; si->chars to send; cx=# chars to include in calc
; Exit: Returns when transmission complete.
; ---------------------------------------------------------------------
ZCBLKSND PROC NEAR
PUSH AX ; save caller's regs
PUSH BX
PUSH DX
PUSH SI
PUSH DI
PUSH CX
MOV DI, SBUF ; di -> send buffer
TEST FLG1, FLG1B ; Q. control-break detected?
JZ ZCBLKSND05 ; A. no .. continue
MOV AL, DIENOW ; al = die now command
OR FLG1, FLG1S ; .. show shutdown sent
ZCBLKSND05: PUSH AX
CLD ; we want to increment
MOV AL, STX ; al = stx value
STOSB ; .. save in send buffer
ADD DI, 2 ; di -> past CRC bytes
MOV AX, CX ; ax = characters string len
ADD AX, 3 ; ax = chars + cmd + blk# len
STOSW ; .. save the length
MOV AX, SEND_BLKNO ; ax = next send block number
STOSW ; save send block number
POP AX ; restore the command
STOSB ; save the command
JCXZ ZCBLKSND10 ; jump if no bytes to move
REP MOVSB ; .. move in the chars
ZCBLKSND10: MOV AL, ETX ; al = etx value
STOSB ; .. save at end of buffer
MOV BX, SBUF ; bx -> buffer
MOV CX, [BX+MLEN] ; cx = blk#+cmd+data len
LEA SI, [BX+MBLKNO] ; si -> blk#/cmd/data area
CALL ZCCRC ; calculate the crc
MOV [BX+MCRC], AX ; .. save in the buffer
MOV DL, RETRIES ; dl = max retries
ZCBLKSND20: MOV SI, BX ; si -> buffer
MOV CX, [BX+MLEN] ; cx = blk#/cmd/data length
ADD CX, MOHEAD ; characters to send
ZCBLKSND25: LODSB ; al = char to send
CALL ZCPUTC ; .. send it
LOOP ZCBLKSND25 ; .. loop until all sent
MOV BX, WAIT_COUNT ; bx = now
ADD BX, SEC_10 ; bx = later, 10 seconds
ZCBLKSND35: CALL ZCWAITC ; .. and wait for a character
JC ZCBLKSND60 ; .. timeout .. see if any resp
CMP AL, ACK ; Q. send ok?
JE ZCBLKSND80 ; A. yes .. continue
CMP AL, NAK ; Q. send bad?
JE ZCBLKSND75 ; A. yes .. restart send
CMP AL, RLR ; Q. request last response
JE ZCBLKSND50 ; A. yes .. continue
JMP SHORT ZCBLKSND70 ; .. clear buffer, retry
ZCBLKSND50: CALL ZCGETC ; kill the rlr
MOV AL, LAST_RESP ; al = last response sent
CALL ZCPUTC ; .. tell the other machine
MOV BX, SBUF ; bx -> buffer
JMP ZCBLKSND20 ; .. and resend our block
ZCBLKSND60: CMP WAIT_COUNT, BX ; Q. 10 seconds yet
JB ZCBLKSND65 ; A. no .. continue
MOV DX, OFFSET NOTUP ; dx -> error message
CALL ZCDIE ; .. and die now
ZCBLKSND65: MOV AL, RLR ; al = get last response
CALL ZCPUTC ; .. request last response
INC ERRORS ; .. increment the error count
JMP ZCBLKSND35 ; .. and ask other machine
ZCBLKSND70: CALL ZCGETC ; get a char
CALL ZCWAITC ; .. wait for another to arrive
JNC ZCBLKSND70 ; .. if another does, get it
JMP ZCBLKSND65 ; .. get last response now.
ZCBLKSND75: CALL ZCGETC ; .. kill the nak
INC ERRORS ; increment error count
MOV BX, SBUF ; bx -> buffer
JMP ZCBLKSND20 ; .. retry
ZCBLKSND80: CALL ZCGETC ; kill the character
INC SEND_BLKNO ; next send block number
TEST FLG1, FLG1S ; Q. shutdown sent?
JZ ZCBLKSND90 ; A. no .. continue
MOV DX, OFFSET SHUTDOWN_R1 ; dx -> shutdown request
CALL ZCDIE ; .. and end it all
ZCBLKSND90: POP CX ; restore length
POP DI
POP SI
POP DX
POP BX
POP AX
RET
ZCBLKSND ENDP
; ---------------------------------------------------------------------
; This routine waits for a character, .5 secs.
; Exit: carry=TIMEOUT; no carry=char received; al = character
; ---------------------------------------------------------------------
ZCWAITC PROC NEAR
PUSH BX
MOV BX, WAIT_COUNT ; bx = now ..
ZCPCR10: ADD BX, 13 ; bx = later (.5 secs) ..
ZCWAITC10: CALL ZCCLA ; Q. char available?
JNC ZCWAITC90 ; A. yes .. return
CMP WAIT_COUNT, BX ; Q. .5 secs?
JB ZCWAITC10 ; A. no .. continue
STC ; show timeout
JMP SHORT ZCWAITC90 ; .. return to caller
ZCWAITC90: POP BX ; .. return to caller
RET ; .. and return to caller
ZCWAITC ENDP
; ---------------------------------------------------------------------
; This routine receives a block, checks CRC, ACKs its reception and places
; the data in wbuf. STX of block should have already been read and discarded
; The block format is documented in ZCBLKSND.
; Exit: Carry - block not available (timeout or bad crc).
; No Carry - block received ok, in wbuf, starting w/CRC; al = command byte
; ---------------------------------------------------------------------
ZCBLKRCV PROC NEAR
PUSH BX ; save regs
PUSH CX
PUSH DX
PUSH DI
PUSH SI
MOV BX, WAIT_COUNT ; bx = current timer
ZCPCR20: ADD BX, 5 ; bx = max time to wait until
MOV CX, 0 ; zero out char counter
MOV DI, WBUF ; di -> wbuf
ADD DI, MCRC ; di -> work buffer crc field
MOV DX, -1 ; .. dummy # chars needed
ZCBLKRCV10: CALL ZCGETC ; Q. char available?
JC ZCBLKRCV30 ; A. no .. error
MOV BX, WAIT_COUNT ; bx = current timer
ZCPCR30: ADD BX, 5 ; .. next time to wait until
STOSB ; put in wbuf
INC CX ; cx = # chars
CMP CX, 4 ; Q. len in yet?
JNE ZCBLKRCV20 ; A. no .. continue
MOV DX, [DI-2] ; dx = message len
ADD DX, 5 ; dx = # character needed
ZCBLKRCV20: CMP CX, DX ; Q. enough chars received?
JE ZCBLKRCV50 ; A. yes .. check 'em out.
JMP SHORT ZCBLKRCV10 ; else .. get another
ZCBLKRCV30: CMP WAIT_COUNT, BX ; Q. timeout?
JA ZCBLKRCV70 ; A. yes .. NAK
JMP SHORT ZCBLKRCV10 ; .. try again
ZCBLKRCV50: MOV SI, WBUF ; si -> wbuf
MOV CX, [SI+MLEN] ; dx = length
PUSH SI ; save wbuf pointer
LEA SI, [SI+MBLKNO] ; si -> blk#
CALL ZCCRC ; .. calc crc
POP SI ; si -> wbuf
CMP AX, [SI+MCRC] ; Q. crc same?
JE ZCBLKRCV55 ; A. yes .. ok
JMP SHORT ZCBLKRCV70 ; .. else .. NAK
ZCBLKRCV55: MOV AX, RCV_BLKNO ; ax = expected block
CMP AX, [SI+MBLKNO] ; Q. same block?
JE ZCBLKRCV80 ; A. yes .. continue
CALL ZCCLRCOM ; else .. clear com buffer
MOV AL, ACK ; al = ack
MOV LAST_RESP, AL ; .. save as last resp
CALL ZCPUTC ; .. ack last block
STC ; show no receive
JMP SHORT ZCBLKRCV90 ; .. return to caller
ZCBLKRCV70: MOV AL, RLR ; al = NAK
MOV LAST_RESP, AL ; .. save as last resp
CALL ZCPUTC ; .. tell remote .. no go
CALL ZCCLRCOM ; .. clear our recv buffer
INC ERRORS ; increment error count
STC ; show error condition
JMP SHORT ZCBLKRCV90 ; .. and return to caller
ZCBLKRCV80: MOV AL, ACK ; al = ACK
MOV LAST_RESP, AL ; .. save as last resp
CALL ZCPUTC ; .. tell remote .. all is go
INC RCV_BLKNO ; next block number
MOV AL, [SI+MCMD] ; al = received command
CMP AL, DIENOW ; Q. die now?
JNE ZCBLKRCV85 ; A. no .. continue
MOV DX, OFFSET SHUTDOWN_R1 ; dx -> shutdown msg
CALL ZCDIE ; .. end it all now
ZCBLKRCV85: CLC ; show received ok
ZCBLKRCV90: POP SI ; restore regs
POP DI ; save regs
POP DX
POP CX
POP BX
RET
ZCBLKRCV ENDP
; ---------------------------------------------------------------------
; Determine if chars are available. If so, attempt to receive a block.
; Exit: CY=block not available; NC=block received ok, in wbuf, starting w/CRC.
; al = command byte
; ---------------------------------------------------------------------
ZCTRYRCV PROC NEAR
CALL ZCGETC ; Q. any chars available?
JC ZCTRYRCV90 ; A. no .. exit
CMP AL, STX ; Q. stx received?
JNE ZCTRYRCV60 ; A. no .. exit
CALL ZCBLKRCV ; receive a block
JMP SHORT ZCTRYRCV90 ; tell 'em how it went
ZCTRYRCV60: CMP AL, RLR ; Q. request of last resp?
JNE ZCTRYRCV70 ; A. no .. show no block
MOV AL, NAK ; al = resend last block
CALL ZCPUTC ; .. send the response
ZCTRYRCV70: STC ; show no block
ZCTRYRCV90: RET ; .. and exit
ZCTRYRCV ENDP
; ---------------------------------------------------------------------
; This routine subtracts the IO_LEN from the bytes in the current file, and
; prints the number of blocks left to transfer on each 10h blocks transferred
; ---------------------------------------------------------------------
ZCPRTLFT PROC NEAR
PUSH AX ; save regs
PUSH CX
CMP WORD PTR BYTESLFT+2, 0 ; Q. < 64k bytes to go?
JA ZCPRTLFT10 ; A. no .. continue
CMP WORD PTR BYTESLFT, IO_LEN ; Q. io_len left?
JA ZCPRTLFT10 ; A. yes .. continue
MOV WORD PTR BYTESLFT, 0 ; zero out bytes left
JMP SHORT ZCPRTLFT80 ; ... and print!
ZCPRTLFT10: SUB WORD PTR BYTESLFT, IO_LEN ; subtract transferred
SBB WORD PTR BYTESLFT+2, 0 ; .. from left to xfer
MOV AX, WORD PTR BYTESLFT ; get # bytes left (lws)
AND AX, 1E00H ; Q. 16 block boundary?
JNZ ZCPRTLFT90 ; A. no .. skip print
ZCPRTLFT80: CALL ZCPRBLKS ; .. print # blocks left
ZCPRTLFT90: POP CX ; restore regs
POP AX
RET ; .. return to caller
ZCPRTLFT ENDP
; ---------------------------------------------------------------------
; This routine calculates and prints the number of blocks left.
; ---------------------------------------------------------------------
ZCPRBLKS PROC NEAR
PUSH AX ; restore es
PUSH BX
PUSH CX
PUSH DX
PUSH DI
PUSH ES ; save es
LES BX, BYTESLFT ; bx = bytes left
MOV DX, ES ; dx = high order
POP ES ; .. restore es
CLC ; clear the carry bit
RCR DX, 1 ; move lsb of dx to cf
RCR BX, 1 ; .. continue in bx
MOV BL, BH ; bl = low order
MOV BH, DL ; bh = middle
MOV DL, DH ; dl = hight
XOR DH, DH ; .. high is zero
MOV DI, OFFSET B_LEFT ; di -> blocks left
STD ; .. and count down
MOV CX, 6 ; .. max bytes to do
ZCPRBLKS20: PUSH CX ; save counter
MOV AL, BL ; al = digit
AND AL, 0FH ; .. upper bits off
OR AL, 30H ; change to printable
CMP AL, '9' ; Q. above '9'?
JNA ZCPRBLKS25 ; A. no .. continue
ADD AL, 7 ; .. convert to prtable
ZCPRBLKS25: STOSB ; save the char
MOV CL, 4 ; cl = shift value
ZCPRBLKS27: CLC ; clear the carry bit
RCR DX, 1 ; rotate dx:bs ..
RCR BX, 1 ; .. by as many bits as needed
LOOP ZCPRBLKS27 ; .. continue
POP CX ; .. restore count
OR BX, BX ; Q. all done?
JNZ ZCPRBLKS30 ; A. no .. continue
OR DX, DX ; Q. all done?
JZ ZCPRBLKS40 ; A. yes .. print it
ZCPRBLKS30: LOOP ZCPRBLKS20 ; .. xlat next char
ZCPRBLKS40: LEA DX, [DI+1] ; dx -> message to print
MOV AH, 9 ; .. ah = print ascii$
INT 21H ; .. ask DOS to do it
CLD ; .. return direction to up
POP DI ; restore registers
POP DX
POP CX
POP BX
POP AX
RET
ZCPRBLKS ENDP
; ---------------------------------------------------------------------
; Determine if speed sync string received ok.
; Entry: Receive buffer should have sync string.
; Exit: Carry bit set indicates sync error.
; ---------------------------------------------------------------------
ZCSPDCHK PROC NEAR
CALL ZCLSRGET ; Q. did lsr change?
JNC ZCSPDCHK10 ; A. no .. check received string
AND AL, LSR_ERR ; Q. any error?
JNZ ZCSPDCHK90 ; A. yes .. return.
ZCSPDCHK10: MOV CX, SYNC_LEN ; len of speed set
MOV BL, 0 ; start of speed string
ZCSPDCHK20: MOV AX, WAIT_COUNT ; ax = wait counter
ADD AX, 2 ; .. wait 2 ticks, max
ZCSPDCHK25: CALL ZCGETC ; Q. any char?
JNC ZCSPDCHK30 ; A. yes ... check it
CMP WAIT_COUNT, AX ; Q. count up?
JB ZCSPDCHK25 ; A. no .. check again.
JMP SHORT ZCSPDCHK90 ; .. else .. error
ZCSPDCHK30: CMP AL, BL ; Q. same character?
JNE ZCSPDCHK90 ; A. no .. error
ADD BL, SYNC_INC ; bl = next char
LOOP ZCSPDCHK20 ; .. check next char
CLC ; show sync ok
RET ; .. return to caller
ZCSPDCHK90: STC ; show no sync
RET ; .. return to caller
ZCSPDCHK ENDP
; ---------------------------------------------------------------------
; This routine causes a prompt to be placed on both machines.
; The response may be given from either machine.
; Entry: di -> prompt message, ended in $
; Exit: al = response
; ---------------------------------------------------------------------
ZCSPROMPT PROC NEAR
PUSH BX ; save registers
PUSH CX
PUSH DX
PUSH SI
PUSH DI
CLD ; clear direction
PUSH DI ; save initial pointer
MOV AL, '$' ; Look for $ character
MOV CX, 100 ; .. max 100 chars
REPNE SCASB ; .. find the value
MOV CX, DI ; cx -> char after '$'
POP SI ; si -> start of string
SUB CX, SI ; cx = length of string
MOV AL, OPR_PROMPT ; al = command (prompt)
CALL ZCBLKSND ; Q. send ok?
MOV DX, SI ; bx -> start of string
CALL ZCPRESP ; prompt & get response
POP DI ; restore regs
POP SI
POP DX
POP CX
POP BX
RET
ZCSPROMPT ENDP
; ---------------------------------------------------------------------
; This routine displays a prompt and waits for a response.
; The response may be given from either machine.
; Entry: dx -> prompt message, ended in $
; Exit: al = response; Carry=response came from remote machine
; no carry - response came from local machine
; ---------------------------------------------------------------------
ZCPRESP PROC NEAR
PUSH SI ; save regs
PUSH BX
PUSH CX
MOV AH, 09H ; al = print string
INT 21H ; .. display prompt
MOV BX, WBUF ; bx -> wbuf
ZCPRESP10: CALL ZCTIMUP ; update timer
MOV AH, 1 ; ah = query keyboard
INT 16H ; Q. is a key available?
JZ ZCPRESP20 ; A. no .. check for block
MOV AH, 0 ; al = get key
INT 16H ; al = key typed
PUSH AX ; save ax
MOV [BX], AL ; save response in wbuf
MOV AL, OPR_REPLY ; al = command
MOV SI, WBUF ; si -> wbuf
MOV CX, 1 ; cx = # chars to send
CALL ZCBLKSND ; send the block
POP AX ; restore reply
CLC ; response from local
JMP SHORT ZCPRESP90 ; .. return to caller
ZCPRESP20: CALL ZCTRYRCV ; Q. block available?
JC ZCPRESP10 ; A. no .. try again
CMP BYTE PTR [BX+MCMD], OPR_REPLY ; Q. reply?
JNE ZCPRESP10 ; A. no .. try again
MOV AL, BYTE PTR [BX+MDATA] ; al = response
STC ; response from remote
ZCPRESP90: POP CX ; restore regs
POP BX
POP SI
RET ; return to caller
ZCPRESP ENDP
; ---------------------------------------------------------------------
; This routine displays the prompt sent from the other machine.
; Entry: wbuf contains received prompt
; ---------------------------------------------------------------------
ZCPPROMPT PROC NEAR
PUSH AX ; save ax
MOV DX, WBUF ; dx -> received buffer
ADD DX, MDATA ; dx -> prompt
CALL ZCPRESP ; get response
POP AX ; restore ax
RET ; return to caller
ZCPPROMPT ENDP
; ---------------------------------------------------------------------
; This routine sends the requested file.
; Entry: handle = currently opened file.
; ---------------------------------------------------------------------
ZCSEND PROC NEAR
PUSH AX ; save regs
PUSH BX
PUSH CX
PUSH DX
PUSH SI
MOV AL, CRE_FILE ; al = file header cmd
MOV CX, DTA_LEN ; cx = find file data
MOV SI, DTA ; si -> dta
CALL ZCBLKSND ; send the request
CALL ZCRECV ; get the response
CMP AL, MSG_NAK ; Q. create ok?
JNE ZCSEND10 ; A. yes .. continue
MOV DX, OFFSET FILENOPEN ; dx -> error message
MOV AH, 9 ; ah = print ascii$
INT 21H ; .. tell 'em, Jim
JMP SHORT ZCSEND90 ; try next file
ZCSEND10: MOV CX, XBUF_LTS ; cx = bytes left to send
OR CX, CX ; Q. any?
JNZ ZCSEND20 ; A. yes .. send them
MOV AH, 3FH ; ah = read from file
MOV BX, HANDLE ; .. bx = file handle
MOV CX, XBUF_RBL ; .. cx = # of bytes
MOV DX, XBUF ; .. dx -> buffer
MOV XBUF_PTR, DX ; .. save in send pointer
INT 21H ; .. read a buffer full
JC ZCSEND80 ; .. process errors
OR AX, AX ; Q. anything read?
JZ ZCSEND70 ; A. no .. eof
MOV CX, AX ; cx = number of bytes
MOV XBUF_LTS, AX ; .. left to send
ZCSEND20: CMP CX, IO_LEN ; Q. more than io_len?
JNA ZCSEND25 ; A. no .. send it
MOV CX, IO_LEN ; cx = bytes to send
ZCSEND25: SUB XBUF_LTS, CX ; adjust pointer
MOV SI, XBUF_PTR ; .. si -> data
ADD XBUF_PTR, CX ; .. adjust pointer
MOV AL, DATA_BLK ; .. al = data block cmd
MOV ERRORS, 0 ; .. zero out errors
CALL ZCBLKSND ; .. send a block
CALL ZCRECV ; wait & execute reply
CALL ZCPRTLFT ; .. print blocks left
CMP ERRORS, MAX_ERRORS ; Q. too many errors
JB ZCSEND10 ; A. no ..continue
MOV AL, RESYNC ; al = resync
MOV CX, 0 ; cx = no data to send
CALL ZCBLKSND ; .. send the block
CALL RESYNC_P ; resync on too many block errs
JMP ZCSEND10 ; .. and continue
ZCSEND70: MOV AL, EOF_MARK ; al = eof command
XOR CX, CX ; .. cx = no data
CALL ZCBLKSND ; .. tell other side
CALL ZCRECV ; wait for reply
JMP SHORT ZCSEND90 ; .. return to caller
ZCSEND80: MOV AL, SHUTDOWN ; al = shutdown command
XOR CX, CX ; .. cx = no data
CALL ZCBLKSND ; .. tell other side
ZCSEND90: POP SI ; restore registers
POP DX
POP CX
POP BX
POP AX
RET
ZCSEND ENDP
; ---------------------------------------------------------------------
; Receive blocks and process them based on request from the other machine.
; ---------------------------------------------------------------------
ZCRECV PROC NEAR
MOV BX, WAIT_COUNT ; bx = current wait count
ADD BX, SEC_10 ; bx = ten secs from now
ZCRECV05: CALL ZCTIMUP ; update the timer
CMP WAIT_COUNT, BX ; Q. 10 seconds yet?
JB ZCRECV07 ; A. no .. continue
MOV DX, OFFSET NOTUP ; dx -> error message
CALL ZCDIE ; .. I'm dead, Jim
ZCRECV07: CALL ZCTRYRCV ; Q. anything waiting?
JC ZCRECV05 ; A. no.. try again
CBW ; ax = command
SHL AL, 1 ; ax = entry offset
LEA BX, MSG_P_TBL-2 ; bx -> message table
ADD BX, AX ; bx -> run pointer
CALL [BX] ; .. call requested routine
ZCRECV90: RET ; return to caller
ZCRECV ENDP
; ----------------------------------------
; create the requested file
; ----------------------------------------
CRE_FILE_P PROC NEAR ; create file
PUSH AX ; save regs
PUSH BX
PUSH CX
PUSH SI
PUSH DI
MOV WAIT_COUNT, 0 ; clear the wait counter
MOV SI, WBUF ; si -> received data
MOV AX, [SI+MDATA+28] ; ax = file size high
MOV WORD PTR BYTESLFT+2, AX ; .. save high value
MOV AX, [SI+MDATA+26] ; ax = file size low
MOV WORD PTR BYTESLFT, AX ; .. save low value
ADD SI, MDATA+30 ; si -> file name
MOV DI, OFFSET FILENAME ; di -> file name area
MOV CX, 13 ; .. length to move
REP MOVSB ; move in the file name
MOV DX, OFFSET CURDIR ; dx -> file name to open
XOR CX, CX ; cx = attributes
MOV AH, 3CH ; ah = create file
INT 21H ; Q. create ok?
JC CRE_FILEP1 ; A. no .. error
MOV HANDLE, AX ; save handle
OR FLG1, FLG1O ; .. show file is open
MOV SI, WBUF ; si -> received data
PUSH MDATA+22[SI] ; push file time
POP FILETIME ; .. pop it
PUSH MDATA+24[SI] ; push file date
POP FILEDATE ; .. pop it
MOV SI, OFFSET FILENAME ; si -> file created
CALL ZCPRTAZ ; .. print the name
MOV DX, OFFSET BRECVD ; dx -> being received
MOV AH, 09H ; ah = print ascii$ string
INT 21H ; .. print the string
CALL ZCPRBLKS ; .. print blocks to send
MOV AL, MSG_ACK ; ack the request
JMP SHORT CRE_FILEP2 ; .. continue
CRE_FILEP1: MOV AH, 9 ; ah = print ascii$
MOV DX, OFFSET FILENOPEN ; dx -> error message
INT 21H ; .. tell 'em Jim
MOV AL, MSG_NAK ; nak the request
CRE_FILEP2: MOV CX, 0 ; .. no data
CALL ZCBLKSND ; .. reply
POP DI ; restore regs
POP SI
POP CX
POP BX
POP AX
RET
CRE_FILE_P ENDP
; ----------------------------------------
; determine if file exists
; ----------------------------------------
QRY_FLE_P PROC NEAR ; determine if file exists
PUSH AX ; save caller's regs
PUSH CX
PUSH DX
PUSH SI
PUSH DI
MOV SI, WBUF ; si -> received data
ADD SI, MDATA+30 ; si -> file name
MOV DI, OFFSET FILENAME ; di -> file name area
MOV CX, 13 ; .. length to move
REP MOVSB ; move in the file name
MOV DX, OFFSET CURDIR ; dx -> file name to open
XOR CX, CX ; cx = attributes
MOV AH, 4EH ; ah = find first
INT 21H ; Q. file found?
JC QRY_FLE_P1 ; A. no .. error
MOV AL, MSG_ACK ; ack the request
JMP SHORT QRY_FLE_P2 ; .. continue
QRY_FLE_P1: MOV AL, MSG_NAK ; nak the request
QRY_FLE_P2: PUSH AX ; save reply
MOV AH, 36H ; ah = get free space
XOR DL, DL ; .. on current drive
INT 21H ; .. via dos
XOR DX, DX ; dx = 0
MUL CX ; .. clusters x secs/cluster
MUL BX ; .. secs x bytes/sector
MOV DS:DTA+DTA_LEN, AX ; save lsw of free
MOV DS:DTA+DTA_LEN+2, DX ; .. and msw
MOV CX, DTA_LEN+4 ; cx = find file data len
MOV SI, DTA ; si -> dta
POP AX ; .. restore reply
CALL ZCBLKSND ; .. send reply
POP DI ; restore caller's regs
POP SI
POP DX
POP CX
POP AX
RET
QRY_FLE_P ENDP
; ----------------------------------------
; process shutdown request
; ----------------------------------------
SHUTDOWN_P PROC NEAR ; process shutdown request
MOV DX, OFFSET SHUTDOWN_R ; dx -> request
JMP ZCDIE ; .. we'll never return
SHUTDOWN_P ENDP
; ----------------------------------------
; ack received
; ----------------------------------------
MSG_ACK_P PROC NEAR ; process ack
CLC ; show ack received
RET
MSG_ACK_P ENDP
; ----------------------------------------
; process nak request
; ----------------------------------------
MSG_NAK_P PROC NEAR ; process nak
STC ; show nak received
RET
MSG_NAK_P ENDP
; ----------------------------------------
; process data block
; ----------------------------------------
DATA_BLK_P PROC NEAR ; process data block
MOV BX, WBUF ; bx -> buffer
LEA DX, [BX+MDATA] ; dx -> data area
MOV DI, XBUF_PTR ; di -> build buffer
MOV SI, DX ; si -> input data
MOV CX, [BX+MLEN] ; cx = buffer length
SUB CX, 3 ; .. exclude cmd & blkno
CLD ; .. positive direction
REP MOVSB ; .. move data to buffer
MOV XBUF_PTR, DI ; save new o/p ptr
MOV SI, XBUF ; si -> xbuf
ADD SI, XBUF_WL ; si -> write pos
CMP DI, SI ; Q. write?
JB DATA_BLK90 ; A. no .. continue
MOV CX, XBUF_PTR ; cx -> past data
MOV DX, XBUF ; dx -> data
SUB CX, DX ; cx = data length
MOV XBUF_PTR, DX ; .. save put pointer
MOV BX, HANDLE ; bx - handle
MOV AH, 40H ; ah = write
INT 21H ; .. write file
DATA_BLK90: CALL ZCPRTLFT ; print # blocks left
MOV AL, MSG_ACK ; ack the msg
XOR CX, CX ; .. no data
CALL ZCBLKSND ; .. send it
RET
DATA_BLK_P ENDP
; ----------------------------------------
; process eof request
; ----------------------------------------
EOF_MARK_P PROC NEAR ; process eof
MOV CX, XBUF_PTR ; cx -> past data
MOV DX, XBUF ; dx -> data
SUB CX, DX ; Q. any to write?
JZ EOF_MARK80 ; A. no .. close & exit
MOV XBUF_PTR, DX ; .. save put pointer
MOV BX, HANDLE ; bx - handle
MOV AH, 40H ; ah = write
INT 21H ; .. write file
EOF_MARK80: MOV BX, HANDLE ; bx = handle to close
TEST FLG, FLGD ; Q. use machine date?
JNZ EOF_MARK85 ; A. yes .. skip sent date.
MOV AX, 5701H ; ax = set file date
MOV CX, FILETIME ; cx = file time
MOV DX, FILEDATE ; dx = file date
INT 21H ; set file date & time
EOF_MARK85: MOV AH, 3EH ; ah = close command
INT 21H ; .. close the file
AND FLG1, NOT FLG1O ; .. show file closed
MOV AL, MSG_ACK ; ack the msg
XOR CX, CX ; .. no data
CALL ZCBLKSND ; .. send it
MOV DX, OFFSET CRLF ; dx -> crlf
MOV AH, 9 ; ah = print ascii$
INT 21H ; .. display it
RET
EOF_MARK_P ENDP
; ----------------------------------------
; process set flags request
; ----------------------------------------
SET_FLG_P PROC NEAR ; process verify ok
MOV BX, WBUF ; bx -> received packet
MOV AL, MDATA[BX] ; al = flags sent
AND AL, FLG_SET ; assure other flags off
OR FLG, AL ; .. turn on other flags
MOV AL, FLG ; al = new flag set
AND AL, FLG_SET ; .. set off others
XOR CX, CX ; cx = send no data
CALL ZCBLKSND ; .. return flags
RET
SET_FLG_P ENDP
; ----------------------------------------
; resync speed
; ----------------------------------------
RESYNC_P PROC NEAR ; resync speed
MOV DX, OFFSET TOOMANY ; dx -> message
MOV AH, 9 ; ah = print ascii$
INT 21H ; .. display message
MOV DSRWAIT, SEC_30 ; .. reset start wait time
CMP FLGPCR,0 ; Q. pcremote active
JZ RESYNC_P10 ; A. no
JMP RESYNC_P20 ; A. yes, don't change baud rate
RESYNC_P10: INC BAUD_CNTR ; .. select next baud rate
RESYNC_P20: CALL ZCSPEED ; .. resync
CALL ZCCLRCOM ; .. clear our recv buffer
RET
RESYNC_P ENDP
; ---------------------------------------------------------------------
; This routine will send the requested files.
; Exit: Returns to DOS when all files sent.
; ---------------------------------------------------------------------
ZCSF PROC NEAR
MOV AH, FNDOP ; ah = find operation to use
XOR CX, CX ; cx = attribute to find
MOV DX, OFFSET CURDIR ; dx -> path/filename
INT 21H ; Q. any file found?
JNC ZCSF05 ; A. yes .. try to send it
JMP ZCSF90 ; .. else .. end of job
ZCSF05: MOV FNDOP, 4FH ; set op to find next
PUSH ES ; save es
LES AX, DS:DWORD PTR DTA_LSIZ ; es:ax = file size
MOV WORD PTR BYTESLFT, AX ; .. save lsw
MOV WORD PTR BYTESLFT+2, ES ; .. and msw
POP ES
MOV AX, 3D00H ; ax = open for read
MOV DX, DTA_NAME ; ds:dx -> filename to open
INT 21H ; Q. open the file ok?
JC ZCSF ; A. no .. try next file
MOV HANDLE, AX ; save the handle
MOV AL, QRY_FLE ; al = determine existence
MOV CX, DTA_LEN ; cx = find file data
MOV SI, DTA ; si -> dta
CALL ZCBLKSND ; send the request
CALL ZCRECV ; Q. does file exist?
MOV BX, WBUF ; bx -> received buffer
MOV AX,WORD PTR DTA_LEN[BX+MDATA] ; ax = lsw of free
MOV DX,WORD PTR DTA_LEN[BX+2+MDATA] ; dx = msw of free
MOV FILESZL, AX ; .. save locally
MOV FILESZH, DX ; .. lsw & msw
JC ZCSF20 ; A. no .. continue
ADD AX, MDATA+26[BX] ; add in file's len
ADC DX, MDATA+28[BX] ; .. lsw & msw
MOV FILESZL, AX ; .. save locally
MOV FILESZH, DX ; .. lsw & msw
TEST FLG, FLGO ; Q. overwrite?
JNZ ZCSF20 ; A. yes .. make it so
TEST FLG, FLGU ; Q. update?
JZ ZCSF10 ; A. no .. ask operator
MOV BX, WBUF ; bx -> recv'd message
MOV AX, MDATA+24[BX] ; ax = receiver's file date
CMP AX, DS:DTA_DATE ; Q. is receivers file older?
JB ZCSF20 ; A. yes.. send our's
JA ZCSF80 ; A. younger .. skip it
MOV AX, MDATA+22[BX] ; ax = receiver's file time
CMP AX, DS:DTA_TIME ; Q. is receivers file older?
JB ZCSF20 ; A. yes .. send our's
JMP SHORT ZCSF80 ; .. else .. skip
ZCSF10: MOV DX, OFFSET FILEXISTS ; dx -> message
CALL ZCFPR ; .. issue overwrite prompt
CMP AL, 'Y' ; Q. overwrite?
JE ZCSF20 ; A. yes .. do it
CMP AL, 'N' ; Q. do not overwrite?
JE ZCSF80 ; A. yes ... skip file
JMP SHORT ZCSF10 ; .. retry prompt
ZCSF20: MOV AX, DS:DTA_HSIZ ; ax = hi file size
CMP AX, FILESZH ; Q. is our file smaller?
JB ZCSF30 ; A. yes .. start transfer
JA ZCSF25 ; A. no .. check for abort
MOV AX, DS:DTA_LSIZ ; .. get low order
CMP AX, FILESZL ; Q. is our file smaller?
JNA ZCSF30 ; A. yes .. start transfer
ZCSF25: TEST FLG, FLGA ; Q. abort if too big?
JNZ ZCSF28 ; A. no .. next file
MOV SI, DTA_NAME ; si -> file name
CALL ZCPRTAZ ; .. display it
MOV DX, OFFSET TOOBIG ; dx -> too big message
MOV AH, 9 ; ah = print to $
INT 21H ; .. display message
JMP SHORT ZCSF80 ; .. next file
ZCSF28: MOV DI, OFFSET DISKFULL ; di -> full prompt
CALL ZCSPROMPT ; .. tell the user
JMP SHORT ZCSF90 ; .. shutdown
ZCSF30: MOV SI, DTA_NAME ; si -> filename
CALL ZCPRTAZ ; print the
MOV DX, OFFSET BSENT ; dx -> being sent
MOV AH, 09H ; ah = display ascii$
INT 21H ; display message
CALL ZCPRBLKS ; print blocks left message
MOV WAIT_COUNT, 0 ; .. clear the wait count value
CALL ZCSEND ; .. and send the file
MOV DX, OFFSET CRLF ; dx -> crlf
MOV AH, 9 ; ah = print ascii$
INT 21H ; .. display it
ZCSF80: MOV BX, HANDLE ; bx = handle of last file
MOV AH, 3EH ; ah = close file opcode
INT 21H ; .. file closed, captain!
JMP ZCSF ; .. try next file
ZCSF90: MOV AL, SHUTDOWN ; al = shutdown command
XOR CX, CX ; .. no data is sent
CALL ZCBLKSND ; send the command
MOV DX, OFFSET SHUTDOWN_R ; dx -> shutdown string
JMP ZCDIE ; end gracefully
ZCSF ENDP
; ---------------------------------------------------------------------
; This routine will display the requested string.
; Entry: si -> string to print.
; ---------------------------------------------------------------------
ZCPRTAZ PROC NEAR
PUSH AX ; save regs
PUSH DX
PUSH SI
MOV AH, 02H ; ah = display character
ZCPRTAZ10: LODSB ; al = char to prt
OR AL, AL ; Q. anything to prt?
JZ ZCPRTAZ90 ; A. no .. return
MOV DL, AL ; dl = char to prt
INT 21H ; .. display the char
JMP ZCPRTAZ10 ; .. next char
ZCPRTAZ90: POP SI ; restore regs
POP DX
POP AX
RET ; return to caller
ZCPRTAZ ENDP
; ---------------------------------------------------------------------
; This routine will build a prompt for both machines.
; Entry: filename in the DTA contains file name; dx -> prompt string to use
; Exit: al = reply char, upper case
; ---------------------------------------------------------------------
ZCFPR PROC NEAR
PUSH SI ; save regs
PUSH DI
MOV DI, XBUF ; di -> work area
MOV SI, DTA_NAME ; si -> filename
ZCFPR10: LODSB ; al = char from filename
OR AL, AL ; Q. end of name?
JZ ZCFPR20 ; A. yes .. next field
STOSB ; .. save in xbuf
JMP SHORT ZCFPR10 ; process next char
ZCFPR20: MOV SI, DX ; dx -> prompt
ZCFPR25: LODSB ; al = prompt char
STOSB ; .. save it
CMP AL, '$' ; Q. end of prompt?
JNE ZCFPR25 ; A. no .. continue
MOV DI, XBUF ; di -> xbuf
CALL ZCSPROMPT ; issue prompt
AND AL, NOT 20H ; response to upper case
POP DI ; restore regs
POP SI
RET ; return to caller
ZCFPR ENDP
; ---------------------------------------------------------------------
; This routine transfers ZCOPY out the port in DX.
; Entry: dx = port to transfer on; cx = # chars to send
; Exit: Stops via int 3 - debug better be there
; ---------------------------------------------------------------------
ZCXFER PROC NEAR
MOV SI, 0FEH ; si -> start of area to send
MOV WORD PTR [SI], CX ; set up length of program
ADD CX, 2 ; add in length
ZCXFER10: ADD DX, 5 ; dx -> lsr
IN AL, DX ; al = lsr
SUB DX, 5 ; dx -> base port
TEST AL, LSR_THRE ; Q. thr empty?
JZ ZCXFER10 ; A. no .. wait
LODSB ; al = char to send
OUT DX, AL ; .. sent the char
LOOP ZCXFER10 ; .. loop til done
INT 3 ; then return to debug
ZCXFER ENDP
; Uninitialized data areas
UDATA EQU $ ; start of unitialized data
IO_BASE EQU WORD PTR UDATA ; base com port address
INT_VECTOR EQU BYTE PTR IO_BASE+2 ; interrupt vector to use
OLD_COM EQU DWORD PTR INT_VECTOR+1 ; old interrupt for com:
OLD_TIMER EQU DWORD PTR OLD_COM+4 ; old interrupt for timer tick
OLD_CTLBRK EQU DWORD PTR OLD_TIMER+4 ; old interrupt for control break
OLD_DOSCTLB EQU DWORD PTR OLD_CTLBRK+4 ; old interrupt for dos ^break
OLD_DOSERR EQU DWORD PTR OLD_DOSCTLB+4 ; old interrupt for dos error
HANDLE EQU WORD PTR OLD_DOSERR+4 ; open file handle
RBUF_GPTR EQU WORD PTR HANDLE+2 ; receive buffer next get address
RBUFL EQU 1100H ; length of receive buffer
SBUF EQU WORD PTR RBUF_GPTR+2 ; send buffer address
SBUFL EQU 600H ; length of send buffer
WBUF EQU WORD PTR SBUF+2 ; work buffer address
WBUFL EQU 500H ; length of work buffer
XBUF EQU WORD PTR WBUF+2 ; file build buffer
XBUF_PTR EQU WORD PTR XBUF+2 ; i/o pointer
EDRV EQU BYTE PTR XBUF_PTR+2 ; entry time logged drive
EDIR EQU WORD PTR EDRV+1 ; pointer to entry time directory
EDIRL EQU 65 ; length of area
FILESZL EQU WORD PTR EDIR+2 ; file size low
FILESZH EQU WORD PTR FILESZL+2 ; .. and high
FILEDATE EQU WORD PTR FILESZH+2 ; file date
FILETIME EQU WORD PTR FILEDATE+2 ; file time
BYTESLFT EQU DWORD PTR FILETIME+2 ; bytes left to transfer
BUF_START EQU BYTESLFT+4 ; start of buffer space

CSEG ENDS
END START


  3 Responses to “Category : Files from Magazines
Archive   : VOL11N02.ZIP
Filename : ZCOPY.ASM

  1. Very nice! Thank you for this wonderful archive. I wonder why I found it only now. Long live the BBS file archives!

  2. This is so awesome! 😀 I’d be cool if you could download an entire archive of this at once, though.

  3. But one thing that puzzles me is the “mtswslnkmcjklsdlsbdmMICROSOFT” string. There is an article about it here. It is definitely worth a read: http://www.os2museum.com/wp/mtswslnk/