DataMuseum.dk

Presents historical artifacts from the history of:

DKUUG/EUUG Conference tapes

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about DKUUG/EUUG Conference tapes

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - metrics - download
Index: T m

⟦2bf8aae91⟧ TextFile

    Length: 101947 (0x18e3b)
    Types: TextFile
    Names: »msxrb1.asm«

Derivation

└─⟦9ae75bfbd⟧ Bits:30007242 EUUGD3: Starter Kit
    └─⟦71044c191⟧ »EurOpenD3/misc/kermit.ms-2.32.tar.Z« 
        └─⟦31f2d420d⟧ 
            └─⟦this⟧ »msxrb1.asm« 

TextFile

        name msxrb1
; File msxrb1.asm
; Kermit system dependent module for Rainbow
; Jeff Damens, July 1984
;  with additional major changes by Joe Doupnik, 1986, 1987, 1988.
; edit history
; Last edit: 12 June 1988
; 1 July 1988 Version 2.31
; 10 Jan 1988 Cleanup 8 bit display in outtty. [jrd]
; 1 Jan 1988 version 2.30

        public  serini, serrst, clrbuf, outchr, coms, vts, vtstat, dodel
        public  ctlu, cmblnk, locate, lclini, prtchr, dobaud, clearl
        public  dodisk, getbaud, beep, pcwait, dumpscr, termtb, shomodem
        public  count, xofsnt, puthlp, putmod, clrmod, poscur, getmodem
        public  sendbr, sendbl, term, machnam, setktab, setkhlp, showkey
        public  ihosts, ihostr, serhng, dtrlow, comptab         ; [jrd]
                        ; action verb procedures for keyboard translator
        public  prvscr, nxtscr, prtscn
        public  uparrw, dnarrw, rtarr, lfarr, pf1, pf2, pf3, pf4
        public  kp0, kp1, kp2, kp3, kp4, kp5, kp6, kp7, kp8, kp9
        public  kpminus, kpcoma, kpenter, kpdot, chrout, cstatus, cquit
        public  cquery, prvscr, nxtscr, prvlin, nxtlin, trnprs, snull
        public  nxttop, nxtbot, klogon, klogof, cdos, chang
        include mssdef.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
csrcol  equ     0f41h           ; current cursor column
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 (?)
newlmod equ     08eh            ; b0 = 0 lf, = 1 newline (cr/lf)
bdprt   equ     06h             ; baud rate port
vt52mod equ     088h            ; b0 = 1 if in ansi mode
off     equ     0
bufon   equ     1               ; buffer level xon/xoff on-state control flag
usron   equ     2               ; user level xon/xoff on-state control flag

mntrgh  equ     bufsiz*3/4      ; High point = 3/4 of buffer full
mntrgl  equ     bufsiz/4        ; Low point = 1/4 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             ; Bios interrupt
kcurfn  equ     8h              ; disable cursor
rcurfn  equ     0ah             ; enable cursor

swidth  equ     132             ; screen width
slen    equ     24              ; screen length
npages  equ     10              ; for use with dynamic memory allocation

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
lmax    dw      ?                       ; max lines of 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
        extrn   filtst:byte, dmpname:byte, rxtable:byte
        extrn   kbdflg:byte

setktab db      0

akeyflg db      0               ; non-zero if in alt keypad mode
ckeyflg db      0               ; non-zero if cursor is in applications mode
ourflgs db      0               ; our flags
fpscr   equ     80H             ; flag definitions
argadr  dw      0               ; pointer to arguments from msster
esc_ch  db      ?               ; active Kermit escape char
crlf    db      cr,lf,'$'
setkhlp db      ?
machnam db      'Rainbow$'
nyimsg  db      cr,lf,'Not yet implemented$'
badbdmsg db     cr,lf,'?Unsupported baud rate$'
dmperr  db      cr,lf,'?Cannot access screen-dump file$',cr,lf
hngmsg  db      cr,lf,' The phone should have hungup.',cr,lf,'$'
hnghlp  db      cr,lf,' The modem control lines DTR and RTS for the current'
        db      ' port are forced low (off)'
        db      cr,lf,' to hangup the phone. Normally, Kermit leaves them'
        db      ' high (on) when it exits.'
        db      cr,lf,'$'
msmsg1  db      cr,lf,' Modem is not ready: DSR is off$'
msmsg2  db      cr,lf,' Modem is ready:     DSR is on$'
msmsg3  db      cr,lf,' no Carrier Detect:  CD  is off$'
msmsg4  db      cr,lf,' Carrier Detect:     CD  is on$'
msmsg5  db      cr,lf,' no Clear To Send:   CTS is off$'
msmsg6  db      cr,lf,' Clear To Send:      CTS is on$'
rdbuf   db      swidth dup (?)  ; temp buf
delstr  db      BS,BS,'  ',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
mdstreg db      0               ; Modem line status report for Show Modem
xofsnt  db      0               ; Say if we sent an XOFF
xofrcv  db      0               ; Say if we received an XOFF
parmsk  db      0ffh            ; 7-8 bit parity mask
flowon  db      ?               ; flow on char (xon or null)
flowoff db      ?               ; flow off char (xoff or null)
mdmhand db      0               ; Modem status register, current
iobuf   db      5 dup (?)       ; buffer for ioctl

gopos   db      escape,'['
rowp    db      20 dup (?)
clrseq  db      escape,'[H',escape,'[J$'
ceolseq db      escape,'[K$'
invseq  db      escape,'[7m$'
nrmseq  db      escape,'[0m$'
ivlatt  db      swidth dup (0fH) ; a line's worth of inverse attribute
dumpbuf db      swidth+2 dup (?) ; screen dump work buffer
dumpsep db      FF,cr,lf        ; screen dump image separator
dovt52  db      escape,'[?2l$'  ; set VT52 mode
dovt102 db      escape,'<$'     ; set VT102 mode

ourarg  termarg <>
comptab db      2                       ; communications port options
        mkeyw   '1',1
        mkeyw   'COM1',1                ; only one option here

onofftbl db     2
        mkeyw   'off',0
        mkeyw   'on',1

vttbl   db      3                       ; SET TERM table
        mkeyw   'Roll',10
        mkeyw   'VT102',ttvt100
        mkeyw   'VT52',ttvt52

termtb  db      2                       ; entries for Status, not Set
        mkeyw   'VT102',ttvt100
        mkeyw   'VT52',ttvt52

rolhlp  db      cr,lf,'  Roll (undo screen roll back before writing new'
        db      ' chars, default=off)$'

; variables for serial interrupt handler
source  db      bufsiz DUP(?)   ; Buffer for data from port
srcpnt  dw      source          ; Pointer in buffer (DI)
count   dw      0               ; Number of chars in int buffer
telflg  db      0               ; non-zero if we're a terminal. NRU
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
twnd    cbuf    <>                      ; top screen spill-buffer struct
bwnd    cbuf    <>                      ; bottom screen spill buffer struct
topline dw      swidth dup (?)          ; top line screen spill buffer
botline dw      swidth dup (?)          ; bottom line screen spill buffer
rlbuf   dw      swidth dup (?)          ; temp buffer for line scrolling
scrnbuf db      swidth*slen dup (?)     ; save-screen, text
attrbuf db      swidth*slen dup (?)     ; save-screen, attributes
srcseg  dw      0

topdwn  db      escape,'[H',escape,'M$' ; go to top, scroll down
botup   db      escape,'[24;0H',escape,'D$' ; go to bottom, scroll up
curinq  db      escape,'[6n$'   ; cursor inquiry
posbuf  db      20 dup (?)      ; place to store cursor position
gtobot  db      escape,'[24;0H$'        ; go to bottom of screen
ourscr  dw      ?
ourattr dw      ?               ; storage for screen and attributes
inited  db      0               ; terminal handler not inited yet
dosmsg  db      '?Must be run in version 2.05 or higher$'
dmphand dw      ?               ; file handle for screen dump
anssq1  db      escape,'[c'
an1len  equ     $-anssq1
anssq2  db      escape,'Z'
an2len  equ     $-anssq2
eakseq  db      escape,'='
eaklen  equ     $-eakseq
dakseq  db      escape,'>'
daklen  equ     $-dakseq
cuapseq db      escape,'[?1h'
cuaplen equ     $-cuapseq
cunapseq db     escape,'[?1l'
cunaplen equ    $-cunapseq
crsseq  db      escape,'c'
crslen  equ     $-crsseq
enqseq  db      escape,'[6n'
enqlen  equ     $-enqseq
ansbk1  ans     <anssq1,an1len,anssq1,an1len,sndans> ; two answerbacks
ansbk2  ans     <anssq2,an2len,anssq2,an2len,sndans>
ansbk3  ans     <eakseq,eaklen,eakseq,eaklen,enaaky> ; enable alt keypad
ansbk4  ans     <dakseq,daklen,dakseq,daklen,deaaky> ; disable alt keypad
ansbk5  ans     <crsseq,crslen,crsseq,crslen,sndspc> ; crash sequence (!)
ansbk6  ans     <enqseq,enqlen,enqseq,enqlen,ansenq>
ansbk7  ans     <cuapseq,cuaplen,cuapseq,cuaplen,cuapp> ; cursor application
ansbk8  ans     <cunapseq,cunaplen,cunapseq,cunaplen,cunapp>; cursor cursor
ansret  db      escape,'[?6c'
ansrln  equ     $-ansret
vt52ret db      escape,'/Z'                     ; VT52 identification
vt52ln  equ     $-vt52ret
temp    dw      0
vtroll  db      0

