; Edit history: ; ; [v2.28] ; Let debug packet display routines print packets with '$' in them, ; Fix timeout in inchr to work correctly ; (from Edgar Butt, Univ. of Md.) ; Ignore packets which are too small ; (from Greg Small, UC Berkeley) ; Added sleep routine public data, spack, rpack, rpack5, portval, port1, port2, hierr public prtbase, nports, port3, port4, sleep include msdefs.h maxlp equ 100 ; Use as number of times to loop (in inchr). true equ 1 false equ 0 mntrgl equ bufsiz/4 ; Low point = 1/4 of the way full. maxpack equ 78H ; largest packet we can handle datas segment public 'datas' extrn flags:byte, trans:byte, pack:byte, count:word, xofsnt:byte prtbase label byte port1 prtinfo <0FFFH,0,defpar,1,0,defhand,floxon> port2 prtinfo <0FFFH,0,defpar,1,0,defhand,floxon> port3 prtinfo <0FFFH,0,defpar,1,0,defhand,floxon> port4 prtinfo <0FFFH,0,defpar,1,0,defhand,floxon> rept portmax-4 prtinfo <0FFFH,0,defpar,1,0,defhand,floxon> endm ;; systems with two ports can set portval to port1 or port2. ;; systems with more than two ports can set nports higher, ;; then set portval to the address prtbase+(#-1)*size prtinfo ;; where # is the desired port. portval dw port1 ; Default is to use port 1. nports db 2 ; # of known ports hierr db 0 ; Non-ascii char (non-zero if yes). spmes db 'Spack: $' rpmes db 'Rpack: $' crlf db cr,lf,'$' infms0 db 'Waiting .....$' hibit db 'Warning - Non Ascii char$' cemsg db 'User intervention$' temp dw 0 tmp db ?,'$' prvtyp db 0 ; Type of last packet sent. [27e] pktptr dw ? ; Position in receive packet. incnt dw ? ; Number of chars read in from port. loopct db ? ; Loop counter. time dw ? ; When we should timeout. dw ? ; Want a double word. packet db ?,?,?,? ; Packet (data is part of it). data db 5AH DUP(?) ; Data and checksum field of packet. recpkt db maxpack DUP(?) ; Receive packet storage (use the following). db ?,?,?,? ; Space for '$' and other stuff. 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 crctb2 dw 00000H dw 01189H dw 02312H dw 0329BH dw 04624H dw 057ADH dw 06536H dw 074BFH dw 08C48H dw 09DC1H dw 0AF5AH dw 0BED3H dw 0CA6CH dw 0DBE5H dw 0E97EH dw 0F8F7H datas ends code segment public extrn prtchr:near, clrbuf:near, outchr:near extrn sppos:near, stpos:near, biterr:near, intmsg:near extrn clearl:near, rppos:near, errpack:near, prtscr:near assume cs:code, ds:datas ; Packet routines ; Send_Packet ; This routine assembles a packet from the arguments given and sends it ; to the host. ; ; Expects the following: ; AH - Type of packet (D,Y,N,S,R,E,F,Z,T) ; ARGBLK - Packet sequence number ; ARGBK1 - Number of data characters ; Returns: +1 always SPKT PROC NEAR spack: push ax ; Save the packet type. mov prvtyp,ah ; Remember packet type. [27e] call clrbuf ; Clear the input buffer. [20e] mov bx,offset packet ; Get address of the send packet. mov ah,trans.ssoh ; Get the start of header char. mov [bx],ah ; Put in the packet. inc bx ; Point to next char. mov ax,pack.argbk1 ; Get the number of data chars. xchg ah,al mov al,trans.chklen ; Length of checksum. dec al ; Extra length of checksum. add ah,' '+3 ; Real packet character count made printable. add ah,al ; Account for checksum length in count. mov [bx],ah ; Put in the packet. inc bx ; Point to next char. mov ch,0 ; For the 16 bit checksum. mov cl,ah ; Start the checksum. mov ax,pack.argblk ; Get the packet number. add al,' ' ; Add a space so the number is printable. mov [bx],al ; Put in the packet. inc bx ; Point to next char. add cx,ax ; Add the packet number to the checksum. pop ax ; Get the packet type. mov [bx],ah ; Put in the packet. inc bx ; Point to next char. mov al,0 xchg ah,al add cx,ax ; Add the type to the checksum. mov dx,pack.argbk1 ; Get the packet size. spack2: cmp dx,0 ; Are there any chars of data? jz spack3 ; No, finish up. dec dx ; Decrement the char count. mov al,[bx] ; Get the next char. inc bx ; Point to next char. mov ah,0 add cx,ax ; Add the char to the checksum. cmp al,0 jns spack2 cmp hierr,0ffH ; Printed message already? je spack2 ; Yes, then that's it. push bx push cx push dx call biterr pop dx pop cx pop bx mov hierr,0FFH ; set err flag. jmp spack2 ; Go try again. spack3: cmp trans.chklen,2 ; What kind of checksum are we using. je spackx ; 2 characters. jg spacky ; 3 characters. mov ah,cl ; 1 char: get the character total. mov ch,cl ; Save here too (need 'cl' for shift). and ah,0C0H ; Turn off all but the two high order bits. mov cl,6 shr ah,cl ; Shift them into the low order position. mov cl,ch add ah,cl ; Add it to the old bits. and ah,3FH ; Turn off the two high order bits. (MOD 64) add ah,' ' ; Add a space so the number is printable. mov [bx],ah ; Put in the packet. inc bx ; Point to next char. jmp spackz ; Add EOL char. spacky: mov al,0 ; Get a null. mov [bx],al ; To determine end of buffer. push bx ; Don't lose our place. mov bx,offset packet+1 ; First checksummed character. call crcclc ; Calculate the CRC. pop bx push cx mov ax,cx ; Manipulate it here. and ax,0F000H ; Get 4 highest bits. mov cl,4 shr ah,cl ; Shift them over 4 bits. add ah,' ' ; Make printable. mov [bx],ah ; Add to buffer. inc bx pop cx ; Get back checksum value. spackx: push cx ; Save it for now. and cx,0FC0H ; Get bits 6-11. mov ax,cx mov cl,6 shr ax,cl ; Shift them bits over. add al,' ' ; Make printable. mov [bx],al ; Add to buffer. inc bx pop cx ; Get back the original. and cx,003FH ; Get bits 0-5. add cl,' ' ; Make printable. mov [bx],cl ; Add to buffer. inc bx spackz: cmp flags.debug,0 ; debug mode. je spack4 push bx ; save end of packet position call sppos call clearl mov dx,offset crlf mov ah,prstr int dos call clearl ; clear spack line and line below call sppos mov ah,prstr mov dx,offset spmes int dos ; print "spack:" message mov di,offset packet ; address of packet pop cx push cx sub cx,di ; calculate length of string call prtscr pop bx ; restore end of string pointer spack4: mov ah,trans.seol ; Get the EOL the other host wants. mov [bx],ah ; Put in the packet. inc bx ; Point to next char. mov ah,0 ; Get a null. mov [bx],ah ; Put in the packet. call outpkt ; Call the system dependent routine. jmp r jmp rskp SPKT ENDP ; Write out a packet. OUTPKT PROC NEAR mov dh,trans.spad ; Get the number of padding chars. outpk2: dec dh cmp dh,0 jl outpk3 ; If none left proceed. mov ah,trans.spadch ; Get the padding char. push dx ; save loop counter call outchr ; Output it. pop dx ret ; we failed... jmp outpk2 outpk3: mov bx,offset packet ; Point to the packet. outlup: mov ah,[bx] ; Get the next character. cmp ah,0 ; Is it a null? jnz outlp2 jmp rskp outlp2: call outchr ; Output the character. jmp r inc bx ; Increment the char pointer. jmp outlup OUTPKT ENDP ; Calculate the CRC. Returns the CRC in CX. Destroys: BX, AX. crcclc: push dx push si mov dx,0 ; Initial CRC value is 0. crc0: mov al,[bx] ; Get the first char of the string. cmp al,0 ; If null, then we're done. je crc1 inc bx xor al,dl ; Xor input with lo order byte of CRC. mov ah,al ; Get a copy. and ah,0F0H ; Get hi 4 bits. mov cl,4 shr ah,cl ; Right justify. and al,0FH ; Get lo 4 bits. push bx mov si,offset crctb2 ; Low portion of CRC factor. mov bh,0 mov bl,al add bl,al ; Get word index. mov cx,[si+bx] ; Low portion. mov si,offset crctab ; High portion of CRC factor. mov bh,0 mov bl,ah add bl,ah ; Get word index. mov bx,[si+bx] xor bx,cx ; Add the two. mov cl,8 shr dx,cl ; Shift CRC 8 bits to the right. xor dx,bx ; XOR table value and CRC. pop bx ; Retrieve index. jmp crc0 crc1: mov cx,dx ; Return it in CX. pop si pop dx ret ; Receive_Packet ; This routine waits for a packet arrive from the host. It reads ; chars until it finds a SOH. RPACK PROC NEAR rpack5: call inpkt ; Read up to a carriage return. jmp r ; Return bad. rpack0: call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jne rpack0 ; No, go until it is. rpack1: call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jz rpack1 ; Yes, then go start over. mov ch,0 ; For 16-bit checksum. mov cl,al ; Start the checksum. mov ah,0 mov pack.argbk1,ax ; Save the data count. call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jz rpack1 ; Yes, then go start over. mov ah,0 add cx,ax ; Add it to the checksum. sub al,' ' ; Get the real packet number. mov ah,0 mov pack.argblk,ax ; Save the packet number. call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jz rpack1 ; Yes, then go start over. mov ah,0 mov temp,ax ; Save the message type. [11] mov bp,portval ; Point to current port structure. [27e] cmp ds:[bp].ecoflg,0 ; Is the host echoing? [27e] jne rpak11 ; No, packets not echoed. [27e] cmp al,prvtyp ; Packet type same as last sent? [27e] je rpack5 ; Yes, chuck echoed packet. [27e] rpak11: add cx,ax ; Add it to the checksum. ; Start of change. ; Now determine block check type for this packet. Here we violate the layered ; nature of the protocol by inspecting the packet type in order to detect when ; the two sides get out of sync. Two heuristics allow us to resync here: ; a. An S packet always has a type 1 checksum. ; b. A NAK never contains data, so its block check type is LEN-2. push cx mov cl,al mov ax,pack.argbk1 ; Get back the size. sub al,34 ; unchar(len) - 2, for SEQ & TYPE fields. mov ah,trans.chklen ; Checksum length we expect. cmp cl,'S' ; Is this an "S" packet? jne rpk0 ; Nope. mov ah,1 ; Yes, use 1 char checksum. rpk0: cmp cl,'N' ; Is this a NAK? jne rpk1 ; Nope. mov ah,al ; So, len - 2 is checksum type. rpk1: mov trans.chklen,ah ; Then, this is the chksum length. sub al,ah ; Real size of data. mov dh,al ; Need it here. mov ah,0 mov pack.argbk1,ax ; And here. pop cx ; End of change. mov bx,offset data ; Point to the data buffer. rpack2: dec dh ; Any data characters? js rpack3 ; If not go get the checksum. call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jnz rpak2a jmp rpack1 ; Yes, then go start over. rpak2a: mov [bx],al ; Put the char into the packet. inc bx ; Point to the next character. mov ah,0 add cx,ax ; Add it to the checksum. jmp rpack2 ; Go get another. rpack3: call getchr ; Get a character. jmp r ; Hit the carriage return, return bad. cmp al,trans.rsoh ; Is the char the start of header char? jnz rpk3x jmp rpack1 ; Yes, then go start over. rpk3x: sub al,' ' ; Turn the char back into a number. cmp trans.chklen,2 ; What checksum length is in use. je rpackx ; Two character checksum. jg rpacky ; Three character CRC. mov dh,cl ; 1 char - get the character total. and dh,0C0H ; Turn off all but the two high order bits. mov ch,cl mov cl,6 shr dh,cl ; Shift them into the low order position. mov cl,ch add dh,cl ; Add it to the old bits. and dh,3FH ; Turn off the two high order bits. (MOD 64) cmp dh,al ; Are they equal? jz rpack4 ; If so finish up. jmp rpack6 ; No, we fail. rpacky: mov tmp,al ; Save value from packet here. mov ah,0 ; Three character CRC. push bx mov bx,pktptr ; Where we are in the packet. dec bx mov [bx],ah ; Add null to signify end of buffer. mov bx,offset recpkt+1 ; Where data for CRC is. call crcclc ; Calculate the CRC and put into CX. pop bx push cx mov ax,cx ; Manipulate it here. and ax,0F000H ; Get 4 highest bits. mov cl,4 shr ah,cl ; Shift them over 4 bits. pop cx ; Get back checksum value. cmp ah,tmp ; Is what we got == what we calculated? jne rpack6 call getchr ; Get next character of checsum. jmp r ; Failed. cmp al,trans.rsoh ; Restarting? jz rpack7 sub al,' ' ; Get back real value. rpackx: mov tmp,al ; Save here for now. push cx ; Two character checksum. and cx,0FC0H ; Get bits 6-11. mov ax,cx mov cl,6 shr ax,cl ; Shift them bits over. pop cx ; Get back the original. cmp al,tmp ; Are they equal? jne rpack6 ; No, we fail. call getchr ; Get last character of checsum. jmp r ; Failed. cmp al,trans.rsoh ; Restarting? jz rpack7 sub al,' ' ; Get back real value. and cx,003FH ; Get bits 0-5. cmp al,cl ; Do the last chars match? jne rpack6 rpack4: mov ah,0 mov [bx],ah ; Put a null at the end of the data. mov ax,temp ; Get the type. [11] xchg al,ah ; Packet type should be in AH. jmp rskp rpack6: ret rpack7: jmp rpack1 ; For the jump out of range. RPACK ENDP INPKT PROC NEAR mov bl,flags.cxzflg ; Remember original value. [20b] mov tmp,bl ; Store it here. [20b] inpkt0: call inchr ; Get a character. [27a] jmp inpkt8 ; Return failure. [27a] nop ; Make it three bytes long. [27a] cmp ah,trans.rsoh ; Is it SOH char? [27a] jne inpkt0 ; No hold out for SOH. [27a] inpkt1: mov bx,offset recpkt ; Point to the beginning of the packet. mov incnt,0 mov [bx],ah ; Add SOH to buffer. [27a] inc bx ; Increment pointer. [27a] inc incnt ; Increment counter. [27a] inpkt2: call inchr ; Get a character. jmp inpkt8 ; Return failure. [20b] nop ; Make it three bytes long. [20b] cmp ah,trans.rsoh ; Starting over again? [27a] je inpkt1 mov [bx],ah ; Put the char in the packet. inc bx inc incnt cmp ah,trans.reol ; Is it the EOL char? je inpkt3 ; ended by eol, keep going cmp incnt,maxpack ; is it too big? jbe inpkt2 ; no, keep going jmp inpkt1 ; else just start over inpkt3: cmp incnt,5 ; Ignore packets which are too small jbe inpkt0 mov bp,portval cmp ds:[bp].hndflg,0 ; Waiting for handshake? jz inpkt5 ; If not then proceed. inpkt4: call inchr ; Wait for the turn around char. jmp inpkt8 ; Return failure. [20b] nop ; Make it three bytes long. [20b] cmp ah,trans.rsoh ; Start of packet? [27a] je inpkt1 ; Yes go start over. [27a] mov bp,portval cmp ah,ds:[bp].hands ; Is it the IBM turn around character? jne inpkt4 ; If not, go until it is. inpkt5: cmp flags.debug,0 ; In debug mode? je inpkt6 push bx ; save character pointer call rppos call clearl mov dx,offset crlf mov ah,prstr int dos call clearl ; clear debug line and line beneath call rppos ; Reposition cursor. mov ah,prstr mov dx,offset rpmes int dos mov di,offset recpkt ; buffer address pop cx sub cx,di ; length of buffer call prtscr ; display packet inpkt6: mov bx,offset recpkt mov pktptr,bx ; Save the packet pointer. mov bl,tmp ; Get the original value. [20b] cmp bl,flags.cxzflg ; Did ^X/^Z flag change? [20b] je inpkt7 ; If not, just return. [20b] cmp flags.cxzflg,'E' ; Error packet? je inpkt9 call intmsg ; Else, say we saw the interrupt. [20b] inpkt7: jmp rskp ; If so we are done. inpkt8: cmp flags.cxzflg,'C' ; Did the user type a ^C? [25] jne inpkt9 mov pack.state,'A' ret inpkt9: cmp flags.cxzflg,'E' ; How about ^E? jne inpk10 ; No just go on. mov bx,offset cemsg ; Null message for error packet. call errpack mov pack.state,'A' ret inpk10: mov bl,tmp ; Get the original value. [20b] cmp bl,flags.cxzflg ; Did ^X/^Z flag change? [20b] je inpk11 ; If not, just return failure. [20b] call intmsg ; Else, say we saw the interrupt. [20b] inpk11: jmp r INPKT ENDP ; sleep for the # of seconds in al sleep proc near saveac push ax ; save argument mov ah,gettim int dos ; get current time pop bx ; restore desired # of seconds add dh,bl ; add # of seconds sleep1: cmp dh,60 ; too big for seconds? jb sleep2 ; no, keep going sub dh,60 ; yes, subtract a minute inc cl ; and make up for it here cmp cl,60 ; did minutes overflow? jb sleep1 ; no, check seconds again sub cl,60 ; else take away an hour inc ch ; add it back here jmp sleep1 ; and keep checking sleep2: mov time,cx mov time+2,dx ; store desired ending time sleep3: mov ah,gettim ; get time int dos ; bug dos ; adjust time when times are before and after midnight. cmp ch,0 ; is ending time between 0:00 and 1:00? jne sleep4 ; no, keep going cmp byte ptr time+1,23 ; is desired time after 23:00? jne sleep4 ; no, go on mov ch,24 ; otherwise set current hour to 24 sleep4: cmp cx,time ; check hours and minutes jb sleep3 ja sleep5 ; over limit, time to exit cmp dx,time+2 ; same, check seconds and fraction jb sleep3 ; below, keep looking sleep5: ret ; else just return sleep endp inchr: cmp flags.timflg,0 ; Are timeouts turned off. je inchr1 ; Yes, so skip this stuff. cmp trans.stime,0 ; Don't time out? je inchr1 ; Yes, so skip this stuff. mov loopct,0 ; Use to check for timeout. mov ah,gettim ; Get the time. int dos add dh,trans.stime ; add timeout to seconds inch01: cmp dh,60 ; seconds overflowed? jb inch02 ; no, break loop sub dh,60 inc cl ; add one minute cmp cl,60 ; did this make minutes overflow? jb inch01 ; no, check seconds again (should just divide) sub cl,60 inc ch ; add one hour jmp inch01 ; and check seconds again inch02: mov time,cx mov time+2,dx ; store ending time now. inchr1: call prtchr ; Is there a character to read? jmp inchr6 ; Got one. mov dl,0FFH ; To read in a char. mov ah,dconio ; Is a char on the console? int dos jz inchr2 ; If not go look for another char. mov ah,al cmp ah,cr ; Is it a carriage return? je inchr5 ; If yes, then leave. cmp ah,'Z'-100O ; Control-Z? [20b] je inchr4 ; Yes - flag it. [20b] cmp ah,'X'-100O ; Control-X? [20b] je inchr4 ; Yes - flag it. [20b] cmp ah,'E'-100O ; Control-E? je inchr4 ; Flag it and get rest of packet. cmp ah,'C'-100O ; Control-C? [25] jne inchr2 ; No, then wait for input. [25] add ah,100O ; Make it printable. [25] mov flags.cxzflg,ah ; Save it. [25] ret ; Return right away. [25] inchr2: cmp flags.timflg,0 ; Are timeouts turned off? je inchr1 ; Yes, just check for more input. cmp trans.stime,0 ; Doing time outs? je inchr1 ; No, just go check for more input. inc loopct cmp loopct,maxlp ; Times to go without checking time. jne inchr1 ; Don't check yet. mov ah,gettim ; Get the current time. int dos ; adjust time when times are before and after midnight ; note: this won't work for timeouts which start before ; midnight and are more than an hour (not likely!). cmp ch,0 ; is ending time between 00:00 and 1:00? jne inch21 ; no, can just compare times cmp byte ptr time+1,23 ; is desired hour after 23:00? jne inch21 ; no, just compare them mov ch,24 ; otherwise set current hour to 24 for wrap inch21: cmp cx,time ; check hours and minutes jb inchr3 ; under limit, keep looking ja inchr5 ; over limit, time out cmp dx,time+2 ; same, compare seconds and fraction jae inchr5 ; over limit, time out ; fall thru if time hasn't occurred yet. inchr3: mov loopct,0 ; Reset counter. jmp inchr1 inchr4: add ah,100O ; Make it printable. [20b] mov flags.cxzflg,ah ; Remember what we saw. [20b] jmp inchr2 ; Continue getting input. [20b] inchr5: ret inchr6: mov ah,al mov bp,portval ; Point to current port structure. cmp ds:[bp].parflg,parnon ; Is the parity none? [10] je inchr7 ; We're done. [10] and ah,7FH ; Turn off the parity bit. inchr7: cmp ds:[bp].floflg,0 ; Doing any flow control? jne inchr8 ; Yes, check it out. jmp rskp ; No, just return the data. inchr8: cmp xofsnt,true ; Have we sent flow char (XOFF)? je inchr9 ; Yes. jmp rskp ; No, just return. inchr9: cmp count,mntrgl ; Under the low trigger point? jb inchra ; Yes. jmp rskp ; No, just return. inchra: push ax mov bp,portval mov ax,ds:[bp].flowc ; Get flow control char (AH = XON, AL = XOFF). call outchr ; Send it (XON). mov xofsnt,false ; Turn off the flag. pop ax jmp rskp ; Return the character. ; Return next character in AL. GETCHR PROC NEAR push bx mov bx,pktptr ; Get the packet pointer. mov al,[bx] ; Get the char. inc bx mov pktptr,bx pop bx ; Restore BX. cmp al,trans.reol ; Is it the EOL char? jne getcr2 ; If not return retskp. ret ; If so return failure. getcr2: jmp rskp GETCHR ENDP ; Jumping to this location is like retskp. It assumes the instruction ; after the call is a jmp addr. RSKP PROC NEAR pop bp add bp,3 push bp ret RSKP ENDP ; Jumping here is the same as a ret. R PROC NEAR ret R ENDP code ends end