CCS-A CCS-B CCS-C C...

; File CCSCOM.ASM
include msscom.dat
include ccscom.dat
segment public 'code'
prtchr:near, clrbuf:near, outchr:near, isdev:near
sppos:near, stpos:near, biterr:near, intmsg:near
clearl:near, rppos:near, errpack:near, prtscr:near
pktcpt:near, strlen:near, pcwait:near
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:
- Type of packet (D,Y,N,S,I,R,E,F,Z,other)
PACK.SEQNUM - Packet sequence number
PACK.DATLEN - Number of data characters
; Returns: +1 always
; Packet construction areas:
Prolog (8 bytes)
;+----------------------------------------+---------------+---------------+
;| SOH,LEN,SEQ,TYPE,Xlen(2-3),Xlen chksum | packet's data | chksum,EOL,HS |
;+----------------------------------------+---------------+---------------+
; where Xlen is 2 byte (Long) or 3 byte (Extra Long) count of bytes to follow.
push save packet type (in ah)
call clear serial port input buffer
call exercise receiver
call clear serial
port input buffer
spkcnt,0 number of bytes sent in this packet
fsta.pspkt,1 statistics, count a packet being sent
fsta.pspkt+2,0
ripple carry
al, Wait spause milliseconds before
sending a packet
spk1 z = yes
to let other side get ready
dh,trans. Get the number of padding chars.
spk5 If none left proceed.
ah,trans. Get the padding char.
push save loop counter
call Output it.
spk3 failed
nop must be three bytes
get loop counter
spk2 do remaining padding chars
recover ah
prvtyp, Remember packet type
bx, Get current port structure [umd]
parmsk,0 Set parity mask for 8 bits [umd]
[bx].parflg, Using parity? [umd]
e = no. use mask as is. [umd]
parmsk,7 else set mask for 7 data bits. [umd]
spacka: call do debug display (while it's still our turn)
pktptr,offset prolog
word ptr prolog,0
word ptr prolog+2,0
word ptr prolog+4,0
word ptr prolog+6,0
al,trans. Get the start of header char.
prolog, Put SOH in the packet.
ax,pack. SEQ
al,20 ascii bias
prolog+2, store SEQ in packet
chksum, start checksum
prolog+3, store TYPE
chksum, add to checksum
; packet length type is directly governed here by length of header plus data
; field, pack.datlen, plus chksum: regular <= 94, long = 95?
spdlp7 ae = yes, recurse
push push for pop below
spdlp8: pop
get a digit
al,20 apply tochar()
[bx], store in data field
chksum, accumulate checksum for header
point to next data field byte
byte ptr[bx],0 insert terminator
spdlp8 get the rest
ax, current checksum
ax,1 put two highest bits of al into ah
ah,3 want just those two bits
al,1 put al back in place
al, add two high bits to earlier checksum
al,03 chop to lower 6 bits (mod 64)
al,20 apply tochar()
[bx], store that in length's header checksum
chksum, add that byte to running checksum
spklp5: assume soh, len, seq, type, extra len are in prolog
set es to data segment for implied es:di
si,o source
di,offset data-1 end point of destination
pktptr, start of packet ptr for debug
pack.lentyp,0 long packets?
spklp6 ne = no
si,6 long packets
cx,7 seven bytes soh,len,seq,type, xl1,xl2,xlchk
spklp6: cmp
pack.lentyp,1 extra long packets?
spklp7 ne = no
cx,8 extra long packets
spklp7: add
si,3 regular packets, slide up by four bytes
cx,4 number of bytes to move
spklp8: jcxz
spklp9 no movement needed
pktptr, pktprt=new offset of prolog section
move the protocol header, cx times
spklp9: pop
bx, place where protocol section starts
spklp10:mov
ah,[bx] protocol part
call send byte to serial port
spklp11 nc = good send
spklp11:cmp
bx, done all protocol parts yet?
spklp10 b = not yet
bx, select from given data buffer
dx,pack. Get the number of data bytes in packet.
spack2: dec
Decrement the char count.
sign = no, finish up.
al,byte ptr[bx] ; get a data char
point to next char [umd]
al,80 eighth bit set?
al, apply parity mask, may clear 8th bit [umd]
hierr,0 printed high bit error yet? [umd]
ne = yes [umd]
hierr,0FFH set err flag.
spackb: mov
chksum, add the char to the checksum [umd]
chksum,0 keep only low order 12 bits
ah, put char in ah where spkout wants it
call send it
spack2 Go get more data chars
spack3: mov
trans.chklen,2 What kind of checksum are we using?
e = 2 characters.
g = 3 characters.
ah, 1 char: get the character total.
ch, Save here too (need 'cl' for shift).
ah,0C0H Turn off all but the two high order bits.
ah, Shift them into the low order position.
ah, Add it to the old bits.
ah,3FH Turn off the two high order bits.
ah,' ' Add a space so the number is printable.
[bx], Put in the packet.
Point to next char.
call send it
Add EOL char.
spacky: mov
byte ptr[bx],0 null, to determine end of buffer.
push Don't lose our place.
bx, First checksummed character.
call Calculate the CRC.
push save the crc
ax, Manipulate it here.
ax,0F000H Get 4 highest bits.
ah, Shift them over 4 bits.
ah,' ' Make printable.
[bx], Add to buffer.
Get back checksum value.
call send it
spackx: push Save it for now.
cx,0FC0H Get bits 6-11.
ax, Shift them bits over.
al,' ' Make printable.
[bx], Add to buffer.
call send it
Get back the original.
c = bad send
cx,003FH Get bits 0-5.
cl,' ' Make printable.
[bx], Add to buffer.
call send it
spackq: RET
bad send, do ret to caller of spack
spackz: mov
ah,trans. Get the EOL the other host wants.
[bx], Put eol
call do debug display (while it's still our turn)
flags.debug,0 In debug mode?
spackz0 ne = yes
flags.capflg, log packets?
spackz1 z = no
spackz0:cmp
linecnt,0 anything on current line?
spackz1 e = no
dx, finish line with cr/lf
to log file
spackz1:mov
ah,trans. recover EOL
call send it
ax, number of bytes sent in this packet
fsta.psbyte, total bytes sent
fsta.psbyte+2,0 ; propagate carry to high word
call check console for user interrupts
no action on plain rets
return successfully
spkout: push send char in ah out the serial port
push return carry clear if success
tmp,1 retry counter
spkour: call serial port transmitter procedure
jmp bad send, retry
count number of bytes sent in this packet
carry clear for good send
spkoux: cmp
tmp,5 done 5 attempts on this char?
spkoux1 ge = yes, fail the sending
ax,10 wait 10 milliseconds
spkoux1:pop
failed to send char
set carry for bad send
; Calculate the CRC of the null-terminated string whose address is in BX.
; Returns the CRC in CX.
Destroys BX and AX.
; The CRC is based on the SDLC polynomial: x**16 + x**12 + x**5 + 1.
; By Edgar Butt
28 Oct 1987 [ebb].
crcclc: push
dx,0 Initial CRC value is 0
cl,4 Load shift count
ah,[bx] Get the next char of the string
ah,0 If null, then we're done
dl, XOR input with lo order byte of CRC
ah, Copy it
ah, Shift copy
ah, XOR to get quotient byte in ah
dl, High byte of CRC becomes low byte
dh, Initialize high byte with quotient
ax, Shift quotient byte
dl, XOR (part of) it with CRC
ax,1 Shift it again
dx, XOR it again to finish up
short crc0
cx, Return it in CX
; Receive_Packet
; This routine waits for a packet arrive from the host.
; chars until it finds a SOH.
PACK.SEQNUM - Packet sequence number
PACK.DATLEN - Number of data characters
DATA array
- data in packet
packet type (letter code)
; Packet construction areas:
Prolog (8 bytes+2 nulls)
;+----------------------------------------+---------------+---------------+
;| SOH,LEN,SEQ,TYPE,Xlen(2-3),Xlen chksum | packet's data | chksum,EOL,HS |
;+----------------------------------------+---------------+---------------+
; where Xlen is 2 byte (Long) or 3 byte (Extra Long) count of bytes to follow.
rcvd setup debug banner, if needed.
fairflg,0 set fairness flag
pktptr, where to place packet prolog material
bx,p bx = debug buffer pointer for new data
rpkcnt,0 number of bytes received in this packet
ax,0 most recently read char, initialize it
bl,flags. Remember original value
tmpflg, Store it here
parmsk,0 parity mask, assume 8 bit data
bx,portval
[bx].parflg, parity is none?
rpack0 e = none
parmsk,07 else strip parity (8th) bit
rpack0: call
debl debug, show chars received thus far
word ptr prolog,0 clear prolog and data fields
word ptr prolog+2,0
word ptr prolog+4,0
word ptr prolog+6,0
word ptr data,0
pktptr, where to place packet prolog material
bx, bx = debug buffer pointer for new data
status,stat_ assume success
inch Get a character. SOH
rpack0 failure (eol, timeout, user intervention)
rpack0b:mov
byte ptr[bx], store char in buffer
al,trans. Is the char the start of header char?
rpack0 ne = no, go until it is.
rpack1 got the SOH char from the port
rpack0a:jc
rpack0 c = hit eol from prev packet, restart
rpack6 timeout or user intervention
rpack1: mov
pktptr, if we got here from below
bx,p debug pointer
byte ptr[bx], store SOH in buffer
status,stat_ say success, in case rescanning for pkt.
call Get a character. LEN
rpack4 failure
byte ptr[bx], store LEN in buffer
al,trans. Is the char the start of header char?
rpack1 ne = no
rpack7 yes, start over
rpack1e:mov
chksum, start the checksum
al,20 unchar() to binary
pack.datlen, Save the data count (byte)
call Get a character. SEQ
rpack4 failure
byte ptr[bx], store SEQ in buffer
al,trans. Is the char the start of header char?
rpack1 nz = yes, then go start over.
al,' ' Get the real packet number.
pack.seqnum, Save the packet number. SEQ
call Get a character. TYPE
rpack4 failure
byte ptr[bx], store TYPE in buffer
al,trans. Is the char the start of header char?
rpack1 nz = yes, then go start over.
pktype, Save the message type
chksum, Add it to the checksum.
bx, Point to current port structure
[bx].ecoflg,0 Is the host echoing?
rpak11 No, packets not echoed
al, Packet type same as last sent?
rpak11 ne = no
prvtyp,0 clear to respond to next packet
rpack0 Yes, chuck echoed packet
rpak11: call get complicated data length (reg, lp, elp)
pack.datlen and kind into pack.lentyp
carry set if error
rpack1 nc = long packet checksum is ok
status,stat_ say bad checksum
rpack4 checksum failure
; 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. I and S packets always has a type 1 checksum.
b. A NAK never contains data, so its block check type is seqnum1.
prolog+3,'S' Is this an "S" packet?
rpk0 ne = no.
trans.chklen,1 S packets use one byte checksums
prolog+3,'I' I packets are like S packets
trans.chklen,1 I packets use one byte checksums
prolog+3,'N' Is this a NAK?
rpk3 ne = no.
pack.datlen,1 NAK, get length of data + chklen
rpk1 b = impossible length
pack.datlen,3 longest NAK (3 char checksum)
rpk2 be = possible
status,stat_ status = bad length
ret on impossible length
ax,pack.datlen
trans.chklen, remainder must be checksum type for NAK.
ax,pack. get length of data + chksum
al,trans. minus checksum length, for all packets
ah,0 propagate borrow
pack.datlen, store apparent length of data field
; End of change.
; now, for long packets we start the real data (after the extended byte
; count 3 or 4 bytes) at offset data and thus the checksumming starts
; such packets a few bytes earlier. [jrd]
di,offset data-1
si,offset prolog
pktptr,offset data
pack.lentyp,0 long packets?
rpk5 ne = no
cx,7 seven bytes mark...type, xl,xl,xlchk
pack.lentyp,1 extra long packets?
rpk6 ne = no
cx,8 extra long packets, no movement
si,3 regular packets, slide by four bytes
cx,4 number of bytes to move
rpk8 no movement needed
pktptr, pktptr=new offset of prolog section
push save es
set es to datas segment
move backward
move the protocol header, cx times
reset direction flag to normal
dx,pack. length of data field, excl LP header
dx,trans. longest packet we can receive
dl,trans. minus checksum length
dh,0 propagate borrow
pack.lentyp,3 Regular Packet?
rpk8 ne = no
dx,2 minus SEQ, TYPE for regular packets
dx,pack. is data field too long?
rpk8 ae = not too big
status,stat_ failure status, packet too long
rpack4 too big, quit now
bx, Point to the data buffer.
Get DATA field characters
rpack2: dec
# data chars
rpack3 s = exhausted data, go get the checksum.
call Get a character into al. DATA
rpack4 control-c, timeout (out of data), eol
byte ptr[bx], Put the char into the packet.
Point to the next character.
al,trans. Is the char the start of header char?
rpak2 nz = no
rpack7 yes, then go start over.
rpak2b: mov
chksum,0 keep only lower 12 bits
rpack2 Go get another.
rpack3: call Get a character. Start Checksum bytes
rpack4 failed
byte ptr[bx], place to store checksum, EOL, HS for debug
point at next slot
al,trans. Is the char the start of header char?
rpk3 ne = no
rpack7 yes, then go start over.
al,' ' Turn the char back into a number.
cx, current checksum
trans.chklen,2 What checksum length is in use.
e = Two character checksum.
g = Three character CRC.
cx,1 put two highest digits of al into ah
ch,3 want just those two bits
cl,1 put al back in place
cl, add two high bits to earlier checksum
cl,03 chop to lower 6 bits (mod 64)
cl, computed vs received checksum byte (binary)
rpk3 e = equal, so finish up.
status,stat_ say checksum failure
rpk3xa: jmp
rpack7: call dump debugging information so far
rpack1 For the jump out of range.
rpacky: mov
tmp, Save value from packet here.
push Three character CRC.
cx,[bx-1] save checksum char and next
word ptr[bx-1],0 ; put null at end of Data field for crc
bx, Where data for CRC is.
call Calculate the CRC and put into CX.
[bx-1], restore char pair from above
ah, cx = 16 bit binary CRC of rcv'd data
ah,0f0 Manipulate it here.
ah,1 Get 4 highest bits.
ah,1 Shift them over 4 bits.
ah, Is what we got == what we calculated?
rpky1 e = yes
status,stat_ checksum failure
call Get next character of checksum.
rpack4 Failed.
byte ptr[bx], put into buffer for debug
al,trans. Restarting?
rpack7 e = yes
al,' ' Get back real value.
rpackx: mov
tmp, Save here for now.
push Two character checksum.
cx,0FC0H Get bits 6-11.
ax, Shift them bits over.
Get back the original.
al, Are they equal?
status,stat_ checksum failure
call Get last character of checksum.
rpack4 Failed.
byte ptr[bx], put into buffer for debug
al,trans. Restarting?
rpack7 e = yes
al,' ' Get back real value.
cx,003FH Get bits 0-5.
al, Do the last chars match?
rpack4 e = yes
status,stat_ say checksum failure
rpack4: test
status,stat_ timeout?
rpack6 nz = yes
status,stat_ premature eol?
rpack4 nz = yes, try handshake
call get eol char (ok = ret with carry set)
rpack6 nc = timeout or user intervention
bx,offset data+maxpack+7 filled debug buffer yet?
rpack4 a = yes
byte ptr[bx], put into buffer for debug
rpack4e:cmp
al,trans. soh already?
rpack4 ne = no
rpack7 yes
rpack4a:and
status,not stat_ desired eol is not an error
rpack4c:push test for line turn char, if handshaking
bx,portval
ah,[bx]. get desired handshake char
[bx].hndflg,0 doing half duplex handshaking?
rpack6 e = no
tmp, keep it here
call get handshake char
rpack5 nc = timeout or user intervention
status,not stat_ ignore unexpected eol status here.
bx,offset data+maxpack+7 filled debug buffer yet?
rpack4 a = yes
byte ptr[bx], put into buffer for debug
rpack4f:cmp
al,trans. soh already?
rpack4 ne = no
rpack7 yes, do debug display and start over
rpack4d:cmp
al, compare received char with handshake
rpack4 ne = not handshake, try again til timeout
rpack5: and
status,not stat_ ignore timeouts on handshake char
rpack6: call do debug display
flags.debug,0 In debug mode?
rpack6 ne = yes
flags.capflg, log packets?
rpack6 z = no
rpack6a:cmp
linecnt,0 anything on current line?
rpack6 e = no
dx, finish line with cr/lf
to log file
rpack6b:call check console for user interrupt
status,stat_ did a timeout get us here?
rpack6 z = no
pktype,'T' yes, say 'T' type packet (timeout)
rpack6c:mov
bl, flags before rpack began
bl,flags. did flags change?
rpack6 e = no
flags.cxzflg,'C'; did user type contol-C?
rpack6 e = yes
flags.cxzflg,'E'; protocol exit request?
rpack6 ne = no
bx, user intervention message for error packet
cemsg, ccemsg
call send error message
rpack6d:mov
pack.state,'A' and move to abort state
call show interrupt msg for control-C-E
rpack6e:mov
ax, number of bytes received in this packet
fsta.prbyte, total received bytes
fsta.prbyte+2,0 ; propagate carry to high word
fsta.prpkt,1 count received packet
fsta.prpkt+2,0
ripple carry
ah, return packet type in ah
status,stat_ successful so far?
rpack6 ne = no
success exit
rpack6x:ret
failure exit
; Check Console (keyboard). Ret if "action" chars: cr for forced timeout,
; Control-E for force out Error packet, Control-C for quit work now.
; Return rskp on Control-X and Control-Z as these are acted upon by higher
; layers. Consume and ignore anything else.
chkcon: call is stdin a device and not a disk file?
chkco5 nc = no, a disk file so do not read here
ah, read console
chkco5 z = nothing there
al, carriage return?
chkco3 e = yes, simulate timeout
al,'C'-40 Control-C?
chkco1 e = yes
al,'E'-40 Control-E?
chkco1 e = yes
al,'X'-40 Control-X?
chkco4 e = yes
al,'Z'-40 Control-Z?
chkco4 record it, take no immmediate action here
al,0 scan code being returned?
ah, read and discard second byte
else unknown, read any more
chkco1: add
al,40 Make Control-C-E printable.
flags.cxzflg, Remember what we saw.
chkco2: or
status,stat_ interrupted
chkco3: or
status,stat_ cr simulates timeout
chkco4: add
al,40 make control-X-Z printable
flags.cxzflg, put into flags
do not act on them here
chkco5: cmp
flags.cxzflg,'C'; control-C intercepted elsewhere?
chkco2 e = yes
else say no immediate action needed
proc compute packet length for short & long types
returns length in pack.datlen and length
type (0, 1, 3) in pack.lentyp
returns length of
data + checksum
ax,pack. LEN from packet's second byte
ah, clear unused high byte
al,3 regular packet has 3 or larger here
getln0 b = long packet
pack.datlen,2 minus SEQ and TYPE = DATA + CHKSUM
pack.lentyp,3 store assumed length type (3 = regular)
clear carry for success
getln0: push counter for number of length bytes
pack.lentyp,0 store assumed length type 0 (long)
cx,2 two base-95 digits
al,0 is this a type 0 (long packet)?
getln5 e = yes, go find & check length data
getln1: mov
pack.lentyp,1 store length type (1 = extra long)
cx,3 three base 95 digits
al,1 is this a type 1 (extra long packet)?
getln5 e = yes, go find & check length data
set carry bit to say error (unkn len code)
chk header chksum and recover binary length
push save working reg
ax, clear length accumulator, low part
pack.datlen, clear final length too
getln7: xor
dx, ditto, high part
ax,pack. length to date
multiply accumulation (in ax) by 95
pack.datlen, save results
call read another serial port char into al
nop should do something here about failures
byte ptr[bx], store in buffer
al,20 subtract space, apply unchar()
pack.datlen, add to overall length count
getln7 cx preset earlier for type 0 or type 1
dx, get running checksum
dx,1 get two high order bits into dh
dh,3 want just these two bits
dl,1 put low order part back
dl, add low order byte to two high order bits
dl,03 chop to lower 6 bits (mod 64)
dl,20 apply tochar()
call read another serial port char
byte ptr[bx], store in buf for debug
dl, our vs their checksum, same?
unsave regs (preserves flags)
getln9 e = checksums match, success
status,stat_ checksum failure
else return carry set for error
getln9: clc
clear carry (say success)
; Get char from serial port into al, with timeout and console check.
; Ret carry clear if timeout or console char, Ret carry set if EOL seen,
; Rskp on other port chars. Fairflg allows occassional reads from console
; before looking at serial port, to avoid latchups.
timeit,0 reset timeout flag (do each char separately)
push save a reg
fairflg, look at console first every now and then
inchr1 be = not console's turn yet
call check console
inchr5 got cr or control-c/e input
fairflg,0 reset fairness flag for next time
inchr1: call Is there a serial port character to read?
inchr6 Got one (in al); else does rskp.
call check console
inchr5 got cr or control-c/e input
inchr2: cmp
flags.timflg,0 Are timeouts turned off?
inchr1 e = yes, just check for more input.
trans.stime,0 Doing time outs?
inchr1 e = no, just go check for more input.
push save regs
push Stolen from Script code.
timeit,0 have we gotten time of day for first fail?
inchr4 ne = yes, just compare times
ah, get DOS time of day
ch = hh, cl = mm, dh = ss, dl = 0.01 sec
ch, get ordering of low byte = hours, etc
word ptr rptim, hours and minutes
word ptr rptim+2, seconds and fraction
bl,trans. our desired timeout interval (seconds)
bh,0 one byte's worth
temp, work area
bx,2 start with seconds field
inchr3: mov
ax, desired timeout interval, working copy
al,rptim[bx] add current tod digit interval
dx, clear high order part thereof
compute number of minutes or hours
temp, quotient, for next time around
rptim[bx], put normalized remainder in timeout tod
look at next higher order time field
bx,0 done all time fields?
inchr3 ge = no
rptim[0],24 normalize hours
inchr3 l = not 24 hours or greater
rptim[0],24 discard part over 24 hours
inchr3a:mov
timeit,1 say have tod of timeout
inchr4: mov
ah, compare present tod versus timeout tod
get the time of day
ch, hours difference, ch = (now - timeout)
inchr4 e = same, check mmss.s
inchr4 l = we are early
ch,12 hours difference, large or small?
inchr4 ge = we are early
inchr4 l = we are late, say timeout
inchr4b:cmp
cl,rptim+1 minutes, hours match
inchr4 b = we are early
inchr4 a = we are late
dh,rptim+2 seconds, hours and minutes match
inchr4 b = we are early
inchr4 a = we are late
dl,rptim+3 hundredths of seconds, hhmmss match
inchr4 b = we are early
inchr4c:or
status,stat_ say timeout
inchr5 timeout exit
inchr4d:pop
inchr1 not timed out yet
inchr5: pop
here with console char or timeout
clear carry bit
inchr6: pop
here with char in al from port
al, apply 7/8 bit parity mask
al, null char?
inchr6 nz = no
inchr6a:jmp
ignore the null, read another char
inchr6b:cmp
al, ascii del byte?
inchr6 e = yes, ignore it too
count received byte
al,trans. eol char we want?
inchr7 e = yes, ret with carry set
char is in al
inchr7: or
status,stat_ set status appropriately
set carry to say eol seen
and return qualified failure
; sleep for the # of seconds in al
; Preserve all regs. Added console input forced timeout 21 March 1987 [jrd]
push save argument
ah, DOS tod (ch=hh, cl=mm, dh=ss, dl=.s)
get current time
restore desired # of seconds
dh, add # of seconds
sleep1: cmp
dh,60 too big for seconds?
sleep2 no, keep going
dh,60 yes, subtract a minute's overflow
and add one to minutes field
cl,60 did minutes overflow?
sleep1 no, check seconds again
cl,60 else take away an hour's overflow
add it back in hours field
sleep1 and keep checking
sleep2: mov
time, store desired ending time,
time+2, ss, .s
sleep3: call check console for user timeout override
short sleep5 have override
three bytes for rskp
ah, get time
ch,byte ptr time+1 ; hours difference, ch = (now - timeout)
sleep4 e = hours match, check mmss.s
sleep3 l = we are early
ch,12 hours difference, large or small?
sleep3 ge = we are early
sleep5 l = we are late, exit now
sleep4: cmp
cl, check minutes, hours match
sleep3 b = we are early
sleep5 a = over limit, time to exit
dx,time+2 check seconds and fraction, hhmm match
sleep3 b = we are early
sleep5: pop
Packet Debug display routines
rcvdeb: cmp
flags.debug,0 In debug mode?
rcvde1 ne = yes
flags.capflg, log packets?
rcvde1 e = yes
rcvde1: mov
debflg,'R' say receiving
snddeb: cmp
flags.debug,0 In debug mode?
sndde1 ne = yes
flags.capflg, log packets?
sndde1 yes
sndde1: mov
debflg,'S' say sending
push Debug. Packet display.
push save some regs.
flags.debug, is debug active (vs just logging)?
deb1 z = no, just logging
fmtdsp,0 non-formatted display?
deb1 e = yes, skip extra line clearing
debflg,'R' receiving?
deb1 e = yes
call spack: cursor position
call rpack: cursor position
call clear the line
dx,offset crlf
ah, display
call clear debug line and line beneath
debflg,'R' receiving?
deb1 e = yes
call reposition cursor for spack:
call reposition cursor for rpack:
dx, spack: message
debflg,'R'
deb2 ne = sending
dx, rpack: message
call record dollar terminated string in Log file
linecnt,7 number of columns used so far
; Display/log packet chars processed so far.
; Displays chars from pktptr to bx, both are pointers.
; Enter with bx = offset of next new char. All registers preserved
deblin: cmp
flags.debug,0 In debug mode?
debln0 ne = yes
flags.capflg, log packets?
debln0 nz = yes
nothing to do
debln0: push
di, starting place for debug analysis
cx, place for next new char
cx, minus where we start = number chars to do
debln5 le = nothing to do
debln2: cmp
di,offset data+maxpack+10 ; end of buffer data?
debln5 a = all done
push save loop counter
linecnt,70
debln3 b = not yet, get next data char
dx, break line with cr/lf
call and in log file
linecnt,0 setup for next line
debln3: mov
dl,byte ptr [di]; get char
dl,80 high bit set?
debln3 z = no
push save char in dl
dl,7 show tilde char for high bit set
call record in Log file
count displayed column
linecnt,70 exhausted line count yet?
debln3 b = not yet
dx, break line with cr/lf
call and in log file
linecnt,0 setup for next line
debln3a:pop
dl,7 get lower seven bits here
debln3b:cmp
dl,' ' control char?
debln4 ae = no
dl,40 uncontrollify the char
push save char in dl
dl,5 show caret before control code
call record in Log file
count displayed column
linecnt,70 exhausted line count yet?
debln3 b = not yet
dx, break line with cr/lf
call and in log file
linecnt,0 setup for next line
debln3c:pop
recover char in dl
debln4: call record char in dl in the log file
done with this char, point to next
one more column used on screen
recover loop counter
debln2 get next data char
debln5: pop
captdol proc write dollar sign terminated string in dx
to the capture file (Log file). [jrd]
push save regs
si, point to start of string
captdo1:lods get
a byte into al
al,'$' at the end yet?
captdo2 e = yes
call Log the char
short captdo1 repeat until dollar sign is encountered
captdo2:pop
captdol endp
proc record counted string, starts in di, count
is in cx. [jrd]
captc2 if count = zero, exit now
push save regs
si, get start address
captc1: lods get a char into al
call record it, cptchr is in msster.asm
captc1 do this cx times
captc2: ret
captchr proc record char in dl into the Log file
flags.debug,0 debug display active?
captch1 z = no.
display char in dl
captch1:test
flags.capflg, logging active?
captch2 z = no
al, where pktcpt wants it
call record the char, pktcpt is in msster.asm
captch2:pop
captchr endp
; Jumping to this location is like retskp.
It assumes the instruction
after the call is a jmp addr.
; Jumping here is the same as a ret.

我要回帖

更多关于 ccs link 2011a 的文章

 

随机推荐