;port initialization data for 7201 [ejz]
;enables Rx,Tx, CTS, DTR, 8 bits, no parity, 1.5 stop bits
prtpar  db      18H,14H,48H,13H,0C1H,15H,0EAH,11H,18H,00H
datas   ends

code    segment public 'code'
        extrn   comnd:near, dopar:near, sleep:near
        extrn   sbrk:near, isfile:near
        extrn   strlen:near, strcpy:near
        extrn   msuinit:near, keybd:near

        assume  cs:code,ds:datas,es:datas

; local initialization routine, called by Kermit initialization.
; Memory allocation rewritten by [jrd].

lclini  proc    near
        mov     ah,dosver       ; make sure this is DOS version 2.05 or higher
        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,4c10H                ; exit(16)
        int     dos
lclin1: call    setterm                 ; set terminal type to VT102
        call    msuinit                 ; initialize keyboard translator
        mov     ourscr,offset scrnbuf   ; save-screen text buf address
        mov     ourattr,offset attrbuf  ; save-screen attr buf address

        mov     ax,swidth*2*2           ; ask for two lines (1 per buffer)
        call    sbrk                    ; allocate mem. Exit Kermit on failure
                                        ;if we get here them we have the lines
                                        ;if we get here them we have the lines
        mov     bwnd.orig,ax            ; memory segment, bottom window area
        mov     twnd.orig,ax            ; top. same place for both buffers!
        push    es                      ; save this register
        mov     es,ax                   ; seg pointer to new memory block
        mov     bx,(swidth*slen*npages+7)/8 ; paragraphs wanted for roll back
        add     bx,24000D/16            ; plus paragraphs to run Command.com
        mov     ah,setblk               ; DOS Setblock. Ask for that space
        int     dos                     ; bx has # paragraphs available
        sub     bx,24000D/16            ; deduct space for DOS 3.x Command.Com
        cmp     bx,(swidth*4+15)/16     ; any room left for buffers?
        jae     lclyin2                 ; some space is available for buffers
        mov     bx,(swidth*4+15)/16     ; else use our sbrk allocation
lclyin2:mov     ah,setblk               ; ask for that many (bx) paragraphs
        int     dos                     ; Errors here == DOS deceived us
        pop     es                      ; restore reg
        mov     ax,bx                   ; bx = # paragraphs allocated by DOS
        mov     cl,3                    ; 2**3 = 8
        shl     ax,cl                   ; paragraphs to words (char + attrib)
        xor     dx,dx                   ; clear extended size
        mov     cx,swidth               ; number of chars per line in buffer
        div     cx                      ; ax = number of lines in buffer
        mov     bwnd.lmax,ax            ; max lines per buffer (quotient)
        mov     twnd.lmax,ax            ; max lines per buffer
        add     cx,cx                   ; count char and attribute per item
        xor     dx,dx                   ; clear extended numerator
        mul     cx                      ; ax = effective # bytes per buffer
        dec     ax                      ; adjust for counting from zero
        mov     bwnd.bend,ax            ; offset of last byte in buffer
        mov     twnd.bend,ax            ; offset of last byte in buffer
        mov     bwnd.pp,0               ; offset of first byte in buffer
        mov     twnd.pp,0               ; offset of first byte in buffer
        mov     bwnd.lcnt,0             ; number of lines occupied in buffer
        mov     twnd.lcnt,0             ; number of lines occupied in buffer
        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
        ret                     ; and return
showkey endp


; SHOW MODEM, displays current status of lines DSR, CD, and CTS.
; Uses byte mdmhand, the modem line status register. [jrd]
shomodem proc   near
        mov     ah,cmcfm                ; get a confirm
        call    comnd
         jmp    r                       ; no confirm
         nop
        call    getmodem                ; get modem status
        mov     mdmhand,al
        mov     ah,prstr
        mov     dx,offset msmsg1        ; modem ready msg
        test    mdmhand,20h             ; is DSR asserted?
        jz      shomd1                  ; z = no
        mov     dx,offset msmsg2        ; say not asserted
shomd1: int     dos
        mov     dx,offset msmsg3        ; CD asserted msg
        test    mdmhand,80h             ; CD asserted?
        jz      shomd2                  ; z = no
        mov     dx,offset msmsg4        ; say not asserted
shomd2: int     dos
        mov     dx,offset msmsg5        ; CTS asserted msg
        test    mdmhand,10h             ; CTS asserted?
        jz      shomd3                  ; z = no
        mov     dx,offset msmsg6        ; say not asserted
shomd3: mov     ah,prstr
        int     dos
        jmp     rskp
shomodem endp

; Get modem status and set global byte mdmhand. Preserve all registers.
; Uses byte mdstreg, the modem line status register, bits as follows:
; Int Z80, Int 8088, Hwd fail det enable, CD, CTS, DSR, SI/SecCD, RI   [jrd]
getmodem proc   near                    ; gets modem status upon request
        push    dx
        mov     al,0                    ; assume nothing is on
        mov     dx,mnctrl               ; modem control port (read 02h)
        in      al,dx                   ; read modem control port
        mov     mdmhand,0               ; clear status byte
        test    al,4                    ; DSR asserted?
        jz      getmod1                 ; z = no
        or      mdmhand,20h             ; set IBM spec DSR bit
getmod1:test    al,8                    ; CTS asserted?
        jz      getmod2                 ; z = no
        or      mdmhand,10h             ; set IBM spec CTS bit
getmod2:test    al,10                   ; CD asserted?
        jz      getmod3                 ; z = no
        mov     mdmhand,80h             ; set IBM spec CD bit
getmod3:mov     al,mdmhand              ; setup return
        mov     ah,0                    ; return status in al
        pop     dx
        ret
getmodem 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 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.
; Msxibm routine with Rainbow port names. [jrd]
OUTCHR  PROC    NEAR
        cmp flowoff,0           ; Are we doing flow control
        je outch2               ; No, just continue
        cmp ah,flowoff          ; sending xoff?
        jne outch1              ; ne = no
        mov xofsnt,usron        ; indicate user level xoff being sent
        jmp outch1b
outch1: cmp ah,flowon           ; user sending xon?
        jne outch1b             ; ne = no
        mov xofsnt,off          ; say an xon has been sent (cancels xoff)
outch1b:cmp xofrcv,off          ; Are we being held (xoff received)?
        je outch2               ; e = no - it's OK to go on
        cmp flags.timflg,0      ; is timer off?
        je outch2               ; e = yes, no timeout period
        push cx                 ; save reg
        mov cl,trans.rtime      ; receive timeout interval
        mov ch,0
        jcxz outch1c            ; z = no timeout wanted
outch1a:cmp xofrcv,off          ; Are we being held (xoff received)?
        je outch1c              ; e = no - it's OK to go on
        mov al,1                ; else sleep for a second
        call sleep
        loop outch1a            ; and try it again
        mov xofrcv,off          ; timed out, force it off and fall thru
outch1c:pop cx                  ; end of flow control section
                     ; OUTCH2 is entry point for sending without flow control
OUTCH2: mov al,ah               ; Parity routine works on AL
        call dopar              ; Set parity appropriately
        mov ah,al               ; Don't overwrite character with status
outch3: push cx                 ; Save registers
        push dx
        sub cx,cx
outch3b:mov dx,mnstata          ; Get port status
        in al,dx
        test al,txrdy           ; Transmitter ready?
        jnz outch4              ; Yes
        jmp $+2                 ; use time, prevent overdriving UART
        jmp $+2
        loop outch3b
         jmp outch5             ; Timeout
outch4: mov al,ah               ; Now send it out
        mov dx,mndata           ; use a little time
        jmp $+2
        out dx,al
        pop dx                  ; exit success
        pop cx
        jmp rskp
outch5: pop dx                  ; exit failure
        pop cx
        ret
OUTCHR  ENDP

; 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 rdbuf ; this is destination
        xor     cx,cx           ; # of chars in the line
        cld
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 rdbuf ; the actual message
        mov     di,14H          ; send direct to screen
        mov     bp,ds           ; need data segment as well
        push    ax
        push    cx
        push    dx
        push    di
        mov     di,14H          ; send direct to screen
        int     firmwr
        pop     di
        pop     dx
        pop     cx
        pop     ax
        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
        clc
        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
        push    bx
        push    ds
        pop     es              ; set es to datas segment
        cld
        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
        pop     bx
        ret
doba1:  mov     dx,offset badbdmsg
        call    tmsg
        pop     bx
        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    ax              ; save some regs
        push    bx
        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
        pop     bx              ; restore regs
        pop     ax
        ret                     ; and return
GETBAUD ENDP


