; Kermit system dependent module for Rainbow ; Jeff Damens, July 1984 ; edit history ; install set baud command, JD 11:57pm Thursday, 29 November 1984 ; fix scrprep so that autowrap works correctly, JD 12:23am, 5 December 1984 ; save attributes as well as screen text, JD 12:26am 6 December 1984 ; Handle 132 column mode correctly, JD 12:26am Thursday, 6 December 1984 ; pop into vt100 mode when displaying escape sequences, JD, 6 December 1984 ; Made break 275 ms, thanks to Bernie Eiben, JD, 6 December 1984 public serini, serrst, clrbuf, outchr, coms, vts, dodel, public ctlu, cmblnk, locate, lclini, prtchr, dobaud, clearl, public dodisk, getbaud, beep, public count, xofsnt, puthlp, putmod, clrmod, poscur public sendbr, term, machnam, setktab, setkhlp, showkey include msdefs.h ; rainbow-dependent screen constants scrseg equ 0ee00H ; screen segment latofs equ 0ef4h ; ptrs to line beginnings, used by firmware l1ptr equ latofs ; ptr to first line llptr equ latofs+23*2 ; ptr to last line csrlin equ 0f42h ; current cursor line. curlin equ 0f43h ; current line flags wrpend equ 2 ; wrap pending... attoffs equ 1000H rmargin equ 0f57h ; right margin limit... ; rainbow-dependent firmware locations nvmseg equ 0ed00h ; segment containing NVM xmitbd equ 0a1h ; address of xmit baud rcvbd equ 0a2h ; " " receive baud autwrp equ 08dH ; b0 = 1 if auto wrap on (?) bdprt equ 06h ; baud rate port vt52mod equ 088h ; b0 = 1 if in ansi mode. ; level 1 console definitions fnkey equ 100H ; function key flag shfkey equ 200H ; shift key ctlkey equ 400H ; control key cplk equ 800H prvkey equ 23H nxtkey equ 25H brkkey equ 65H prtkey equ 3 false equ 0 true equ 1 mntrgh equ bufsiz*3/4 ; High point = 3/4 of buffer full. mnstata equ 042H ;Status/command port A mnstatb equ 043H ;Status/command port B. mndata equ 040H ;Data port. mndatb equ 041H mnctrl equ 002H ;Control port. serchn equ 0A4H ; interrupt to use serch1 equ 044H ; use this too for older rainbows. txrdy EQU 04H ;Bit for output ready. rxrdy EQU 01H ;Bit for input ready. fastcon equ 29H ; fast console handler firmwr equ 18H kcurfn equ 8h ; disable cursor rcurfn equ 0ah ; enable cursor swidth equ 132 ; screen width slen equ 24 ; screen length npgs equ 2 ; # of pages to remember stbrk equ 15 ; start sending a break enbrk equ 16 ; stop sending break. ; external variables used: ; drives - # of disk drives on system ; flags - global flags as per flginfo structure defined in pcdefs ; trans - global transmission parameters, trinfo struct defined in pcdefs ; portval - pointer to current portinfo structure (currently either port1 ; or port2) ; port1, port2 - portinfo structures for the corresponding ports ; global variables defined in this module: ; xofsnt, xofrcv - tell whether we saw or sent an xoff. ; circular buffer ptr cbuf struc pp dw ? ; place ptr in buffer bend dw ? ; end of buffer orig dw ? ; buffer origin lcnt dw 0 ; # of lines in buffer. cbuf ends ; answerback structure ans struc anspt dw ? ; current pointer in answerback ansct db ? ; count of chars in answerback ansseq dw ? ; pointer to whole answerback anslen db ? ; original length ansrtn dw ? ; routine to call. ans ends datas segment public 'datas' extrn drives:byte,flags:byte, trans:byte extrn portval:word, port1:byte, port2:byte setktab db 22 mkeyw 'F4',fnkey+5h mkeyw 'F5',fnkey+65h mkeyw 'F6',fnkey+7h mkeyw 'F7',fnkey+9h mkeyw 'F8',fnkey+0Bh mkeyw 'F9',fnkey+0Dh mkeyw 'F10',fnkey+0Fh mkeyw 'F11',esc mkeyw 'F12',bs mkeyw 'F13',lf mkeyw 'F14',fnkey+11h mkeyw 'F17',fnkey+13h mkeyw 'F18',fnkey+15h mkeyw 'F19',fnkey+17h mkeyw 'F20',fnkey+19h mkeyw 'FIND',fnkey+1bh mkeyw 'INSERTHERE',fnkey+1dh mkeyw 'REMOVE',fnkey+1fh mkeyw 'SCAN',-1 mkeyw 'SELECT',fnkey+21h ourflgs db 0 ; our flags fpscr equ 80H ; flag definitions... crlf db cr,lf setkhlp db ' F4 ... F20 or SCAN$' machnam db 'Rainbow$' nyimsg db cr,lf,'Not yet implemented$' badbdmsg db cr,lf,'?Unsupported baud rate$' delstr db BS,' ',BS,'$' ; Delete string. clrlin db cr,'$' ; Clear line (just the cr part). oldser dw ? ; old serial handler oldseg dw ? ; segment of above old1ser dw ? ; old serial handler, alternate address old1seg dw ? ; segment of same. portin db 0 ; Has comm port been initialized. xofsnt db 0 ; Say if we sent an XOFF. xofrcv db 0 ; Say if we received an XOFF. iobuf db 5 dup (?) ; buffer for ioctl phbuf db swidth dup (?) gopos db esc,'[' rowp db 20 dup (?) clrseq db esc,'[H',esc,'[J$' ceolseq db esc,'[K$' invseq db esc,'[7m$' nrmseq db esc,'[0m$' ivlatt db swidth dup (0fH) ; a line's worth of inverse attribute ; special keys. spckey dw prvkey,nxtkey,brkkey,prtkey,prtkey+ctlkey,prvkey+ctlkey dw nxtkey+ctlkey,brkkey+ctlkey spclen equ ($-spckey)/2 ; special key handlers. Must parallel spckey spchnd dw prvscr,nxtscr,sendbr,prtscr,togprt,prvlin,nxtlin,sendbr ; arrow and PF keys arrkey db 27H,29H,2bH,2dH,59H,5cH,5fH,62H arrlen equ $-arrkey ; translations for arrow and PF keys, must parallel arrkey arrtrn dw uptrn,dntrn,rgttrn,lfttrn dw pf1trn,pf2trn,pf3trn,pf4trn ; keypad keys keypad db 2fh,32h,35h,38h,3bh,3eh,41h,44h,47h,4ah,4dh,50h,53h,56h keypln equ $-keypad ; keytrn and altktrn must parallel keypad keytrn db '0123456789-,.',cr altktrn db 'pqrstuvwxymlnM' keyptr dw keytrn ; pointer to correct translation table akeyflg db 0 ; non-zero if in alt keypad mode. ; arrow and PF key translations uptrn db 3,esc,'[A' dntrn db 3,esc,'[B' rgttrn db 3,esc,'[C' lfttrn db 3,esc,'[D' pf1trn db 3,esc,'OP' pf2trn db 3,esc,'OQ' pf3trn db 3,esc,'OR' pf4trn db 3,esc,'OS' ourarg termarg <> ; variables for serial interrupt handler source db bufsiz DUP(?) ; Buffer for data from port. srcpnt dw 0 ; Pointer in buffer (DI). count dw 0 ; Number of chars in int buffer. savesi dw 0 ; Save SI register here. telflg db 0 ; non-zero if we're a terminal. NRU. respkt db 10 dup (?) ; ioctl packet ivec dw tranb ; transmit empty B dw tranb ; status change B dw tranb ; receive b dw tranb ; special receive b dw stxa ; transmit empty a dw sstata ; status change a dw srcva ; receive a dw srcva ; special receive a ; baud rate definitions ; position in table is value programmed into baud rate port, value ; is our baud rate constant bdtab db b0050,b0075,b0110,b01345,b0150,0ffh,b0300,b0600 db b1200,b1800,b2000,b2400,0ffh,b4800,b9600,b19200 bdsiz equ $-bdtab ; multi-screen stuff bsize equ swidth*2*slen*npgs ; # of bytes needed to store screens tbuf db bsize dup (?) bbuf db bsize dup (?) ; top and bottom buffers topbuf cbuf botbuf cbuf tlbuf db swidth*2 dup (?) ; top line temp buffer blbuf db swidth*2 dup (?) ; bottom line temp buffer rlbuf db swidth*2 dup (?) ; line temp buffer prbuf db swidth dup (?) ; print temp buffer topdwn db esc,'[H',esc,'M$' ; go to top, scroll down botup db esc,'[24;0H',esc,'D$' ; go to bottom, scroll up curinq db esc,'[6n$' ; cursor inquiry posbuf db 20 dup (?) ; place to store cursor position gtobot db esc,'[24;0H$' ; go to bottom of screen. ourscr db slen*swidth dup (?) ourattr db slen*swidth dup (?) ; storage for screen and attributes inited db 0 ; terminal handler not inited yet. dosmsg db '?Must be run in version 2.05 or higher$' anssq1 db esc,'[c' ansln1 equ $-anssq1 anssq2 db esc,'Z' ansln2 equ $-anssq2 eakseq db esc,'=' dakseq db esc,'>' crsseq db esc,'c' ansbk1 ans ; two answerbacks ansbk2 ans ansbk3 ans ; enable alt keypad ansbk4 ans ; disable alt keypad ansbk5 ans ; crash sequence (!) ansret db esc,'[?6c' ansrln equ $-ansret shkbuf db 300 dup (?) ; room for definition shkmsg db ' Scan code: ' shkmln equ $-shkmsg shkms1 db cr,lf,' Definition: ' shkm1ln equ $-shkms1 datas ends code segment public extrn comnd:near, dopar:near assume cs:code,ds:datas ; local initialization routine, called by Kermit initialization. lclini proc near ; make sure this is DOS version 2.05 or higher... mov ah,dosver int dos xchg al,ah ; put major version in ah, minor in al cmp ax,205H ; is it 2.05? jae lclin1 ; yes, go on mov dx,offset dosmsg call tmsg mov ax,4c00H ; exit(0) int dos lclin1: mov flags.vtflg,0 ; turn off heath emulation ret lclini endp ; this is called by Kermit initialization. It checks the ; number of disks on the system, sets the drives variable ; appropriately. The only problem is that a value of two ; is returned for single drive systems to be consistent ; with the idea of the system having logical drives A and ; B. Returns normally. DODISK PROC NEAR mov ah,gcurdsk ; Current disk value to AL. int dos mov dl,al ; Put current disk in DL. mov ah,seldsk ; Select current disk. int dos ; Get number of drives in AL. mov drives,al ret DODISK ENDP ; show the definition of a key. The terminal argument block (which contains ; the address and length of the definition tables) is passed in ax. ; Returns a string to print in AX, length of same in CX. ; Returns normally. showkey proc near push es push ax ; save the ptr cld showk1: mov di,6 ; get level one char int firmwr cmp cl,0ffH jne showk1 ; wait until char available mov bx,ds mov es,bx ; address data segment and ax,not cplk ; no caps lock push ax ; remember scan code mov di,offset shkbuf mov si,offset shkmsg mov cx,shkmln rep movsb ; copy in initial message call nout ; write out scan code mov si,offset shkms1 mov cx,shkm1ln ; second message rep movsb pop ax ; get scan code back pop bx ; and terminal arg block mov cx,[bx].klen ; and length jcxz showk2 ; no table, not defined push di ; remember output ptr mov di,[bx].ktab ; get key table repne scasw ; search for a definition for this mov si,di ; remember result ptr pop di ; get output ptr back jne showk2 ; not defined, forget it sub si,[bx].ktab ; compute offset from beginning sub si,2 ; minus 2 for pre-increment add si,[bx].krpl ; get index into replacement table mov si,[si] ; pick up replacement mov cl,[si] ; get length mov ch,0 inc si rep movsb ; copy into buffer showk2: mov ax,offset shkbuf ; this is buffer mov cx,di sub cx,ax ; length pop es ret ; and return showkey endp ; Clear the input buffer. This throws away all the characters in the ; serial interrupt buffer. This is particularly important when ; talking to servers, since NAKs can accumulate in the buffer. ; Returns normally. CLRBUF PROC NEAR cli mov ax,offset source mov srcpnt,ax mov savesi,ax mov count,0 sti ret CLRBUF ENDP ; Clear to the end of the current line. Returns normally. CLEARL PROC NEAR mov dx,offset ceolseq ; clear sequence jmp tmsg CLEARL ENDP ; Put the char in AH to the serial port. This assumes the ; port has been initialized. Should honor xon/xoff. Skip returns on ; success, returns normally if the character cannot be written. outchr: mov bp,portval cmp ds:[bp].floflg,0 ; Are we doing flow control. je outch2 ; No, just continue. xor cx,cx ; clear counter outch1: cmp xofrcv,true ; Are we being held? jne outch2 ; No - it's OK to go on. loop outch1 ; held, try for a while mov xofrcv,false ; timed out, force it off and fall thru. outch2: push dx ; Save register. sub cx,cx mov al,ah ; Parity routine works on AL. call dopar ; Set parity appropriately. mov ah,al ; Don't overwrite character with status. mov dx,mnstata ; port status register outch3: in al,dx test al,txrdy ; Transmitter ready? jnz outch4 ; Yes loop outch3 jmp outch5 ; Timeout outch4: mov al,ah ; Now send it out mov dx,mndata out dx,al pop dx jmp rskp outch5: pop dx ret ; This routine blanks the screen. Returns normally. CMBLNK PROC NEAR mov dx,offset clrseq ; clear screen sequence jmp tmsg CMBLNK ENDP ; Locate; homes the cursor. Returns normally. LOCATE PROC NEAR mov dx,0 ; Go to top left corner of screen. jmp poscur LOCATE ENDP ; write a line in inverse video at the bottom of the screen... ; the line is passed in dx, terminated by a $. Returns normally. putmod proc near push dx ; preserve message mov dx,24 * 100H ; line 24 call poscur mov dx,offset invseq ; put into inverse video call tmsg pop dx call tmsg ; print the message mov dx,offset nrmseq ; normal videw call tmsg ret ; and return putmod endp ; clear the mode line written by putmod. Returns normally. clrmod proc near mov dx,24 * 100H call poscur call clearl ret clrmod endp ; Put a help message on the screen. This one uses reverse video... ; pass the message in ax, terminated by a null. Returns normally. puthlp proc near push ax mov dx,slen * 100H ; go to bottom line call poscur pop ax push es mov bx,ds mov es,bx ; address data segment mov si,ax ; convenient place for this mov bx,101H ; current line/position puthl1: mov di,offset phbuf ; this is destination xor cx,cx ; # of chars in the line puthl2: lodsb ; get a byte cmp al,cr ; carriage return? je puthl2 ; yes, ignore it cmp al,lf ; linefeed? je puthl3 ; yes, break the loop cmp al,0 je puthl3 ; ditto for null dec cx ; else count the character stosb ; deposit into the buffer jmp puthl2 ; and keep going puthl3: add cx,80 ; this is desired length of the whole mov al,' ' rep stosb ; fill the line push bx push si push es ; firmware likes to eat this one mov ax,0 ; send chars and attributes mov cx,80 ; this is # of chars to send mov dx,offset ivlatt ; this are attributes to send mov si,offset phbuf ; the actual message mov di,14H ; send direct to screen mov bp,ds ; need data segment as well int firmwr ; go send it pop es pop si pop bx ; restore everything inc bx ; next line cmp byte ptr [si-1],0 ; were we ended by a 0 last time? jne puthl1 ; no, keep looping pop es ; else restore this ret ; and return puthlp endp ; Set the baud rate for the current port, based on the value ; in the portinfo structure. Returns normally. DOBAUD PROC NEAR mov bx,portval mov ax,[bx].baud ; get desired baud rate mov di,offset bdtab mov cx,bdsiz repne scasb ; hunt for baud rate jne doba1 ; not found, forget it sub di,offset bdtab+1 ; this is baud rate mov ax,di mov bl,al mov cl,4 shl bl,cl ; shift constant into high nibble as well or al,bl out bdprt,al ; write into port or al,0f0h ; turn on high nibble push es mov bx,nvmseg mov es,bx mov es:[xmitbd],al mov es:[rcvbd],al ; set baud in nvm pop es ret doba1: mov dx,offset badbdmsg call tmsg jmp getbaud ; reset baud and return DOBAUD ENDP ; Get the current baud rate from the serial card and set it ; in the portinfo structure for the current port. Returns normally. ; This is used during initialization. GETBAUD PROC NEAR push es mov ax,nvmseg mov es,ax mov bl,es:[xmitbd] ; get xmit baud rate pop es and bl,0fh ; only low nibble is used mov bh,0 mov al,bdtab[bx] ; get baud rate value mov bx,portval mov ah,0 mov [bx].baud,ax ; set value ret ; and return GETBAUD ENDP ; skip returns if no character available at port, ; otherwise returns with char in al, # of chars in buffer in dx. PRTCHR PROC NEAR call chkxon ; see if we have to xon the host. cmp count,0 jnz prtch2 jmp rskp ; No data - check console. prtch2: mov si,savesi lodsb ; get a byte cmp si,offset source + bufsiz ; bigger than buffer? jb prtch1 ; no, keep going mov si,offset source ; yes, wrap around prtch1: dec count mov savesi,si mov dx,count ; return # of chars in buffer ret PRTCHR ENDP ; local routine to see if we have to transmit an xon chkxon proc near push bx mov bx,portval cmp [bx].floflg,0 ; doing flow control? je chkxo1 ; no, skip all this cmp xofsnt,false ; have we sent an xoff? je chkxo1 ; no, forget it cmp count,mntrgh ; below trigger? jae chkxo1 ; no, forget it mov ax,[bx].flowc ; ah gets xon call outchr ; send it nop nop nop ; in case it skips mov xofsnt,false ; remember we've sent an xon. chkxo1: pop bx ; restore register ret ; and return chkxon endp ; Send a break out the current serial port. Returns normally. SENDBR PROC NEAR push bx push cx push dx push ax mov ah,ioctl mov al,3 ; write to control channel. mov bx,3 ; aux port handle mov dx,offset iobuf mov iobuf,stbrk ; start sending a break int dos mov ax,275 ; # of ms to wait call rbwait ; hold break for desired interval mov ah,ioctl mov al,3 mov bx,3 mov dx,offset iobuf mov iobuf,enbrk ; stop sending the break int dos pop ax pop dx pop cx pop bx ret ; And return. SENDBR ENDP ; wait for the # of milliseconds in ax ; thanks to Bernie Eiben for this one. rbwait proc near mov cx,240 ; inner loop counter for 1 millisecond rbwai1: sub cx,1 ; inner loop takes 20 clock cycles jnz rbwai1 dec ax ; outer loop counter jnz rbwait ; wait another millisecond ret rbwait endp ; Position the cursor according to contents of DX: ; DH contains row, DL contains column. Returns normally. POSCUR PROC NEAR add dx,101H ; start at 1,1 push es push dx cld mov ax,ds mov es,ax ; address right segment mov di,offset rowp mov al,dh ; row comes first mov ah,0 call nout mov al,';' stosb ; separated by a semi pop dx mov al,dl mov ah,0 call nout mov al,'H' stosb ; end w/H mov byte ptr [di],'$' ; and dollar sign mov dx,offset gopos call tmsg pop es ret POSCUR ENDP ; Delete a character from the terminal. This works by printing ; backspaces and spaces. Returns normally. DODEL PROC NEAR mov dx,offset delstr ; Erase weird character. jmp tmsg DODEL ENDP ; Move the cursor to the left margin, then clear to end of line. ; Returns normally. CTLU PROC NEAR mov dx,offset clrlin ; this just goes to left margin... call tmsg jmp clearl ; now clear line CTLU ENDP ; set the current port. COMS PROC NEAR mov dx,offset nyimsg jmp tmsg COMS ENDP ; Set heath emulation on/off. VTS PROC NEAR mov dx,offset nyimsg jmp tmsg VTS ENDP ; initialization for using serial port. This routine performs ; any initialization necessary for using the serial port, including ; setting up interrupt routines, setting buffer pointers, etc. ; Doing this twice in a row should be harmless (this version checks ; a flag and returns if initialization has already been done). ; SERRST below should restore any interrupt vectors that this changes. ; Returns normally. SERINI PROC NEAR push es cmp portin,0 ; Did we initialize port already? [21c] jne serin0 ; Yes, so just leave. [21c] cli ; Disable interrupts cld ; Do increments in string operations xor ax,ax ; Address low memory mov es,ax mov ax,es:[4*serchn] ; get old serial handler mov oldser,ax ; save. mov ax,es:[4*serchn+2] ; get segment mov oldseg,ax ; save segment as well mov ax,es:[4*serch1] ; this is alternate for older rainbows mov old1ser,ax mov ax,es:[4*serch1+2] mov old1seg,ax ; pretty silly, huh? mov ax,offset serint ; point to our routine mov word ptr es:[4*serchn],ax ; point at our serial routine mov word ptr es:[4*serch1],ax ; have to set both of these mov es:[4*serchn+2],cs ; our segment mov es:[4*serch1+2],cs mov al,030h ;[DTR] enable RTS and DTR out mnctrl,al ;[DTR] mov portin,1 ; Remember port has been initialized. call clrbuf ; Clear input buffer. sti ; Allow interrupts serin0: pop es ret ; We're done. SERINI ENDP ; this is used to by serini prtset proc near lodsb ; get a byte or al,al jz prtse1 ; end of table, stop here out dx,al ; else send it out jmp prtset ; and keep looping prtse1: ret ; end of routine prtset endp ; Reset the serial port. This is the opposite of serini. Calling ; this twice without intervening calls to serini should be harmless. ; Returns normally. SERRST PROC NEAR push es ; preserve this cmp portin,0 ; Reset already? je srst1 ; Yes, just leave. cli ; Disable interrupts xor ax,ax mov es,ax ; address segment 0 mov ax,oldser mov es:[4*serchn],ax mov ax,oldseg mov es:[4*serchn+2],ax mov ax,old1ser mov es:[4*serch1],ax mov ax,old1seg mov es:[4*serch1+2],ax ; restore old handlers mov portin,0 ; Reset flag. srst1: pop es ret ; All done. SERRST ENDP ; serial port interrupt routine. This is not accessible outside this ; module, handles serial port receiver interrupts. serint PROC NEAR push bx push dx push ax push es push di push ds push bp push cx cld mov ax,seg datas mov ds,ax ; address data segment mov es,ax mov di,srcpnt ; Registers for storing data. mov dx,mnstatb ; Asynch status port. mov al,0 ; innocuous value out dx,al ; send out to get into a known state... mov al,2 ; now address register 2 out dx,al in al,dx ; read interrupt cause cmp al,7 ; in range? ja serin7 ; no, just dismiss (what about reset error?) mov bl,al shl bl,1 ; double for word index mov bh,0 call ivec[bx] ; call appropriate handler serin7: mov dx,mnstata ; reload port address mov al,38H out dx,al ; tell the port we finished with the interrupt pop cx pop bp pop ds pop di pop es pop ax pop dx pop bx intret: iret ; handler for serial receive, port A srcva: mov dx,mnstata mov al,0 out dx,al ; put into known state... in al,dx test al,rxrdy ; Data available? jnz srcva1 ; yes, go read it jmp srcva7 srcva1: mov al,30H ; reset any errors out dx,al mov dx,mndata in al,dx ; read the character cmp telflg,0 ; File transfer or terminal mode? jz srcva2 and al,7FH ; Terminal mode (7 bits only). srcva2: or al,al jz srcva7 ; Ignore nulls. cmp al,7FH ; Ignore rubouts, too. jz srcva7 mov ah,al and ah,7fH ; only consider low-order 7 bits for flow ctl. mov bp,portval cmp ds:[bp].floflg,0 ; Doing flow control? je srcva4 ; Nope. mov bx,ds:[bp].flowc ; Flow control char (BH = XON, BL = XOFF). cmp ah,bl ; Is it an XOFF? jne srcva3 ; Nope, go on. mov xofrcv,true ; Set the flag. jmp short srcva7 srcva3: cmp ah,bh ; Get an XON? jne srcva4 ; No, go on. mov xofrcv,false ; Clear our flag. jmp srcva7 srcva4: stosb cmp di,offset source + bufsiz jb srcva5 ; not past end... mov di,offset source ; wrap buffer around srcva5: mov srcpnt,di ; update ptr inc count cmp ds:[bp].floflg,0 ; Doing flow control? je srcva7 ; No, just leave. cmp xofsnt,true ; Have we sent an XOFF? je srcva7 ; Yes. cmp count,mntrgh ; Past the high trigger point? jbe srcva7 ; No, we're within our limit. mov ah,bl ; Get the XOFF. call outchr ; Send it. nop nop nop ; ignore failure. mov xofsnt,true ; Remember we sent it. srcva7: ret ; The interrupt is for the 'B' port - transfer control to ; the original handler and hope for the best. tranb: pushf ; put flags on stack to simulate interrupt call dword ptr [old1ser] ; call old handler ret ; and return stxa: mov dx,mnstata mov al,28H ; reset transmit interrupt out dx,al ret sstata: mov dx,mnstata mov al,10H ; reset status interrupt out dx,al ret SERINT ENDP ; Produce a short beep. The PC DOS bell is long enough to cause a loss ; of data at the port. Returns normally. BEEP PROC NEAR mov dl,bell mov ah,conout int dos ret BEEP ENDP ; put the number in ax into the buffer pointed to by di. Di is updated nout proc near mov dx,0 ; high order is always 0. mov bx,10 div bx ; divide to get digit push dx ; save remainder digit or ax,ax ; test quotient jz nout1 ; zero, no more of number call nout ; else call for rest of number nout1: pop ax ; get digit back add al,'0' ; make printable stosb ; drop it off ret ; and return nout endp term proc near mov si,ax ; this is source mov di,offset ourarg ; place to store arguments mov ax,ds mov es,ax ; address destination segment mov cx,size termarg cld rep movsb ; copy into our arg blk cmp inited,0 ; inited yet? jz term1 ; no, keep going test ourarg.flgs,scrsam ; do they want us to leave it alone? jnz term1 ; yes, skip redisplay. call rstscr ; restore screen term1: mov inited,1 ; remember inited term2: call prtchr jmp short term3 ; have a char... nop nop jmp short term6 ; no char, go on term3: and al,7fh ; turn off parity for terminal mov bx,offset ansbk1 ; check 1st answerback call ansbak ; check for answerback mov bx,offset ansbk2 ; maybe second answerback call ansbak ; should probably loop thru a table here... mov bx,offset ansbk3 call ansbak mov bx,offset ansbk4 call ansbak mov bx,offset ansbk5 call ansbak push ax call scrprep ; need to save top line pop ax push ax int fastcon ; go print it pop ax test ourarg.flgs,capt ; capturing output? jz term5 ; no, forget it push ax call ourarg.captr ; else call the routine pop ax term5: test ourflgs,fpscr ; print screen toggled on? jz term6 ; no, keep going mov dl,al mov ah,lstout ; printer output int dos term6: mov di,6 ; get level 1 character push es int firmwr pop es ; don't let firmware steal registers. cmp cl,0ffh ; character available? je term7 ; no, do something else cmp cl,1 ; maybe level 2 sequence around jne term2 ; no, forget it mov di,2 ; get level 2 character push es int firmwr pop es cmp cl,0ffh ; did we really get one? jne term2 ; no, something strange happening. jmp term6 ; else skip and keep trying. term7: test ax,fnkey ; function-type key? jnz term8 ; yes, can't be escape character cmp al,ourarg.escc ; escape char? je term9 ; yes, exit term8: call trnout ; perform necessary translations, output char jmp term2 ; and loop around term9: call savscr ; save screen ret ; and return term endp ; enter with current terminal character in al, answerback ptr in bx. ; calls answerback routine if necessary. ; This can be used to make the emulator recognize any sequence. ansbak proc near push ax ; preserve this mov si,[bx].anspt ; get current pointer cmp al,[si] ; is it correct? jne ansba1 ; no, reset pointers and go on inc [bx].anspt ; increment pointer dec [bx].ansct ; decrement counter jnz ansba2 ; not done, go on push bx call [bx].ansrtn ; send answerback pop bx ansba1: mov ax,[bx].ansseq ; get original sequence mov [bx].anspt,ax mov al,[bx].anslen ; and length mov [bx].ansct,al ansba2: pop ax ret ansbak endp ; send the answerback message. sndans proc near mov si,offset ansret ; this is what we say mov cx,ansrln ; length of same sndan1: lodsb ; get a byte mov ah,al push si push cx call outchr nop nop nop pop cx pop si loop sndan1 ret sndans endp ; enable alternate keypad mode enaaky proc near mov akeyflg,1 ; remember alternate mode mov keyptr,offset altktrn ; set correct translate table ret enaaky endp ; disable alternate keypad mode deaaky proc near mov akeyflg,0 mov keyptr,offset keytrn ret deaaky endp ; send a space so the firmware doesn't see bad escape sequences sndspc proc near mov al,' ' int fastcon ret sndspc endp ; enter with char and flags in ax. Does any necessary character translations, ; then outputs character trnout proc near and ax,not cplk ; forget about caps lock key test ourarg.flgs,havtt ; any translate table? jz trnou2 ; no, just output normally mov cx,ourarg.klen mov di,ourarg.ktab ; get redefined keys repne scasw ; look for this one jne trnou2 ; not found, try something else sub di,ourarg.ktab sub di,2 ; get index add di,ourarg.krpl ; get translation address mov si,[di] ; this is translation mov cl,[si] inc si ; pick up length, increment past it mov ch,0 jcxz trnou6 ; no translation, just return trnou1: lodsb ; get a char push si push cx call sndhst ; send the character pop cx pop si loop trnou1 ; loop thru rest of translation ret ; and return trnou2: test ax,fnkey ; function key? jz trnou5 ; no, keep going and ax,not fnkey ; turn off function bit. mov di,offset spckey ; our special keys mov cx,spclen ; length of special key table repne scasw ; look for it in our table jne trnou3 ; not found, maybe arrow key... sub di,offset spckey+2 ; get index call spchnd[di] ; call appropriate handler ret ; and return trnou3: mov di,offset arrkey ; look for an arrow-type key... mov cx,arrlen ; length of arrow key table repne scasb ; is it an arrow key? jne trnou4 ; no, forget it sub di,offset arrkey+1 ; get index into table shl di,1 ; double for word index mov si,arrtrn[di] ; get translation mov cl,[si] inc si mov ch,0 jmp trnou1 ; go send translation trnou4: mov di,offset keypad ; look for a keypad key. mov cx,keypln repne scasb ; is it in keypad? jne trnou6 ; no, forget it sub di,offset keypad+1 add di,keyptr ; index into correct translation table mov al,[di] ; get translation cmp akeyflg,0 ; in alternate keypad mode? je trnou5 ; no, just send the char push ax ; else save the character mov al,esc call sndhst mov al,'O' call sndhst ; send prefix pop ax ; get the character back and fall thru... trnou5: call sndhst ; send the character trnou6: ret trnout endp ; handle the print screen key prtscr proc near push ds ; save data segment mov ax,scrseg mov ds,ax ; address screen segment mov cx,slen ; # of lines on screen mov bx,0 ; current line # prtsc1: push cx ; save counter push bx ; and line ptr mov si,ds:[latofs+bx] ; get ptr to line mov cx,swidth ; max # of chars/line mov di,offset prbuf ; print buffer prtsc2: lodsb ; get a byte or al,al ; is it a null? jne prtsc3 ; no, go on mov al,' ' ; yes, replace by space prtsc3: stosb ; drop it off cmp al,' ' ; is it a space? je prtsc4 ; yes, go on mov dx,cx ; else remember count at last non-space prtsc4: cmp al,0ffH ; end of line? loopne prtsc2 ; continue if not end mov cx,dx ; count at last non-space, plus 1 neg cx add cx,swidth+1 ; figure out # of chars to print mov dx,offset prbuf push ds ; save this temporarily mov ax,es mov ds,ax ; address data segment to print jcxz prtsc5 ; 0 length, keep going mov bx,4 ; standard printer device mov ah,writef2 ; write call int dos ; write to the printer prtsc5: mov ah,writef2 mov bx,4 mov dx,offset crlf mov cx,2 int dos ; follow line with a crlf pop ds pop bx pop cx ; restore counters add bx,2 ; point to next line loop prtsc1 ; and keep going pop ds ; restore registers ret ; and return prtscr endp ; toggle print flag... togprt proc near xor ourflgs,fpscr ; toggle flag ret ; and return togprt endp ; Send a character to the host, handle local echo sndhst proc near push ax ; save the character mov ah,al call outchr nop nop nop pop ax test ourarg.flgs,lclecho ; echoing? jz sndhs2 ; no, exit push ax call scrprep pop ax int fastcon sndhs2: ret ; and return sndhst endp ; print a message to the screen. Returns normally. ; also puts the terminal into vt100 mode so our escape sequences work... tmsg proc near push es push bx mov bx,nvmseg mov es,bx ; address firmware mov bl,0f1h ; turn on vt100 mode xchg bl,es:[vt52mod] ; remember old mode mov ah,prstr int dos mov es:[vt52mod],bl ; restore mode pop bx pop es ret tmsg endp ; save the screen for later savscr proc near push ds call kilcur ; turn off cursor mov ax,scrseg mov ds,ax mov cx,slen ; # of lines to do mov bx,0 ; current line # mov di,offset ourscr ; place to save screen mov dx,offset ourattr ; and to save attributes savsc1: push cx ; save current count mov si,ds:[latofs+bx] ; get line ptr mov cx,swidth ; # of chars/line rep movsb ; copy it out mov si,ds:[latofs+bx] add si,attoffs ; this is where attributes start xchg dx,di ; this holds attribute ptr mov cx,swidth ; # of attrs to move rep movsb xchg dx,di pop cx ; restore counter add bx,2 ; increment line ptr loop savsc1 ; save all lines and attributes pop ds call rstcur ; put cursor back call savpos ; might as well save cursor pos ret savscr endp ; restore the screen saved by savscr rstscr proc near call cmblnk ; start by clearing screen mov si,offset ourscr ; point to saved screen mov dx,offset ourattr ; and attributes mov cx,slen ; # of lines/screen mov bx,101H ; start at top left corner rstsc1: push bx push cx push si ; save ptrs push dx mov ax,si ; this is source call prlina ; print the line pop dx pop si pop cx pop bx add si,swidth ; point to next line add dx,swidth ; and next attributes inc bx ; address next line loop rstsc1 ; keep restore lines call rstpos ; don't forget position ret rstscr endp ; circular buffer management for screen. ; for these to work correctly, the buffer size MUST be a multiple ; of the screen width. ; put a line into the circular buffer. Pass the buffer structure ; in bx, the pointer to the line in ax. putcirc proc near push si push di push cx push dx mov di,[bx].pp ; pick up buffer ptr add di,swidth*2 ; increment to next avail slot cmp di,[bx].bend ; past end? jb putci1 ; no, leave alone mov di,[bx].orig ; else start at beginning putci1: mov [bx].pp,di ; update ptr mov si,ax ; this is source mov cx,swidth*2 rep movsb ; copy into buffer cmp [bx].lcnt,npgs*slen ; can we increment it? jae putci2 ; no, keep going inc [bx].lcnt ; else count this line putci2: pop dx pop cx pop di pop si ; restore registers ret putcirc endp ; get a line from the circular buffer, removing it from the buffer. ; returns with carry on if the buffer is empty. ; pass the buffer structure in bx, the buffer to copy the line into ; in ax. getcirc proc near push si push di push cx push dx cmp [bx].lcnt,0 ; any lines in buffer? jne getci1 ; yes, ok to take one out. stc ; else set carry jmp short getcir3 ; and return getci1: mov si,[bx].pp ; this is source mov di,ax ; this is dest mov cx,swidth*2 ; # of chars to copy rep movsb mov si,[bx].pp ; get ptr again sub si,swidth*2 ; move back cmp si,[bx].orig ; compare to origin jae getcir2 ; still in range, continue mov si,[bx].bend ; else use end of buffer sub si,swidth*2-1 ; minus length of a piece getcir2:mov [bx].pp,si ; update ptr dec [bx].lcnt ; decrement # of lines in buffer clc ; make sure no carry getcir3:pop dx pop cx pop di pop si ret getcirc endp ; prepares for scrolling by saving the top line in topbuf. scrprep proc near push ds ; preserve data segment push es mov bp,scrseg mov ds,bp ; address screen segment cmp al,cr ; carriage return? je scrpr3 ; yes, will never change line cmp al,lf ; outputting a linefeed? je scrpr2 ; yes, will change line test byte ptr [ds:curlin],wrpend ; wrap pending? jz scrpr3 ; no, forget it mov ax,nvmseg mov es,ax test byte ptr [es:autwrp],1 ; auto-wrap mode? jz scrpr3 ; no, forget this ; about to change lines, see if bottom line scrpr2: cmp byte ptr [ds:csrlin],slen ; are we at the bottom? je scrpr4 ; yes, have to save line scrpr3: pop es pop ds ; get here if not saving line ret scrpr4: pop es pop ds ; restore registers ; alternate entry that doesn't check if we're on the bottom row. savtop: call kilcur ; kill cursor push es push ds mov ax,ds mov es,ax mov ax,scrseg mov ds,ax ; address screen segment mov si,ds:word ptr [l1ptr] ; get ptr to top line mov di,offset tlbuf ; this is where it goes mov cx,swidth ; # of bytes to copy rep movsb ; get the top line mov si,ds:word ptr [l1ptr] add si,attoffs ; add offset of attributes mov cx,swidth rep movsb ; get top line's attributes pop ds pop es ; restore segments mov bx,offset topbuf ; top buffer ptr mov ax,offset tlbuf ; this is where line is now call putcirc ; put into circular buffer call rstcur ret ; and return scrprep endp ; get the screen's bottom line into the buffer in ax. getbot proc near call kilcur ; kill cursor push es push ds push ax mov ax,ds mov es,ax mov ax,scrseg mov ds,ax mov si,ds:word ptr [llptr] ; get ptr to bottom line pop di ; destination is on stack mov cx,swidth ; # of bytes to copy rep movsb ; get the top line mov si,ds:word ptr [llptr] ; get ptr again add si,attoffs mov cx,swidth rep movsb ; copy attributes as well. pop ds ; restore segments pop es call rstcur ; restore cursor ret getbot endp ; handle the previous screen button... prvscr proc near mov ax,offset tlbuf mov bx,offset topbuf call getcirc jc prvsc3 ; no lines, forget it call savpos ; save cursor position mov ax,offset botbuf ; place to put screen mov bx,slen ; else just use last line on screen mov dx,-1 ; move backwards call rolscr ; save current screen call cmblnk ; clear screen mov cx,slen ; # of lines per screenfull prvsc1: mov bl,cl ; this is current line mov bh,1 ; this is column mov ax,offset tlbuf ; where to get the line from mov dx,offset tlbuf+swidth ; this is where attributes should be push cx ; save count call prlina ; put the line on the screen pop cx ; restore count cmp cx,1 jle prvsc2 ; no more to do, don't take more from buffer! push cx mov ax,offset tlbuf mov bx,offset topbuf call getcirc ; get another line pop cx jc prvsc2 ; no more, exit loop loop prvsc1 ; loop for all lines prvsc2: call rstpos ; restore screen position prvsc3: ret ; and return prvscr endp ; handle the next screen button... nxtscr proc near mov ax,offset tlbuf mov bx,offset botbuf call getcirc ; get a line from the bottom jc nxtsc3 ; no lines, forget it call savpos ; save cursor pos mov ax,offset topbuf ; place to put screen mov bx,1 ; start with first line mov dx,1 ; move backwards call rolscr ; save current screen call cmblnk ; clear screen mov cx,slen ; # of lines per screenfull nxtsc1: mov bl,slen+1 sub bl,cl ; this is current line mov bh,1 ; this is column mov ax,offset tlbuf ; where to get the line from mov dx,offset tlbuf+swidth ; this is where attributes are push cx ; save count call prlina ; put the line on the screen pop cx cmp cx,1 jle nxtsc2 ; no more to do, don't remove from buffer... push cx mov ax,offset tlbuf ; where to put the next line mov bx,offset botbuf call getcirc ; try to get another pop cx jc nxtsc2 ; no more, break loop loop nxtsc1 ; loop for all lines nxtsc2: call rstpos ; restore cursor position nxtsc3: ret ; and return nxtscr endp ; save a screen by rolling them into a circular buffer. ; enter with ax/ circular buffer ptr, bx/ first line to get ; dx/ increment rolscr proc near shl dx,1 ; double increment for word ptr dec bx ; ptr starts at 0 shl bx,1 ; convert to word ptr mov cx,slen ; # of lines to save rolsc1: push cx push dx push bx push ax push ds call kilcur ; kill cursor mov ax,scrseg mov ds,ax ; address screen mov si,ds:[latofs+bx] ; get current line mov di,offset rlbuf ; place to put it mov cx,swidth ; # of bytes to move rep movsb ; get the lne mov si,ds:[latofs+bx] ; get current line ptr again add si,attoffs ; where attributes start mov cx,swidth ; # of bytes to move rep movsb ; move attributes as well pop ds ; restore segment pop bx ; this is desired circ buffer ptr call rstcur mov ax,offset rlbuf ; this is where the line is call putcirc ; save in circular buffer mov ax,bx ; put buffer ptr back where it belongs pop bx ; get line pos back pop dx ; and increment pop cx ; don't forget counter add bx,dx ; move to next line loop rolsc1 ; loop thru all lines ret ; and return rolscr endp ; move screen down a line, get one previous line back prvlin proc near ; get the previous line back mov ax,offset tlbuf ; place to put line temporarily mov bx,offset topbuf ; where to get lines from call getcirc ; try to get a line jc prvli1 ; no more, just return mov ax,offset blbuf ; place for bottom line call getbot ; fetch bottom line mov ax,offset blbuf mov bx,offset botbuf call putcirc ; save in circular buffer call savpos ; save cursor position mov dx,offset topdwn ; home, then reverse index call tmsg mov ax,offset tlbuf ; point to data mov bx,0101H ; print line at top of screen mov dx,offset tlbuf+swidth call prlina ; print the line call rstpos ; restore cursor position prvli1: ret ; and return prvlin endp ; move screen up a line, get one bottom line back nxtlin proc near mov ax,offset blbuf ; place to put line temporarily mov bx,offset botbuf ; where to get lines from call getcirc ; try to get a line jc nxtli1 ; no more, just return call savtop ; save one line off of top call savpos ; save cursor position mov dx,offset botup ; go to bottom, then scroll up a line call tmsg mov ax,offset blbuf ; point to data mov bx,0100H + slen ; print at bottom line mov dx,offset blbuf+swidth call prlin ; print the line call rstpos ; restore cursor position nxtli1: ret ; and return nxtlin endp ; save cursor position savpos proc near mov dx,offset curinq ; where is the cursor? call tmsg mov posbuf,esc ; put an escape in the buffer first mov di,offset posbuf+1 savpo1: mov ah,8 ; read, no echo int dos cmp al,'R' ; end of report? je savpo2 ; yes stosb ; no, save it jmp savpo1 ; and go on savpo2: mov al,'H' ; this ends the sequence when we send it stosb mov byte ptr [di],'$' ; need this to print it later ret ; and return savpos endp ; restore the position saved by savpos rstpos proc near mov dx,offset posbuf call tmsg ; just print this ret ; and return rstpos endp ; kill cursor so it doesn't get saved along with real data kilcur proc near push es push di mov di,kcurfn int firmwr pop di pop es ret kilcur endp ; restore the cursor rstcur proc near push es push di mov di,rcurfn int firmwr pop di pop es ret rstcur endp ; print a ff-terminated line at most swidth long... Pass the line in ax. ; cursor position should be in bx. ; prlina writes attributes as well, which should be passed in dx. prlin proc near mov bp,2 ; print characters only jmp short prli1 prlina: xor bp,bp ; 0 means print attributes as well. prli1: push es ; this trashes es!!! push es mov cx,scrseg mov es,cx ; address screen seg for a moment mov cl,es:byte ptr [rmargin] ; get max line length mov ch,0 pop es ; address user's segment again push cx ; remember original length ; mov cx,swidth mov si,ax ; better place for ptr mov di,ax ; need it here for scan mov al,0ffh ; this marks the end of the line repne scasb ; look for the end jne prli2 ; not found inc cx ; account for pre-decrement prli2: neg cx pop ax ; get original length back add cx,ax ; add cx,swidth ; figure out length of line jcxz prli3 ; 0-length line, skip it. mov ax,bp ; writing characters mov bp,ds ; wants segment here mov di,14H ; fast write to screen int firmwr ; pos is in bx, char ptr in si prli3: pop es ; restore register ret ; and return prlin 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