; Get Char from serial port buffer.
; skip returns if no character available at port,
; otherwise returns with char in al, # of chars in buffer in dx.
; Revised 22 May 1986, and again slightly 2 August 1986 by [jrd]
; Copied from msxibm.asm [jrd]
PRTCHR  PROC    NEAR
        call chkxon             ; see if we need to xon
        cmp count,0             ; any characters available?
        jnz prtch1              ; nz = yes, get one
        mov dx,0                ; return count of zero
        jmp rskp                ; No data - check console
prtch1: push si                 ; save si
        cli             ; interrupts off, to keep srcpnt & count consistent
        mov si,srcpnt           ; address of next available slot in buffer
        sub si,count            ; minus number of unread chars in buffer
        cmp si,offset source    ; located before start of buffer (wrapped)?
        jae prtch2              ; ae = no
        add si,bufsiz           ; else do arithmetic modulo bufsiz
prtch2: mov al,byte ptr [si]    ; get a character into al
        dec count               ; one less unread char now
        sti                     ; interrupts back on now
        pop si
        mov dx,count            ; return # of chars in buffer
        ret
PRTCHR  ENDP


; IHOSTS - Initialize the host by sending XON, or equivalent, and enter the
; cycle of clear input buffer, wait 1 second, test if buffer empty then exit
; else repeat cycle. Requires that the port be initialized before hand.
; Ihosts is used by the local send-file routine just after initializing
; the serial port.
; 22 March 1986 [jrd]
; Modified 26 June 1986 to supress sending a null if no flow control. [jrd]
IHOSTS  PROC    NEAR
        push    ax              ; save the registers
        push    cx
        push    dx
        mov     xofrcv,off      ; clear old xoff received flag
        mov     xofsnt,off      ; and old xoff sent flag
        mov     ah,flowon       ; put Go-ahead flow control char in ah
        or      ah,ah           ; doing flow control?
        jz      ihosts1         ; z = no, don't send a null
        call    outchr          ; send it (release Host's output queue)
         nop                    ; outchr can do skip return
         nop
         nop
ihosts1:call    clrbuf          ; clear out interrupt buffer
;;      mov     ax,1            ; sleep for 1 second
;;      call    sleep           ; procedure sleep is in msscom.asm
;;      call    prtchr          ; check for char at port
;;       jmp    ihosts1         ; have a char in al, repeat wait/read cycle
;;       nop                    ; prtchr does skip return on empty buffer
        pop     dx              ; empty buffer. we are done here
        pop     cx
        pop     ax
        ret
IHOSTS  ENDP

; IHOSTR - initialize the remote host for our reception of a file by
; sending the flow-on character (XON typically) to release any held
; data. Called by receive-file code just after initializing the serial
; port.         22 March 1986 [jrd]
; Modified 26 June 1986 to supress sending a null if no flow control. [jrd]
IHOSTR  PROC    NEAR
        push    ax              ; save regs
        push    cx
        mov     xofrcv,off      ; clear old xoff received flag
        mov     xofsnt,off      ; and old xoff sent flag
        mov     ah,flowon       ; put Go-ahead flow control char in ah
        or      ah,ah           ; doing flow control?
        jz      ihostr1         ; z = no, don't send a null
        call    outchr          ; send it (release Host's output queue)
         nop                    ; outchr can do skip return
         nop
         nop
ihostr1:pop     cx
        pop     ax
        ret
IHOSTR  ENDP

; local routine to see if we have to transmit an xon
chkxon  proc    near
        cmp     flowon,0        ; doing flow control?
        je      chkxo1          ; no, skip all this
        test    xofsnt,usron    ; did user send an xoff?
        jnz     chkxo1          ; nz = yes, don't contradict it here
        test    xofsnt,bufon    ; have we sent a buffer level xoff?
        jz      chkxo1          ; z = no, forget it
        cmp     count,mntrgl    ; below (low water mark) trigger?
        jae     chkxo1          ; no, forget it
        mov     ah,flowon       ; ah gets xon
        and     xofsnt,off      ; remember we've sent the xon
        call    outch2          ; send via non-flow controlled entry point
         nop
         nop
         nop                    ; in case it skips
chkxo1: ret
chkxon  endp

; Send a BREAK out the current serial port.  Returns normally.
SENDBR  PROC    NEAR
        push cx
        mov     cx,275          ; 275 millisec
        call    sendbw          ; let worker routine do it
        pop     cx
        ret
; Send a Log BREAK out the current serial port.  Returns normally.
SENDBL: push    cx
        mov     cx,1800         ; 1800 millisec
        call    sendbw          ; let worker routine do it
        pop     cx
        ret

sendbw: push ax                 ; worker routine to send a break [jrd]
        push bx                 ; number of millisec is in cx
        push dx
        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,cx               ; # of ms to wait
        call pcwait             ; 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 dx
        pop bx
        pop ax
        clc
        ret                     ; And return
SENDBR  ENDP


; wait for the # of milliseconds in ax
; thanks to Bernie Eiben for this one.
pcwait  proc    near
        push    cx
pcwai0: mov     cx,240          ; inner loop counter for 1 millisecond
pcwai1: sub     cx,1            ; inner loop takes 20 clock cycles
        jnz     pcwai1
        dec     ax              ; outer loop counter
        jnz     pcwai0          ; wait another millisecond
        pop     cx
        ret
pcwait  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    ax              ; save some regs
        push    bx
        push    di
        push    dx
        cld
        mov     ax,ds
        mov     es,ax           ; address datas segment
        mov     di,offset rowp
        mov     al,dh           ; row comes first
        mov     ah,0
        call    nout
        mov     al,';'
        stosb                   ; separated by a semicolon
        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     di              ; restore regs
        pop     bx
        pop     ax
        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 Terminal command

VTS     PROC    NEAR                    ; SET TERM whatever  [jrd]
        mov     ah,cmkey                ; parse key word
        mov     bx,0                    ; use built-in help
        mov     dx,offset vttbl         ; use this table
        call    comnd
         jmp    r
        cmp     bx,tttypes              ; ROLL or more?
        ja      vts4                    ; a = yes
                                        ; SET TERM {VT52 | VT102}
        mov     temp,bx
        mov     ah,cmcfm
        call    comnd                   ; get a confirm
         jmp    r
        cmp     bl,ttvt100              ; set to VT102?
        je      vts2                    ; e = yes
        mov     flags.vtflg,ttvt52      ; say VT52
        jmp     vts3
vts2:   mov     flags.vtflg,ttvt100     ; say VT102
vts3:   call    setterm                 ; send the message to the console
        ret
vts4:
        mov     ah,cmkey                ; SET TERM ROLL
        mov     bx,offset rolhlp        ; help message
        mov     dx,offset onofftbl      ; table of answers
        call    comnd
         jmp    r
        mov     temp,bx
        mov     ah,cmcfm
        call    comnd                   ; get a confirm
         jmp    r
        mov     bx,temp                 ; get Roll flag
        mov     vtroll,bl               ; set the flag
        ret
VTS     ENDP

VTSTAT  PROC    NEAR            ; Status routine for emulation. [jrd]
        ret                     ; dummy (nothing to do actually)
VTSTAT  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
        cmp portin,0            ; Did we initialize port already?
        jne serin0              ; Yes, so just leave
        cli                     ; Disable interrupts
        cld                     ; Do increments in string operations
        push es
        push si                 ; [ejz] - Save this just in case
        mov si, offset prtpar   ; [ejz]
        mov dx, mnstata         ; [ejz]
        push ds
        pop es                  ; set es to datas segment
        call prtset             ; [ejz]
        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
        pop si                  ; [ejz]
        pop es
        mov al,030h             ;[DTR] enable RTS and DTR Note: bits reversed
        out mnctrl,al           ;[DTR]              compared to documentation
        mov portin,1            ; Remember port has been initialized
        sti                     ; Allow interrupts
        push bx
        mov bx,portval          ; get port
        mov parmsk,0ffh         ; parity mask, assume parity is None
        cmp [bx].parflg,parnon  ; is it None?
        je serin1               ; e = yes
        mov parmsk,07fh         ; no, pass lower 7 bits as data
serin1: mov bx,[bx].flowc       ; get flow control chars
        mov flowoff,bl          ; xoff or null
        mov flowon,bh           ; xon or null
        pop bx
serin0: clc                     ; carry clear for success
        ret
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
        cmp portin,0            ; Reset already?
        je srst1                ; Yes, just leave.
        cli                     ; Disable interrupts
        push es                 ; preserve this
        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
        pop es
        sti                     ; re-enable interrupts
srst1:  ret                     ; All done
SERRST  ENDP

; serial port interrupt routine.  This is not accessible outside this
; module, handles serial port receiver interrupts.
; New code, lifted from msxibm. [jrd]
serint  PROC  NEAR
        push ax
        push ds
        push bx
        push dx
        mov ax,seg datas
        mov ds,ax               ; address data segment
        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
        jmp serin8
serin7: mov dx,mnstata          ; reload port address
        mov al,38H
        out dx,al               ; tell the port we finished with the interrupt
        sti                     ; turn on interrupts
serin8: pop dx
        pop bx
        pop ds
        pop ax
intret: iret

; handler for serial receive, port A

srcva:  mov dx,mnstata
        mov al,0                ; Asynch status port
        out dx,al               ; put into known state
        in al,dx
        test al,rxrdy           ; Data available?
        jnz srcva0a             ; nz = yes
srcva0: mov dx,mnstata
        mov al,38h              ; tell port we are finished with the interrupt
        out dx,al
        sti                     ; turn on interrupts
        jmp retint              ;  and exit now (common jump point)

srcva0a:;;and al,mdmover                ; select overrun bit
;;      mov overrun,al          ; save it for later
        mov al,30h              ; clear any errors
        out dx,al
        mov dx,mndata           ; get modem rx data
        in al,dx                ; read the received character into al
        cmp flowoff,0           ; flow control active?
        je srcva2               ; e = no
        mov ah,al               ; ah = working copy. Check null, flow cntl
        and ah,parmsk           ; strip parity temporarily, if any
        cmp ah,flowoff          ; acting on Xoff?
        jne srcva1              ; ne = Nope, go on
        mov xofrcv,bufon        ; Set the flag saying XOFF received
        jmp srcva0              ;  and exit
srcva1: cmp ah,flowon           ; acting on Xon?
        jne srcva2              ; ne = no, go on
        mov xofrcv,off          ; Clear the XOFF received flag
        jmp srcva0              ;  and exit
srcva2: push ax                 ; save rcvd char around this output cmd
        mov dx,mnstata
        mov al,38h              ; tell port we are finished with the interrupt
        out dx,al
        pop ax
        cli                     ; ensure interrupts are off, critical section
;;      mov ah,overrun          ; get overrun flag
;;      or ah,ah                ; overrun?
;;      jz srcva2a              ; z = no
;;      mov ah,al               ; yes, save present char
;;      mov al,bell             ; insert control-G for missing character
srcva2a:mov bx,srcpnt           ; address of buffer storage slot
        mov byte ptr [bx],al    ; store the new char in buffer "source"
        inc srcpnt              ; point to next slot
        inc bx
        cmp bx,offset source + bufsiz ; beyond end of buffer?
        jb srcva3               ; b = not past end
        mov srcpnt,offset source ; wrap buffer around
srcva3: cmp count,bufsiz        ; filled already?
        jae srcva4              ; ae = yes
        inc count               ; no, add a char
srcva4:;;       or ah,ah                ; anything in overrun storage?
;;      jz srcva4a              ; z = no
;;      mov al,ah               ; recover any recent char from overrun
;;      xor ah,ah               ; clear overrun storage
;;      jmp srcva2a             ; yes, go store real second char
srcva4a:sti                     ; ok to allow interrupts now, not before
        cmp count,mntrgh        ; past the high trigger point?
        jbe retint              ; be = no, we're within our limit
        test xofsnt,bufon       ; Has an XOFF been sent by buffer control?
        jnz retint              ; nz = yes
        mov al,flowoff          ; get the flow off char (Xoff or null)
        or al,al                ; don't send null chars
        jz retint               ; z = null, nothing to send
        call dopar              ; Set parity appropriately
        mov ah,al               ; Don't overwrite character with status
        push cx                 ; save reg
        xor cx,cx               ; loop counter
srcva5: mov dx,mnstata          ; port status register
        in al,dx
        test al,txrdy           ; Transmitter ready?
        jnz srcva6              ; nz = yes
        push ax                 ; use time, prevent overdriving UART
        pop ax
        loop srcva5             ; else wait loop, cx times
         jmp srcva7             ; Timeout
srcva6: mov al,ah               ; Now send out the flow control char
        mov dx,mndata
        out dx,al
        mov xofsnt,bufon        ; Remember we sent an XOFF at buffer level
srcva7: pop cx                  ; restore reg
retint: 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
        jmp     srccom          ; take common exit

stxa:   mov     dx,mnstata
        mov     al,28H          ; reset transmit interrupt
        out     dx,al
        jmp     srccom          ; take common exit

sstata: mov     dx,mnstata
        mov     al,10H          ; reset status interrupt
        out     dx,al           ; fall through to common exit srccom below

srccom: mov dx,mnstata          ; common exit for above
        mov al,38h              ; tell port we are finished with the interrupt
        out dx,al
        sti                     ; turn on interrupts
        ret

SERINT  ENDP

DTRLOW  PROC    NEAR            ; Global proc to Hangup the Phone by making
                                ; DTR and RTS low.
        mov ah,cmtxt            ; allow text to be able to display help
        mov bx,offset rdbuf     ; dummy buffer
        mov dx,offset hnghlp    ; help message
        call comnd              ; get a confirm
         jmp r
        call serhng             ; drop DTR and RTS
        mov ah,prstr            ; give a nice message
        mov dx,offset hngmsg
        int dos
        jmp rskp
DTRLOW  ENDP

; Hang up the Phone. Similar to SERRST except it just forces DTR and RTS low
; to terminate the connection. 29 March 1986 [jrd]
; Calling this twice without intervening calls to serini should be harmless.
; Returns normally.

serhng  proc    near            ; [jrd]
        cli                     ; Disable interrupts
        mov al,00h              ;[DTR] disable RTS and DTR
        out mnctrl,al           ;[DTR]
        sti                     ; Allow interrupts
        clc
        ret                     ; We're done
serhng  endp

; Produce a short beep.
; 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
        cld
        stosb                   ; drop it off
        ret                     ; and return
nout    endp


term    proc    near
        mov si,ax               ; this is source
        mov argadr,ax           ; save here too
        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?
        jne term1               ; ne = yes
        call cmblnk             ; clear the screen
        call locate             ; put cursor at top left corner
        mov inited,1            ; say initialized
        jmp short term2
term1:  call rstscr             ; restore screen
        mov inited,1            ; remember inited
term2:  call prtchr             ; read character from serial port
         jmp short term3        ; have a char from serial port
         nop
        jmp short term6         ; no char, go on
term3:  and al,parmsk           ; turn off parity for terminal
        call outtty             ; send to display and logger
term6:  call keybd              ; read keyboard via translator
        jnc term2               ; nc = keep going
term9:  call savscr             ; save screen
        mov dx,offset gtobot    ; go to last line on screen
        call tmsg
        ret                     ; and return
term    endp


; put the character in al to the screen
outtty  proc    near
        push    es                      ; protect es around fastcon calls
        test    flags.remflg,d8bit      ; keep 8 bits for displays?
        jnz     outnp5                  ; nz = yes, 8 bits if possible
        and     al,7fh                  ; remove high bit
outnp5: cmp     rxtable+256,0           ; translation turned off?
        je      outnp7                  ; e = yes, no translation
        push    bx
        mov     bx,offset rxtable       ; address of translate table
        xlatb                           ; new char is in al
        pop     bx
outnp7: test    ourflgs,fpscr           ; should we be printing?
        jz      outnop                  ; z = no, keep going
        push    ax
        mov     ah,lstout               ; write to system printer device
        mov     dl,al
        int     dos
        pop     ax
        jnc     outnop                  ; nc = successful print
        push    ax
        call    beep                    ; else make a noise and
        call    trnprs                  ;  turn off printing
        pop     ax
outnop: test    ourarg.flgs,capt        ; capturing output?
        jz      outnoc                  ; z = no, forget this part
        push    ax                      ; save char
        call    ourarg.captr            ; give it captured character
        pop     ax                      ; restore character and keep going
outnoc:
        cmp     vtroll,0                ; auto roll back allowed?
        jz      outnp6                  ; z = no, leave screen as is
        cmp     bwnd.lcnt,0             ; is screen rolled back? [dlk]
        je      outnp6                  ; e = no
        call    nxtbot                  ; restore screen before writing [dlk]
outnp6: push    ax
        call    scrprep                 ; need to save top line
        pop     ax
        test    ourarg.flgs,trnctl      ; debug? if so use Bios tty mode
        jz      outnp3                  ; z = no
        cmp     al,7fh                  ; Ascii Del char or greater?
        jb      outnp1                  ; b = no
        je      outnp0                  ; e = Del char
        push    ax                      ; save the char
        mov     al,7eh                  ; output a tilde for 8th bit
        int     fastcon
        pop     ax                      ; restore char
        and     al,7fh                  ; strip high bit
outnp0: cmp     al,7fh                  ; is char now a DEL?
        jne     outnp1                  ; ne = no
        and     al,3fH                  ; strip next highest bit (Del --> '?')
        jmp     outnp2                  ; send, preceded by caret
outnp1: cmp     al,' '                  ; control char?
        jae     outnp3                  ; ae = no
        add     al,'A'-1                ; make visible
outnp2: push    ax                      ; save char
        mov     al,5eh                  ; caret
        int     fastcon                 ; display it
        pop     ax                      ; recover the non-printable char
outnp3: call    ansbak                  ; match answerback sequences
        push    ax
        int     fastcon                 ; write without intervention
        pop     ax
        pop     es
        ret                             ; and return
outtty  endp

; enter with current terminal character in al.
; calls answerback routine if necessary.
; This can be used to make the emulator recognize any sequence.
ansbak  proc    near
        push bx
        mov bx,offset ansbk1    ; check 1st answerback
        call ansbak0            ; check for answerback
        mov bx,offset ansbk2    ; maybe second answerback
        call ansbak0            ; should probably loop thru a table here
        mov bx,offset ansbk3
        call ansbak0
        mov bx,offset ansbk4
        call ansbak0
        mov bx,offset ansbk5
        call ansbak0
        mov bx,offset ansbk6
        call ansbak0
        mov bx,offset ansbk7
        call ansbak0
        mov bx,offset ansbk8
        call ansbak0
        pop bx
        ret
ansbak0:                        ; worker routine for above
        push    ax              ; preserve these
        push    si
        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     si
        pop     ax
        ret
ansbak  endp

; send the answerback message.
sndans  proc    near
        push    cx
        mov     si,offset ansret        ; ansi ident message
        mov     cx,ansrln               ; length of same
        push    es                      ; save seg register
        mov     ax,nvmseg               ; fetch address of nvm
        mov     es,ax                   ; put in segment reg
        test    byte ptr es:[vt52mod],1   ; check bit zero
        pop     es                      ; restore the seg register
        jnz     sndan1                  ; nz = ansi mode
        mov     si,offset VT52ret       ; say VT52
        mov     cx,VT52ln
sndan1: cld
        lodsb                           ; get a byte
        mov     ah,al
        push    si
        push    cx
        call    outchr                  ; send ah out the serial port
         nop
         nop
         nop
        pop     cx
        pop     si
        loop    sndan1
        pop     cx
        ret
sndans  endp

; enable alternate keypad mode
enaaky  proc    near
        mov     akeyflg,1               ; set keypad alternate mode
        ret
enaaky  endp

; disable alternate keypad mode
deaaky  proc    near
        mov     akeyflg,0
        ret
deaaky  endp

cuapp   proc    near
        mov     ckeyflg,1               ; set cursor keys to applications mode
        ret
cuapp   endp

cunapp  proc    near
        mov     ckeyflg,0               ; set cursor keys to cursor mode
        ret
cunapp  endp

; ESC c handler.
; Send a space so the firmware doesn't see bad escape sequences. [jrd]
sndspc  proc    near
        mov     akeyflg,0               ; reset keypad applications mode
        mov     ckeyflg,0               ; reset cursor applications mode
        mov     al,' '                  ; space separates the ESC and 'c'
        int     fastcon                 ; send this to upset esc parser
        push    ax
        call    nxtbot                  ; go to end of screen buffer
        call    cmblnk                  ; clear the screen too
        pop     ax
        clc
        ret
sndspc  endp

; answer a cursor position report
ansenq  proc    near
        push    es
        push    di
        mov     di,offset rdbuf         ; convenient scratch buffer
        mov     al,escape
        cld
        push    ds
        pop     es                      ; set es to datas segment
        stosb
        mov     al,'['
        stosb
        push    es
        mov     ax,scrseg
        mov     es,ax
        mov     al,es:[csrlin]
        mov     ah,es:[csrcol]
        pop     es
        push    ax
        mov     ah,0
        call    nout
        mov     al,';'
        stosb
        pop     ax
        xchg    ah,al
        mov     ah,0
        call    nout
        mov     al,'R'
        stosb
        mov     si,offset rdbuf
        sub     di,si
        mov     cx,di
ansen1: lodsb                           ; get a byte
        push    si
        push    cx
        mov     ah,al
        call    outchr                  ; send it along
         nop
         nop
         nop
        pop     cx
        pop     si
        loop    ansen1                  ; loop thru all
        pop     di
        pop     es
        ret                             ; and return
ansenq  endp

; set terminal to vt52 or vt102, based on current flags.vtflg [jrd]
setterm proc    near
        push    es                      ; save seg register
        mov     ax,nvmseg               ; fetch address of nvm
        mov     es,ax                   ; put in segment reg
        test    byte ptr es:[vt52mod],1   ; check bit zero
        pop     es                      ; restore the seg register
        push    ds
        pop     es                      ; set es to datas segment
        cld
        jnz     setter1                 ; nz = ansi mode
        cmp     flags.vtflg,ttvt52      ; are we already a VT52?
        je      setterx                 ; e = nothing to do
        mov     si,offset dovt102       ; change from vt52 to VT102
        jmp     setter2
setter1:cmp     flags.vtflg,ttvt100     ; already a VT102?
        je      setterx                 ; e = nothing to do
        mov     si,offset dovt52        ; change from vt102 to vt52
setter2:lodsb
        cmp     al,'$'
        je      setterx
        push    es
        push    si
        int     fastcon
        pop     si
        pop     es
        jmp     setter2
setterx:ret
setterm endp

; Handle the print screen key - copy whole screen to printer.
; Rewritten 26 June 1986 by [jrd] to avoid confusion over segment addressing
;  and line length counting. Based on procedure dumpscr code.
prtscn  proc    near
        push    ax                      ; save some regs
        push    bx
        push    cx
        push    dx
        push    si
        push    di
        push    es
        xor     bx,bx                   ; index for current line pointer
        mov     cx,slen                 ; number of screen lines
prtsc1: push    cx                      ; save outer loop (lines to do) count
        push    bx                      ; save index value for bottom of loop
        mov     cx,swidth               ; number of screen columns = 132
        mov     di,offset dumpbuf       ; data segement memory (work buffer)
        mov     ax,scrseg               ; make es hold screen segment
        mov     es,ax                   ;  for inner read-a-row loop
        mov     si,es:[latofs+bx]       ; get pointer to current line
        and     si,0fffh                ; only 12 bits are significant
prtsc2: mov     al,es:byte ptr [si]     ; inner loop. read text char
        mov     byte ptr [di],al        ; just store char, don't use es:
        inc     si                      ; update pointers (si needed below)
        inc     di
        loop    prtsc2                  ; do for all 132 columns, fixed format
                                ; find end of line, replace nulls with spaces
        mov     cx,swidth               ; max chars in a line
        mov     di,offset dumpbuf       ; look at start of line
prtsc3: mov     al,byte ptr [di]        ; get a byte into al
        cmp     al,0ffh                 ; end of line indicator?
        je      prtsc5                  ; e = yes, exit with count left in cx
        cmp     al,0                    ; is it a nasty null?
        jne     prtsc4                  ; ne = no
        mov     al,' '                  ; replace null with nice space
prtsc4: mov     byte ptr [di],al        ; put back into buffer
        inc     di                      ; look ahead for next char
        loop    prtsc3                  ; scan the rest of the line
prtsc5: dec     di                      ; make di point at eol address
        mov     ax,swidth               ; max line length
        sub     ax,cx                   ; minus chars scanned = length of line
        mov     cx,ax                   ; remember it here
                                        ; trim line of trailing spaces
        mov     ax,ds                   ; di needs to point to datas space
        mov     es,ax                   ; string ops use es:di
        mov     al,' '                  ; thing to scan over
        std                             ; set scan backward
        repe    scasb                   ; scan until non-space, dec's di
        cld                             ; set direction forward
        jz      prtsc6                  ; z = all spaces (count was exhausted)
        inc     cx                      ; go forward over last non-space
        inc     di                      ; ditto for address
prtsc6: mov     word ptr [di+1],0A0Dh   ; append cr/lf
        add     cx,2                    ; line count + cr/lf
        mov     dx,offset dumpbuf       ; array to be written
        mov     bx,4                    ; file handle of standard print dev
        mov     ah,write2               ; write the line
        int     dos
        pop     bx                      ; restore index for line pointer
        inc     bx                      ; add 2 for next pointer's location
        inc     bx
        pop     cx                      ; get line counter again
        loop    prtsc1                  ; do next line (needs si preset)
        pop     es
        pop     di
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret
prtscn  endp

; toggle print flag. If turning on printing, check for printer ready; skip
;  printing if not ready and beep the user. [jrd]
trnprs  proc    near
        push    ax
        test    ourflgs,fpscr           ; printing currently?
        jnz     trnpr2                  ; nz = yes, its on and going off
        mov     ah,ioctl
        mov     al,7                    ; get output status of printer
        push    bx
        mov     bx,4                    ; file handle for system printer
        int     dos
        pop     bx
        jc      trnpr1                  ; c = printer not ready
        cmp     al,0ffh                 ; Ready status?
        je      trnpr2                  ; e = Ready
trnpr1: call    beep                    ; Not Ready, complain
        jmp     trnpr3                  ; and ignore request
trnpr2: xor     ourflgs,fpscr           ; flip the flag
trnpr3: pop     ax
        clc
        ret
trnprs  endp


; Save the screen to a buffer and then append buffer to a disk file. [jrd]
; Default filename is Kermit.scn; actual file can be a device too. Filename
; is determined by mssset and is passed as pointer dmpname.
; Modified 1 Sept 1986 to do test for dump destination being ready. [jrd]

dumpscr proc    near                    ; global dump-screen procedure
        push    ax
        push    bx
        push    cx
        push    dx
        call    savscr                  ; first, save screen to memory
        mov     dmphand,-1              ; preset illegal handle
        mov     dx,offset dmpname       ; name of disk file, from mssset
        mov     ax,dx                   ; where isfile wants name ptr
        call    isfile                  ; what kind of file is this?
        jc      dmp5                    ; c = no such file, create it
        test    byte ptr filtst.dta+21,1fh ; file attributes, ok to write?
        jnz     dmp0                    ; nz = no.
        mov     al,1                    ; writing
        mov     ah,open2                ; open existing file
        int     dos
        jc      dmp0                    ; c = failure
        mov     dmphand,ax              ; save file handle
        mov     bx,ax                   ; need handle here
        mov     cx,0ffffh               ; setup file pointer
        mov     dx,-1                   ; and offset
        mov     al,2                    ; move to eof minus one byte
        mov     ah,lseek                ; seek the end
        int     dos
        jmp     dmp1

dmp5:   test    filtst.fstat,80h        ; access problem?
        jnz     dmp0                    ; nz = yes
        mov     ah,creat2               ; file did not exist
        mov     cx,20h                  ; attributes, archive bit
        int     dos
        mov     dmphand,ax              ; save file handle
        jnc     dmp1                    ; nc = ok

dmp0:   mov     dx,offset dmperr        ; say no can do
        mov     ah,prstr
        int     dos
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret
                ; read screen buffer (132 char/line), write lines to file
dmp1:   mov     ah,ioctl                ; is destination ready for output?
        mov     al,7                    ; test output status
        mov     bx,dmphand              ; handle
        int     dos
        jc      dmp0                    ; c = error
        cmp     al,0ffh                 ; ready?
        jne     dmp0                    ; ne = not ready
        push    di                      ; save regs around this work
        push    si
        mov     si,ourscr               ; buffer where screen was stored
        mov     cx,slen                 ; number of saved screen lines
dmp2:   push    cx                      ; save outer loop counter
        mov     di,offset dumpbuf       ; data segement memory (work buffer)
        mov     cx,swidth               ; number of screen columns = 132
dmp3:   mov     al,byte ptr [si]        ; read text char
        mov     byte ptr [di],al        ; store just char, don't use es:
        inc     si                      ; update pointers (si needed below)
        inc     di
        loop    dmp3                    ; do for all 132 columns, fixed format
                                ; find end of line, replace nulls with spaces
        mov     cx,swidth               ; max chars in a line
        mov     di,offset dumpbuf       ; look at start of line
dmp7:   mov     al,byte ptr [di]        ; get a byte into al
        cmp     al,0ffh                 ; end of line indicator?
        je      dmp9                    ; e = yes, exit with count left in cx
        cmp     al,0                    ; is it a nasty null?
        jne     dmp8                    ; ne = no
        mov     al,' '                  ; replace null with nice space
dmp8:   mov     byte ptr [di],al        ; put back into buffer
        inc     di                      ; look ahead for next char
        loop    dmp7                    ; scan the rest of the line
dmp9:   dec     di                      ; make di point at eol address
        mov     ax,swidth               ; max line length
        sub     ax,cx                   ; minus chars scanned = length of line
        mov     cx,ax                   ; remember it here
                                        ; trim line of trailing spaces
        push    es                      ; save register
        mov     ax,ds                   ; di needs to point to datas space
        mov     es,ax                   ; string ops use es:di
        mov     al,' '                  ; thing to scan over
        std                             ; set scan backward
        repe    scasb                   ; scan until non-space, dec's di
        cld                             ; set direction forward
        pop     es                      ; restore reg
        jz      dmp3a                   ; z = all spaces (count was exhausted)
        inc     cx                      ; go forward over last non-space
        inc     di                      ; ditto for address
dmp3a:  mov     word ptr [di+1],0A0Dh   ; append cr/lf
        add     cx,2                    ; line count + cr/lf
        mov     dx,offset dumpbuf       ; array to be written
        mov     bx,dmphand              ; need file handle
        mov     ah,write2               ; write the line
        int     dos
        pop     cx                      ; get line counter again
        loop    dmp2                    ; do next line (needs si preset)
        mov     dx,offset dumpsep       ; put in formfeed/cr/lf
        mov     cx,3                    ; three bytes overall
        mov     ah,write2
        mov     bx,dmphand
        int     dos
        mov     ah,close2               ; close the file now
        int     dos
        pop     si
        pop     di
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret
dumpscr endp

; Send a character to the host, handle local echo
sndhst  proc    near
        push ax                 ; save the character
        mov ah,al
        call outchr             ; send char in ah out the serial port
         nop
         nop
         nop
        pop ax
        test ourarg.flgs,lclecho ; echoing?
        jz sndhs2               ; z = no, exit
        call outtty             ; echo to screen
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    es
        push    ds
        call    kilcur          ; turn off cursor
        mov     di,ourscr       ; place to save screen
        mov     dx,ourattr      ; and to save attributes
        mov     ax,ds
        mov     es,ax           ; save buffer is in datas space (ds seg)
        mov     cx,slen         ; # of lines to do
        mov     ax,scrseg
        mov     ds,ax
        mov     bx,0            ; current line #
savsc1: push    cx              ; save current count
        mov     si,ds:[latofs+bx] ; get line ptr
        and     si,0fffh        ; ptr is in 12 bits
        push    si              ; save pointer
        mov     cx,swidth       ; # of chars/line
        cld
        rep     movsb           ; copy it out
        pop     si              ; restore pointer
        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
        pop     es
        ret
savscr  endp

; restore the screen saved by savscr
rstscr  proc    near
        call    cmblnk          ; start by clearing screen
        mov     si,ourscr       ; point to saved screen
        mov     dx,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

; Put a line into the circular buffer.  Pass the buffer structure in bx.
; Source is srcseg:si
; Rewritten by [jrd]
putcirc proc    near
        push    es
        push    di
        push    cx
        mov     cl,swidth               ; number of columns
        xor     ch,ch
        mov     es,[bx].orig            ; get segment of memory area
        cmp     bx,offset bwnd          ; bottom buffer?
        je      putci6                  ; e = yes
        mov     di,twnd.pp              ; pick up buffer ptr (offset from es)
        add     di,cx                   ; increment to next available slot
        add     di,cx                   ; char and attribute
        cmp     di,twnd.bend            ; would line extend beyond buffer?
        jb      putci1                  ; b = not beyond end
        mov     di,0                    ; else start at the beginning
putci1: mov     twnd.pp,di              ; update ptr
        cld                             ; set direction to forward
        mov     cx,swidth
        push    ds                      ; save regular datas seg reg
        mov     ds,srcseg               ; use source segment for ds:si
        rep     movsw                   ; copy into buffer
        pop     ds                      ; restore regular datas segment
        mov     cx,twnd.lmax            ; line capacity of buffer
        dec     cx                      ; minus one work space line
        cmp     twnd.lcnt,cx            ; can we increment line count?
        jae     putci1b                 ; ae = no, keep going
        inc     twnd.lcnt               ; else count this line
putci1b:cmp     bwnd.lcnt,0             ; any lines in bottom buffer?
        je      putci2                  ; e = no
        mov     cx,bwnd.pp              ; see if we overlap bot buf
        cmp     cx,twnd.pp              ; is this line in bot buf area?
        jne     putci2                  ; ne = no
        add     cl,swidth               ; move bottom pointer one slot earlier
        adc     ch,0
        add     cl,swidth               ; words
        adc     ch,0
        cmp     cx,bwnd.bend            ; beyond end of buffer?
        jb      putci1a                 ; b = no
        mov     cx,0                    ; yes, start at beginning of buffer
putci1a:mov     bwnd.pp,cx              ; new bottom pointer
        dec     bwnd.lcnt               ; one less line in bottom buffer
putci2: pop     cx
        pop     di
        pop     es
        ret
putci6:                                 ; bottom buffer
        add     cx,cx                   ; words worth
        cmp     bwnd.lcnt,0             ; any lines in the buffer yet?
        jne     putci7                  ; ne = yes
        mov     di,twnd.pp              ; get latest used slot of top buff
        add     di,cx                   ; where first free (?) slot starts
        cmp     di,bwnd.bend            ; are we now beyond the buffer?
        jb      putci6a                 ; b = no
        mov     di,0                    ; yes, start at beginning of buffer
putci6a:add     di,cx                   ; start of second free (?) slot
        cmp     di,bwnd.bend            ; are we now beyond the buffer?
        jb      putci6b                 ; b = no
        mov     di,0                    ; yes, start at beginning of buffer
putci6b:mov     cx,twnd.lmax            ; buffer line capacity
        sub     cx,twnd.lcnt            ; minus number used by top buffer
        sub     cx,2                    ; minus one work slot and one we need
        cmp     cx,0                    ; overused some slots?
        jge     putci8                  ; ge = enough to share
        add     twnd.lcnt,cx            ; steal these from top window beginning
        jmp     short putci8

putci7: mov     es,bwnd.orig            ; get segment of memory area
        mov     di,bwnd.pp              ; pick up buffer ptr (offset from es)
        cmp     di,0                    ; would line start before buffer?
        jne     putci7a                 ; ne = after start of buffer
        mov     di,bwnd.bend            ; else start at the end minus one slot
        inc     di
putci7a:sub     di,cx
putci8: mov     bwnd.pp,di              ; update ptr (this is latest used slot)
        mov     cl,swidth
        xor     ch,ch
        cld                             ; set direction to forward
        push    ds                      ; save regular datas seg reg
        mov     ds,srcseg               ; use source segment for ds:si
        rep     movsw                   ; copy into buffer
        pop     ds                      ; restore regular datas segment
        mov     cx,bwnd.lmax            ; line capacity of buffer
        cmp     bwnd.lcnt,cx            ; can we increment line count?
        jae     putci8b                 ; ae = no, keep going
        inc     bwnd.lcnt               ; else count this line
putci8b:cmp     twnd.lcnt,0             ; any lines in top line buf?
        je      putci9                  ; e = no
        mov     cx,twnd.pp              ; yes, see if we used last top line
        cmp     cx,bwnd.pp              ; where we just wrote
        jne     putci9                  ; not same place, so all is well
        dec     twnd.lcnt               ; one less line in top window
        cmp     cx,0                    ; currently at start of buffer?
        jne     putci8a                 ; ne = no
        mov     cx,twnd.bend            ; yes
        inc     cx
putci8a:sub     cl,swidth               ; back up top window
        sbb     ch,0
        sub     cl,swidth               ; by one line
        sbb     ch,0
        mov     twnd.pp,cx              ; next place to read
putci9: pop     cx
        pop     di
        pop     es
        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.
; Destination preset in es:di.
; Rewritten by [jrd]
getcirc proc    near
        cmp     [bx].lcnt,0             ; any lines in buffer?
        jne     getci1                  ; ne = yes, ok to take one out
        stc                             ; else set carry
        ret                             ; and return
getci1: push    cx                      ; top and bottom window common code
        push    si
        mov     cl,swidth               ; # of chars to copy
        xor     ch,ch
        push    di                      ; save destintion offset
        push    cx                      ; save around calls
        mov     si,[bx].pp              ; this is source
        cld                             ; set direction to forward
        push    ds                      ; save original ds
        mov     ds,[bx].orig            ; use seg address of buffer for si
        rep     movsw
        pop     ds                      ; recover original data segment
        pop     cx                      ;
        pop     di                      ; recover destination offset

        push    cx                      ; save again
        mov     si,[bx].pp              ; get ptr again
        pop     cx
        add     cx,cx                   ; words
        cmp     bx,offset bwnd          ; bottom window?
        je      getci6                  ; e = yes
        sub     si,cx                   ; top window, move back
        jnc     getcir2                 ; nc = still in buffer, continue
        mov     si,twnd.bend            ; else use end of buffer
        sub     si,cx                   ; minus length of a piece
        inc     si
getcir2:mov     twnd.pp,si              ; update ptr
        dec     twnd.lcnt               ; decrement # of lines in buffer
        pop     si
        pop     cx
        clc                             ; make sure no carry
        ret
getci6:                                 ; bottom window
        add     si,cx                   ; words, move back (bot buf = reverse)
        cmp     si,bwnd.bend            ; still in buffer?
        jb      getci7                  ; b = yes
        mov     si,0                    ; else use beginning of buffer
getci7: mov     bwnd.pp,si              ; update ptr
        dec     bwnd.lcnt               ; decrement # of lines in buffer
        pop     si
        pop     cx
        clc                             ; make sure no carry
        ret
getcirc endp

; prepares for scrolling by saving the top line in topbuf.
scrprep proc    near
        push    ax              ; save regs
        push    es
        cmp     al,cr           ; carriage return?
        je      scrpr3          ; yes, will never change line
        cmp     al,lf           ; outputting a linefeed?
        je      scrpr2          ; yes, will change line
        mov     ax,scrseg
        mov     es,ax           ; address screen segment
        test    es:byte ptr [curlin],wrpend ; wrap pending?
        jz      scrpr3          ; no, forget it
        mov     ax,nvmseg
        mov     es,ax
        test    es:byte ptr [autwrp],1 ; auto-wrap mode?
        jz      scrpr3          ; no, forget this
                                ; about to change lines, see if bottom line
scrpr2: mov     ax,scrseg
        mov     es,ax
        cmp     es:byte ptr [csrlin],slen ; are we at the bottom?
        je      scrpr4          ; yes, have to save line
scrpr3: pop     es              ; get here if not saving line
        pop     ax
        ret
scrpr4: pop     es              ; restore registers
        pop     ax
; alternate entry that doesn't check if we're on the bottom row.
savtop: push    ax              ; save ax
        push    bx
        push    cx
        push    si
        push    di
        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
        and     si,0fffh        ; only 12 bits are significant
        push    si
        mov     di,offset topline ; this is where it goes
        mov     cx,swidth       ; # of bytes to copy
        cld
        rep     movsb           ; get the top line
        pop     si              ; restore pointer
        add     si,attoffs      ; add offset of attributes
        mov     cx,swidth
        rep     movsb           ; get top line's attributes
        pop     ds
        pop     es              ; restore segments
        mov     srcseg,seg topline ; set segment of source
        mov     si,offset topline  ; set offset of source
        mov     bx,offset twnd  ; buffer structure pointer
        call    putcirc         ; put into circular buffer
        call    rstcur
        pop     di
        pop     si
        pop     cx
        pop     bx
        pop     ax              ; restore character in ax
        ret                     ; and return
scrprep endp


; get the screen's bottom line into the buffer in ax.
getbot  proc    near
        push    cx
        push    si
        push    di
        push    es
        push    ds
        push    ax              ; save destination on the stack
        call    kilcur          ; kill cursor
        push    ds
        pop     es
        mov     si,scrseg
        mov     ds,si
        mov     si,ds:word ptr [llptr] ; get ptr to bottom line
        and     si,0fffh        ; only 12 bits are pointer
        pop     di              ; destination is on stack
        push    si              ; preserve pointer
        mov     cx,swidth       ; # of bytes to copy
        cld
        rep     movsb           ; get the top line
        pop     si              ; get pointer back
        add     si,attoffs      ; this is where attributes are
        mov     cx,swidth
        rep     movsb           ; copy attributes as well
        pop     ds              ; restore segments
        pop     es
        call    rstcur          ; restore cursor
        pop     di
        pop     si
        pop     cx
        ret
getbot  endp

; handle the previous screen button...

prvscr  proc    near
        mov     cx,slen
        cmp     twnd.lcnt,cx
        jge     prvs1
        mov     cx,twnd.lcnt
prvs1:  jcxz    prvs2
        call    prvlin
        loop    prvs1
prvs2:  clc
        ret
prvscr  endp

; handle the next screen button...

nxtscr  proc    near
        mov     cx,slen
        cmp     bwnd.lcnt,cx
        jge     nxts1
        mov     cx,bwnd.lcnt
nxts1:  jcxz    nxts2
        call    nxtlin
        loop    nxts1
nxts2:  clc
        ret
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
        mov     cx,slen         ; # of lines to save
        cmp     cx,[bx].lcnt    ; enough space left in this buffer?
        jbe     rolsc0          ; be = enough
        mov     cx,[bx].lcnt    ; use only as many as we have
        jcxz    rolscx          ; z = none, so quit here
rolsc0: shl     dx,1            ; double increment for word ptr
        dec     bx              ; ptr starts at 0
        shl     bx,1            ; convert to word ptr
        push    es
        push    ds
        pop     es              ; set es to datas segment
        mov     temp,0          ; save number of lines done

rolsc1: push    cx
        push    dx
        push    bx
        push    ax
        push    ds
        call    kilcur          ; kill cursor
        mov     di,offset rlbuf
        mov     ax,scrseg
        mov     ds,ax           ; address screen
        mov     si,ds:[latofs+bx] ; get current line
        and     si,0fffh        ; ptr is in 12 bits
        push    si              ; save pointer
        mov     cx,swidth       ; # of bytes to move
        rep     movsb           ; get the lne
        pop     si              ; restore pointer
        add     si,attoffs      ; where attributes start
        mov     cx,swidth       ; # of bytes to move
        rep     movsb           ; move attributes as well
        pop     ds              ; restore segment
        call    rstcur          ; restore cursor
        pop     bx              ; this is desired circ buffer ptr
        mov     srcseg,seg rlbuf ; segment of source
        mov     si,offset rlbuf ; offset of source
        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
        inc     temp
        loop    rolsc1          ; loop thru all lines
        pop     es
rolscx: ret                     ; and return
rolscr  endp

; move screen down a line, get one previous line back

prvlin  proc    near            ; get the previous line back
        push    ax
        push    bx
        push    dx
        cmp     twnd.lcnt,0     ; any lines in top window?
        je      prvli1          ; e = no, ignore request
        mov     ax,offset botline ; place for bottom line
        call    getbot          ; fetch bottom line
        mov     srcseg,seg botline ; segement of source
        mov     si,offset botline       ; offset of source
        mov     bx,offset bwnd  ; buffer structure pointer
        call    putcirc         ; save in circular buffer
        mov     bx,offset twnd          ; source structure
        push    es
        mov     di,seg topline
        mov     es,di
        mov     di,offset topline ; es:di is address of destination
        call    getcirc         ; try to get a line
        pop     es
        jc      prvli1          ; no more, just return
        call    savpos          ; save cursor position
        call    kilcur          ; turn off cursor
        mov     dx,offset topdwn ; home, then reverse index
        call    tmsg
        mov     ax,offset topline ; point to data
        mov     bx,0101H        ; print line at top of screen
        mov     dx,ax
        add     dx,swidth
        call    prlina          ; print the line
        call    rstcur
        call    rstpos          ; restore cursor position
prvli1: pop     dx
        pop     bx
        pop     ax
        clc
        ret                     ; and return
prvlin  endp

; move screen up a line, get one bottom line back
nxtlin  proc    near
        push    ax
        push    bx
        push    dx
        cmp     bwnd.lcnt,0     ; any lines in bottom window?
        je      nxtli1          ; e = no
        mov     bx,offset bwnd          ; source structure
        push    es
        mov     di,seg botline
        mov     es,di
        mov     di,offset botline ; es:di is address of destination
        call    getcirc         ; try to get a line
        pop     es
        jc      nxtli1          ; no more, just return
        call    savtop          ; save one line off of top
        call    savpos          ; save cursor position
        call    kilcur          ; turn off cursor
        mov     dx,offset botup ; go to bottom, then scroll up a line
        call    tmsg
        mov     ax,offset botline ; point to data
        mov     bx,0100H + slen ; print at bottom line
        mov     dx,ax
        add     dx,swidth
        call    prlina          ; print the line
        call    rstcur          ; turn cursor back on
        call    rstpos          ; restore cursor position
nxtli1: pop     dx
        pop     bx
        pop     ax
        clc
        ret                     ; and return
nxtlin  endp

; move screen up until no more saved in bottom buffer [jrd]
nxtbot  proc    near
        push    cx
        mov     cx,bwnd.lcnt    ; number of pages of scroll back memory
nxtbot1:push    cx
        call    nxtlin
        pop     cx
        loop    nxtbot1         ; do all pages
        pop     cx
        clc
        ret
nxtbot  endp

nxttop  proc    near            ; move to top of screen buffer memory [jrd]
        push    cx
        mov     cx,twnd.lcnt    ; number of pages of scroll back memory
nxttop1:push    cx
        call    prvlin
        pop     cx
        loop    nxttop1         ; do all pages
        pop     cx
        clc
        ret
nxttop  endp

; save cursor position
savpos  proc    near
        push    di
        mov     dx,offset curinq ; where is the cursor?
        call    tmsg
        mov     posbuf,escape   ; put an escape in the buffer first
        mov     di,offset posbuf+1
savpo1: mov     ah,8            ; read, no echo
        int     dos
        cld
        cmp     al,'R'          ; end of report?
        je      savpo2          ; yes
        stosb                   ; no, save it
        jmp     short 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
        pop     di
        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    ax
        push    bx
        push    cx
        push    dx
        push    si
        push    es
        push    di
        mov     di,kcurfn
        int     firmwr
        pop     di
        pop     es
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret
kilcur  endp

; restore the cursor
rstcur  proc    near
        push    ax
        push    bx
        push    cx
        push    dx
        push    si
        push    es
        push    di
        mov     di,rcurfn
        int     firmwr
        pop     di
        pop     es
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        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    ax              ; save regs
        push    cx
        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     si,ax           ; better place for ptr
        mov     di,ax           ; need it here for scan
        mov     al,0ffh         ; this marks the end of the line
        cld
        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
        push    bx
        push    dx
        push    si
        push    di
        mov     di,14H          ; fast write to screen
        int     firmwr
        pop     di
        pop     si
        pop     dx
        pop     bx
prli3:  pop     cx              ; restore registers
        pop     ax
        pop     es
        ret                     ; and return
prlin   endp

; action routines for keyboard translator.
; These are invoked by a jump instruction. Return carry clear for normal
; processing, return carry set for invoking Quit (kbdflg has transfer char).

uparrw: mov     al,'A'                  ; cursor keys
        jmp     short comarr
dnarrw: mov     al,'B'
        jmp     short comarr
rtarr:  mov     al,'C'
        jmp     short comarr
lfarr:  mov     al,'D'
comarr: push    ax                      ; save final char
        mov     al,escape               ; Output an escape
        call    sndhst                  ; Output, echo permitted
        push    es                      ; save seg register
        mov     ax,nvmseg               ; fetch address of nvm
        mov     es,ax                   ; put in segment reg
        test    byte ptr es:[vt52mod],1 ; check bit zero
        pop     es                      ; restore the seg register
        jnz     comar1                  ; nz = ansi mode
        jmp     comar3                  ; VT52 mode
comar1: mov     al,'['                  ; Maybe this next?
        cmp     ckeyflg,0               ; applications cursor mode?
        je      comar2                  ; e = no
        mov     al,'O'                  ; applications mode
comar2: call    sndhst                  ; Output it (echo permitted)
comar3: pop     ax                      ; recover final char
        call    sndhst                  ; Output to port (echo permitted)
        clc
        ret

pf1:    mov     al,'P'                  ; keypad function keys
        jmp     short compf
pf2:    mov     al,'Q'
        jmp     short compf
pf3:    mov     al,'R'
        jmp     short compf
pf4:    mov     al,'S'
compf:  push    ax                      ; save final char
        mov     al,escape               ; Output an escape
        call    prtbout
        push    es                      ; save seg register
        mov     ax,nvmseg               ; fetch address of nvm
        mov     es,ax                   ; put in segment reg
        test    byte ptr es:[vt52mod],1   ; check bit zero
        pop     es                      ; restore the seg register
        jz      compf1                  ; z = VT52 mode
        mov     al,'O'                  ; send an "O" in ansi mode
        call    prtbout                 ; Output it
compf1: pop     ax                      ; Get the saved char back
        call    prtbout                 ; Output to port
        clc
        ret

kp0:    mov     al,'p'                  ; keypad numeric keys
        jmp     short comkp
kp1:    mov     al,'q'
        jmp     short comkp
kp2:    mov     al,'r'
        jmp     short comkp
kp3:    mov     al,'s'
        jmp     short comkp
kp4:    mov     al,'t'
        jmp     short comkp
kp5:    mov     al,'u'
        jmp     short comkp
kp6:    mov     al,'v'
        jmp     short comkp
kp7:    mov     al,'w'
        jmp     short comkp
kp8:    mov     al,'x'
        jmp     short comkp
kp9:    mov     al,'y'
        jmp     short comkp
kpminus:mov     al,'m'
        jmp     short comkp
kpcoma: mov     al,'l'
        jmp     short comkp
kpenter:mov     al,'M'
        jmp     short comkp
kpdot:  mov     al,'n'
comkp:  cmp     akeyflg,0               ; alternate keypad mode?
        jne     comkp1                  ; ne = yes
        sub     al,'p'-'0'              ; change to numeric codes
        jmp     comkp3                  ; and send just the ascii char
comkp1: push    ax                      ; save final char
        mov     al,escape               ; Output an escape
        call    prtbout
        mov     al,3fh                  ; Output the "?" in VT52 mode
        push    es                      ; save seg register
        mov     cx,nvmseg               ; fetch address of nvm
        mov     es,cx                   ; put in segment reg
        test    byte ptr es:[vt52mod],1   ; check bit zero
        pop     es                      ; restore the seg register
        jz      comkp2                  ; z = VT52 mode
        mov     al,'O'                  ; Output the "O" in ansi mode
comkp2: call    prtbout
        pop     ax                      ; recover final char
comkp3: call    prtbout                 ; send it
        clc
        ret

snull   proc    near                    ; send a null byte
        mov     al,0                    ; the null
        call    prtbout                 ; send without logging and local echo
        clc
        ret
snull   endp

chrout: push    es                      ; save segment
        push    bx
        mov     bx,nvmseg               ; point to nvm
        mov     es,bx                   ; set the segment
        test    byte ptr es:[newlmod],1 ; check if we are set to new line
        pop     bx
        pop     es                      ; restore the segment register
        jz      chrout1                 ; just send the cr if bit is off
        call    sndhst                  ; else send the carriage return first
        mov     al,lf                   ; then the line-feed
chrout1:call    sndhst                  ; send char in al to serial port
        clc                             ; for keyboard translator
        ret                             ; can echo and log


prtbout:mov     ah,al                   ; output char with no echo
        call    outchr                  ; outchr works with ah
         nop
         nop
         nop
        clc
        ret

cdos:   mov     al,'P'                  ; Connect mode help screen items
        jmp     short cmdcom
cstatus:mov     al,'S'                  ; these commands invoke Quit
        jmp     short cmdcom
cquit:  mov     al,'C'                  ; C = exit connection
        jmp     short cmdcom
cquery: mov     al,'?'                  ; help
        jmp     short cmdcom
chang:  mov     al,'H'                  ; Hangup, drop DTR & RTS
        jmp     short cmdcom
cmdcom: mov     kbdflg,al               ; pass char to msster.asm via kbdflg
        stc                             ; signal that Quit is needed
        ret

klogon  proc    near                    ; resume logging (if any)
        test    flags.capflg,logses     ; session logging enabled?
        jz      klogn                   ; z = no, forget it
        or      ourarg.flgs,capt        ; turn on capture flag
        or      argadr.flgs,capt        ; permanent argument array too
klogn:  clc
        ret
klogon  endp

klogof  proc    near                    ; suspend logging (if any)
        and     argadr.flgs,not capt    ; stop capturing
        and     ourarg.flgs,not capt    ; stop capturing
klogo:  clc
        ret
klogof  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