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

⟦0a14a7f78⟧ TextFile

    Length: 79591 (0x136e7)
    Types: TextFile
    Names: »msyap3.asm«

Derivation

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

TextFile

        NAME msyap3
; File MSYAP3.ASM;

; NEC APC III system dependent module (taken from msyibm.asm).
;  Much EGA and other screen support commented out from ibm code.
; NEC modifications by Robert F. Goeke
; Last Edit: 14 March 1988
; edit history:
; 15 Mar 1988 Incorporate latest IBM mods for NEC

; Following comments from msyibm.asm code:
; 5 Jan 1988 Restore cursor codes broken by Tek code additions. [jrd]
; 1 Jan 1988 version 2.30
; 24 Dec 1987 Restore startup screen attributes at Kermit prompts. [jrd]
; 21 Dec 1987 Fix memory size sign problem for >640K systems. From Edgar Butt
; 4 Dec 1987 cleanup mode switching, add more Video 7 material. [jrd]
; 8 Nov 1987 Add EGA mode switching, from Terry Kennedy.
; 1 Nov 1987 Add support for Tektronix, based on work by Brian Holley. [jrd]
; 13 Oct 1987 Revise memory allocation sequence to avoid small holes. [jrd]
; 2 Oct 1987 Make log file character width match Set Display but 8 bits when
;  debugging. [jrd]
; 12 Sept 1987 clarify sequence of translation and 8 bit display. [jrd]
; 27 Aug 1987 Do Translation before logging. [jrd]
; 18 Aug 1987 Change ESC to escape for MASM 4.5+ [jrd]
; 28 July 1987 Fix scron problem in screen save. [jrd]
; 23 June 1987 Add plain_attribute macro; fix bug in circular buffer
;  routines which kept attributes from being stored (and replayed)
; 8 June 1987 Add keypad application mode tests to emit single chars. [jrd]
; 6 June 1987 Adapt to most recent msyibm file (keyboard translator et al)
;  [jrd]
; 10 May 1987 Move input translation into terminal emulator, leave copy
;  here for terminal type None, use mszibm byte anspflg to sense print
;  screen is active, print translated characters but don't translate if
;  debugging is active. [jrd]
; 28 March 1987 Make low_rgt screen coord word a global parameter.
;  Add support for variable length screens and cursor size changes with
;  EGA boards. Tests ok with 25, 35, 43, 50 lines with &/without MS Windows.
;  EGA Memory locations 40:84H and 40:87H are used in this process.
;  Use savadr dw as place to save screen: usually screen page 1 if screen
;  dimensions are non-standard (80x25), else memory buffer scrsav. [jrd]
; 21 March 1987 Translate arriving Connect mode chars via table rxtable. [jrd]
;  Add 132 Column support for Tseng Labs EVA board via procedure chgdsp,
;  add restore scrolled screen before writing to it. From David L. Knoell [dlk]
; Modify msy and msz to use variable screen length and widths. [dlk] and [jrd]
; 17 March 1987 Reduce screen roll back buffer to half the memory to do the
;  same number of screens. [jrd]
; 12 Jan 1987 Add keyboard translator, remove older code. [jrd]
; 1 Oct 1986 Version 2.29a

        public  term, lclyini                      ; entry points
        public  prtbout, prtnout, csrtype, scrmod, scrseg, scrsync
        public  scroff, scron, atsclr, vtscru, vtscrd, scrloc, trnmod, telmsy
        public  chgdsp, vtroll
                        ; action verb procedures for keyboard translator
        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, dmpscn, vtans52, vtinit, dnwpg, upwpg, endwnd, homwnd
        public  upone, dnone, trnprs, dumpscr, modlin, modwrt, snull
        public  klogon, klogof, cdos, chang

        public  vtemu, crt_mode, scbattr, refresh, low_rgt  ; data
	public  crt_cols, crt_lins, savescr, restscr, getflgs
        include mssdef.h

; some definitions
; NEC APC III hardware
screen  equ     19h                     ; bios screen call
kb      equ     18h                     ; keyboard interrupt
vram    equ     0A000H                  ; Video Ram
alt_shift equ   8H                      ; alt shift key down
ctl_shift equ   4H                      ; ctl key down
left_shift equ  2H                      ; left shift key down
; right_shift equ 1H                      ; right shift key down
func_shift equ  1H                      ; an NEC mod                    RFG

biostty equ     0eh                     ; Bios screen tty write mode [jrd]

modfrm  struc                           ; format of mode (status) line
        db      'Esc-chr: '             ; do not write in last column.
m_echr  db      2 dup (?)
        db      '  help: '
m_hlp   db      2 dup (?)
        db      '?  port:'
m_prt   db      1 dup (?)
        db      ' speed:'
m_baud  db      5 dup (?)
        db      ' parity:'
m_par   db      4 dup (?)
        db      ' echo:'
m_echo  db      3 dup (?)
m_term  db      13 dup (' ')            ; 13 bytes for term type
m_prn   db      3 dup (' ')             ; show PRN when printer is on [jrd]
modfrm  ends

; This macro flips the rev_video bit of attribute in ah.    RFG
; NB this neither changes any other attribute nor any other register
flip_rev_video  macro
                local   flip,flop
                test    ah,att_rev_video
                jnz     flip
                or      ah,att_rev_video
                jmp     flop
flip:           and     ah,not att_rev_video
flop:           nop
                endm

; This macro makes takes the character attributes in ah and makes them plain
; Different than IBM case 'cause we don't really have "intensity".       RFG
plain_attribute macro
                and     ah,not(att_overline+att_blink+att_underline)
                endm

att_overline    equ     01H             ; this is all NEC version stuff RFG
att_blink       equ     02H
att_rev_video   equ     04H
att_underline   equ     08H
att_intensity   equ     04H             ; same as reverse video

datas   segment public 'datas'
        extrn flags:byte, mar_top:byte, mar_bot:byte, portval:word
        extrn filtst:byte, dmpname:byte, kbdflg:byte, rxtable:byte
        extrn anspflg:byte, tekflg:byte

; stuff for screen routines
yflags  db      ?                       ; status flags...
flags1  db      0                       ; internal flags (but used in mszibm).
prtscr  equ     1                       ; print screen pressed
inited  equ     08h                     ; been here before...
vtinited db     0                       ; flag for emulator having been inited
cursor  dw      ?
esc_ch  db      ?
parmsk  db      ?                       ; 8/7 bit parity mask, for reception
argadr  dw      ?                       ; address of arg blk

savadr  dw      2 dup (?)               ; offset then segment of saved screen
savflg  dw      ?                       ; low_rgt at time of screen save


vtemu   emulst  <>                      ; emulator flags [jrd]
ansflgs db      0                       ; ANSI flags
trmtyp  db      0                       ; most recent terminal type
mtty    db      '  TTY   '              ; no terminal type (mode line)

lincur  dw      ?                       ; cursor type save area
scbattr db      ?                       ; Screen background attribute
oldattr db      ?                       ; screen attributes at init time
curattr db      ?                       ; current attribute
temp    dw      ?                       ; scratch storage
modtemp db      0                       ; temp to hold Kermit modeline status
captrtn dw      ?                       ; routine to call for captured output
dmphand dw      ?                       ; screen dump file handle 
dumpbuf db      132 dup (?), cr, lf     ; 134 byte dump work buffer
dumpsep db      FF,cr,lf                ; screen image separators
dmperr  db      ' Cannot open file to save screen to disk $'
crlf    db      cr,lf,'$'

; some static data for mode line
modbuf  modfrm  <>                      ; mode line buffer
unkbaud db      'unkwn'                 ; must be 5 chars...
baudn   db      ' 45.5',' 50  ',' 75  ',' 110 ','134.5',' 150 ',' 300 ',' 600 '
        db      ' 1200',' 1800',' 2000',' 2400',' 4800',' 9600','19200','38400'
        db      '57.6K','115 K'
baudnsiz  equ   18                      ; # of baud rates known (tbl size / 4)
parnams db      'even','mark','none','odd ','spc '
lclmsg  db      'loc'
remmsg  db      'rem'
portno  db      ?

; storage for multi-window stuff
swidth  equ     80                      ; max screen width
slen    equ     24                      ; and length of text
npages  equ     10                      ; # of pages of scrolling on each side
crt_norm db     ?                       ; video mode for normal screen
crt_mode db     ?                       ; video mode (typ 3, must be text)
crt_cols db     ?                       ; number of screen columns (typ 80)
crt_lins db     24                      ; number of screen rows - 1 (typ 24)
low_rgt dw      ?                       ; lower right corner of text window
                                        ; high = row address (typ 23)
                                        ; low = column address (typ 79)
inipara dw      ?                       ; initial paragraphs of scroll memory
refresh db      0                       ; screen refresh (0=wait for retrace)
vtroll  db      0                       ; auto roll back allowed (0 = no).

; circular buffer for screen roll back.
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. [jrd]
cbuf    ends

twnd    cbuf    <>                      ; top screen spill-buffer struct
bwnd    cbuf    <>                      ; bottom screen spill buffer struct

datas   ends

code    segment public 'code'                   ; code segment
        extrn   beep:near, prtchr:near, outchr:near, sbrk:near, pcwait:near
        extrn   isfile:near, strlen:near, strcpy:near   ; in mssfil
        extrn   anstty:near,ansini:near,ansrei:near     ; in mszibm
        extrn   anstat:near,anskbi:near,ansdsl:near     ; in mszibm
        extrn   ans52t:near, vsinit:near                ; in mszibm
        extrn   msuinit:near, keybd:near                ; in msuibm
        extrn   tekini:near,tekcls:near,tekemu:near,tekend:near ;in msgibm

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

; do initialization local to this module...
; Dynamically allocates 4000 bytes for screen save/restore buffer plus
;  320 to 38400 bytes for screen scroll back buffers. Tries to leave space
;  for Command.com before enlarging buffers. [jrd]
; delete screen dump memory allocation; see savescr                     RFG
lclyini proc    near
        call    msuinit                 ; initialize keyboard module msuxxx
        mov     ax,swidth               ; ask for two lines (1 per buffer)
        add     ax,ax
        add     ax,ax                   ; times four (2 lines of char + attrib)
        call    sbrk                    ; allocate mem. Exit Kermit on failure
                                        ;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     inipara,bx              ; save for later resizing of buffers
        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
        call    scrseg                  ; test running in an Environment
        call    scrmod                  ; read video state, get crt_mode.
        mov     ah,8                    ; read current attributes
        xor     bh,bh                   ; page 0
        int     screen
        mov     scbattr,ah              ; save video attributes
        mov     oldattr,ah              ; and here too
        call    vsinit                  ; init terminal emulator module MSZ
        ret
lclyini endp

scrini  proc    near                    ; init screen stuff
        call    scrmod                  ; get screen mode, low_rgt
        mov     ah,3                    ; get cursor position and char.
        xor     bh,bh                   ; page 0
        int     screen
        mov     lincur,cx               ; save cursor type (scan line #'s)
        mov     dx,cursor               ; assume old cursor
        test    flags1,inited           ; have we been here before?
        jnz     scrin4                  ; nz = yes, use old cursor
        mov     ah,oldattr              ; get init time attributes
        mov     curattr,ah              ; and set nice screen attribute
        mov     scbattr,ah
        mov     ah,3                    ; figure out where cursor is
        xor     bh,bh                   ; page 0
        int     screen                  ; read cursor position, in dx
scrin4: cmp     dh,byte ptr low_rgt+1   ; past logical end of screen?
        jb      scrin2                  ; b = no, keep going
        mov     dh,byte ptr low_rgt+1   ; yes, just use lower right corner
scrin2: cmp     dl,byte ptr low_rgt     ; maybe past right margin
        jb      scrin3                  ; b = no, use the way it is
        mov     dl,byte ptr low_rgt
scrin3: mov     cursor,dx               ; init cursor
        mov     ah,2                    ; set cursor position
        xor     bh,bh                   ; page zero
        int     screen                  ; set cursor in case it moved
        ret
scrini  endp

; Routine to initialize terminal emulator. Call once.

vtinit  proc    near
        cmp     flags.vtflg,0           ; doing emulation?
        je      vtinix                  ; e = no
        cmp     tekflg,0                ; Tek mode active?
        jne     vtini2                  ; ne = yes, do it's reinit
        or      vtinited,inited
        call    ansflg                  ; update ansi flags
        mov     al,yflags               ; Pass the flags.
        mov     bx,argadr               ; Get address of argument block
        mov     dl,[bx].baudb           ; Baud rate code in dl
        mov     dh,[bx].parity          ; Parity code in bits
        mov     cl,4                    ; 0-3 of dh
        shl     dh,cl
        test    flags.remflg,d8bit      ; eight bit display?
        jnz     vtini1                  ; nz = yes
        or      dh,07H                  ; Just say 7 data bits.
        call    ansini                  ; call startup routine in mszibm.
        ret
vtini1: or      dh,8                    ; say 8 bits
        call    ansini
vtinix: clc
        ret
vtini2: call    tekcls                  ; clear Tek screen
        clc
        ret
vtinit  endp


argini  proc    near                    ; read passed arguments
        mov     bx,argadr               ; base of argument block
        mov     al,[bx].flgs            ; get flags
        and     al,capt+emheath+havtt+trnctl+lclecho+modoff+lnwrap
        mov     yflags,al               ; mask for allowable and save
        mov     al,[bx].prt
        mov     portno,al               ; update port number
        mov     al,[bx].rows
        mov     crt_lins,al             ; init # of rows and cols
        mov     ax,[bx].captr
        mov     captrtn,ax              ; buffer capture routine
        mov     al,[bx].escc
        mov     esc_ch,al
        mov     parmsk,0ffh             ; parity mask, assume parity = None
        cmp     [bx].parity,parnon      ; is parity None?
        je      argini1                 ; e = yes, keep all 8 bits
        mov     parmsk,07fh             ; else keep lower 7 bits
argini1:ret				; that's it

argini  endp

modlin  proc    near                    ; turn on mode line
        mov     al,esc_ch
        mov     modbuf.m_echr,' '       ; first char is initial space
        mov     modbuf.m_hlp,' '        ; goes here too.
        cmp     al,32                   ; printable?
        jnb     modl1                   ; yes, keep going
        add     al,40h                  ; made printable
        mov     modbuf.m_echr,5eh       ; caret, note control char
        mov     modbuf.m_hlp,5eh
modl1:  mov     modbuf.m_echr+1,al      ; fill in character
        mov     modbuf.m_hlp+1,al
        mov     bx,argadr               ; get argument block
        mov     al,[bx].baudb           ; get baud bits
        mov     si,offset unkbaud       ; assume unknown baud
        cmp     al,baudnsiz             ; too big?
        jnb     modl2                   ; nb = yes, use default
        mov     cl,size m_baud          ; each is 5 bytes long
        mul     cl
        mov     ah,0
        add     ax,offset baudn
        mov     si,ax
modl2:  mov     cx,size m_baud          ; length of baud space
        mov     di,offset modbuf.m_baud
        push    es                      ; save es
        push    ds
        pop     es                      ; set es to datas segment
        cld
        rep     movsb                   ; copy in baud rate
        mov     al,[bx].parity          ; get parity code
        mov     cl,2                    ; each is 4 bytes long...
        shl     al,cl
        mov     ah,0
        add     ax,offset parnams       ; names of parity settings
        mov     si,ax
        mov     cx,4                    ; each is 4 long
        mov     di,offset modbuf.m_par
        rep     movsb
        mov     si,offset remmsg        ; Assume remote echoing.
        test    yflags,lclecho          ; Is remote side echoing?
        jz      modl4                   ; Yes, keep going
        mov     si,offset lclmsg        ; Else it's local echoing.
modl4:  mov     cx,3                    ; size of on/off
        mov     di,offset modbuf.m_echo
        rep     movsb
        mov     al,portno               ; communications port
        cmp     al,' '                  ; binary (non-printable)?
        jae     modl5                   ; ae = no, ascii
        add     al,'0'                  ; convert to ascii
modl5:  mov     modbuf.m_prt,al         ; fill in port number
        mov     cx,8                    ; blank out terminal id field
        mov     si,offset mtty          ; assume no terminal emulation.
        mov     di,offset modbuf.m_term ; destination
        rep     movsb                   ; copy it in.
        mov     modbuf.m_prn,' '        ; assume not printing the screen [jrd]
        mov     modbuf.m_prn+1,' '
        mov     modbuf.m_prn+2,' '
        test    anspflg,prtscr          ; doing a print the screen?
        jz      modl5a                  ; z = no.
        mov     modbuf.m_prn,'P'        ; yes. display PRN at end of line
        mov     modbuf.m_prn+1,'R'
        mov     modbuf.m_prn+2,'N'
modl5a: mov     cx,size modfrm          ; this is size of mode line
        mov     si,offset modbuf        ; mode line image
        pop     es
                        ; alternate entry to write an alternate mode line
modwrt: push    cx
        push    si                      ; save mode line and size
        mov     ah,3                    ; read cursor position
        xor     bx,bx                   ; screen page 0
        int     screen
        mov     cursor,dx               ; save cursor position
        call    trmatt                  ;[IU2] Get terminal attributes
        plain_attribute
        mov     bh,ah                   ; get video attribute
        mov     dx,low_rgt              ; right most column
        inc     dh                      ; refer to status line
        mov     ch,dh                   ; bottom line [dlk]
        mov     cl,0                    ; left col = 0 (first) [dlk]
        mov     ax,600h                 ; scroll to clear the line
        int     screen
        mov     dh,byte ptr low_rgt+1   ; refer to status line
        inc     dh
        xor     dl,dl                   ; left most column
        mov     bh,0
        mov     ah,2                    ; set cursor position
        int     screen
        pop     si
        pop     cx                      ; restore these
        cmp     cl,crt_cols             ; mode line longer than screen?
        jbe     modl6                   ; le = no
        mov     cl,crt_cols             ; else do just one line's worth [jrd]
        dec     cx                      ; don't let screen scroll
modl6:  cld
        lodsb                           ; get a byte
        push    si                      ; RFG
        mov     ah,14                   ; write to terminal
        mov     bh,0                    ; page 0
        int     screen
        pop     si                      ; RFG
        loop    modl6                   ; write out entire mode line
        cmp     flags.vtflg,0           ; emulating?
        je      modl7                   ; e = no
        and     yflags,not modoff       ; update local flags (mode line on)
        mov     al,yflags               ; Yes - update flags also
        call    ansdsl                  ; get extras from emulator
modl7:  mov     dx,cursor
        mov     ah,2
        mov     bh,0
        int     screen                  ; put cursor back where it belongs
        ret                             ; and return
modlin  endp

clrmod  proc    near                    ; clear mode line
	cmp	flags.vtflg,tttek	; NEC -- a precaution only
	je	clrmodx
        call    trmatt                  ; Get terminal screen attributes
        mov     bh,al                   ; Use screen background attribute
        mov     ax,600h                 ; blank window
        mov     dx,low_rgt              ; right most column
        inc     dh                      ; refer to status line
        mov     cx,dx                   ; bottom line [dlk]
        xor     cl,cl                   ; left most column
        int     screen                  ; clear mode line
clrmodx: ret                            ; and return
clrmod  endp


; Fetch screen attributes from emulator (if emulating). It exists mainly
; so that the reverse video will work.   Returns the current mode
; line background attribute in ah, the current screen background in al,
; and the current "cursor" (foreground) attribute in bl.  (Note: anstat
; returns status yflags in bh).

trmatt  proc    near                    ; Get attributes
        cmp     flags.vtflg,0           ; emulating? [jrd]
        je      trmat1                  ; No, just do simple stuff.
        mov     al,yflags               ; anstat expects flags byte in al.
        call    anstat                  ; Fetch emulator status/attributes
        ret
trmat1: mov     al,scbattr              ; Background attributes. [jrd]
        mov     bl,curattr              ; And cursor attribute.
        mov     ah,al                   ; where modlin needs them [jrd]
        plain_attribute
        flip_rev_video                  ; reverse the video
        ret
trmatt  endp

; Get byte yflags of terminal emulator passed in AL. Used in mode line
; handling when 25th line is used by the emulator.
telmsy  proc    near
        mov     yflags,al               ; get the updated flags
        call    ansflg                  ; and any other emulator info
        ret
telmsy  endp


;[IU2] This routine updates the ANSI status flags from the emulator,
; and passes the "yflags" byte to the VT100 emulator also.

ansflg  proc    near
        push    ax                      ; Save acs over call
        push    bx
        mov     al,yflags
        call    anstat                  ; Get status and attributes
        mov     ansflgs,bh              ; Save.
        pop     bx
        pop     ax
        ret
ansflg  endp

getflgs proc    near                    ; supply yflags for terminal emulators
        mov     al,yflags
        ret
getflgs endp

term    proc    near                    ; terminal mode entry point
        mov     argadr,ax               ; save argument ptr
        call    argini                  ; init options from arg address
        call    scrini                  ; init screen stuff

        test    flags1,inited           ; have we run yet?
        jz      term1                   ; z = no, so no saved screen yet
        call    restscr                 ; restore screen
term1:  or      flags1,inited           ; remember we've run already.
        cmp     flags.vtflg,0           ; current terminal type = None?
        je      term3a                  ; e = yes, nothing to init.
        mov     al,yflags               ; tell emulator we are back
        cmp     vtinited,inited         ; inited emulator yet?
        je      term3                   ; e = yes
        cmp     tekflg,0                ; Tek mode still active?
        jne     term3a                  ; ne = yes, no re-init here
        call    vtinit                  ; init it now
        jmp     term3a
term3:  call    ansrei                  ; reinit the emulator
        call    ansflg                  ; and get its flags
term3a: cmp     flags.modflg,0          ; is mode line disabled?
        je      term2a                  ; e = yes, disabled
        cmp     flags.vtflg,0           ; emulating a terminal?
        jne     term1a                  ; ne = yes, can have mode line
        cmp     trmtyp,0                ; previous terminal type = none?
        jne     term2                   ; ne = no. need to clear mode line.
        jmp     term2a                  ; yes, let 25th line be intact
term1a: test    yflags,modoff           ; is mode line toggled off?
        jnz     term2                   ; nz = yes, clear the line.
        cmp     flags.vtflg,tttek       ; going to be a Tek terminal?
        je      term2a                  ; e = yes, no mode line
        call    modlin                  ; turn on mode line
        jmp     term2a
term2:  call    clrmod                  ; ensure its off
term2a: mov     al,flags.vtflg          ; current terminal type
        mov     trmtyp,al               ; place to remember it til next time
        cmp     flags.vtflg,tttek       ; Tek mode?
        je      term4                   ; e = yes
        cmp     tekflg,0                ; Tek mode active within DEC stuff?
        je      lp                      ; e = no
term4:  call    tekini                  ; reinit to get graphics screen

lp:     call    portchr                 ; char at port?
         jnc    chkinp                  ; nc = no, keep going
         nop
        call    outtty                  ; print on terminal

chkinp: call    keybd                   ; call keyboard translator in msu
        jnc     lp                      ; nc = no char or have processed it
                                        ; carry set = quit Connect mode.

quit:   call	tekend
	mov     ah,3                    ; get cursor position
        xor     bh,bh                   ; page 0
        int     screen
        mov     cursor,dx               ; save position
        call    savescr                 ; save screen
        cmp     flags.vtflg,0           ; emulating?
        je      quit1                   ; e = no
        call    clrmod                  ; erase mode line
quit1:  mov     ah,oldattr              ; attributes at init time
        mov     scbattr,ah              ; background = original state [jrd]
                                        ; for ega in non-standard # lines
        mov     cx,lincur               ; cursor type at startup
        mov     ah,1
        int     screen                  ; restore cursor type
quit3:
        mov     ah,2                    ; Position cursor
        mov     bh,0                    ; Page 0
        mov     dx,low_rgt              ; bottom line
        inc     dh                      ; status line position
        xor     dl,dl                   ; left most column
        int     screen                  ; Do it.

        mov     al,yflags
        mov     bx,argadr
        mov     [bx].flgs,al            ; update flags in arg block
        ret                             ; and return to caller
term    endp

; put the character in al to the screen
outtty  proc    near
        cmp     flags.vtflg,0           ; emulating a terminal?
        jne     outnoc                  ; ne = yes, emulator handles printing
        test    flags.remflg,d8bit      ; keep 8 bits for displays?
        jnz     outnp9                  ; nz = yes, 8 bits if possible
        and     al,7fh                  ; remove high bit
outnp9: 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    anspflg,prtscr          ; should we be printing?
        jz      outnop                  ; 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    yflags,capt             ; capturing output?
        jz      outnoc                  ; no, forget this part
        push    ax                      ; save char
        call    captrtn                 ; give it captured character
        pop     ax                      ; restore character and keep going
outnoc: cmp     tekflg,0                ; Tek mode active?
        jne     outnp6                  ; ne = yes, skip screen rolling
        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    endwnd                  ; restore screen before writing [dlk]
outnp6: cmp     flags.vtflg,0           ; emulating a terminal?
        jnz     outnop1                 ; nz = yup, go do something smart
        test    yflags,trnctl           ; debug? if so use Bios tty mode
        jz      outnp4                  ; z = no
        mov     ah,biostty              ; Bios tty screen write
        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     screen
        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     screen                  ; display it
        pop     ax                      ; recover the non-printable char
outnp3: int     screen
        ret
outnp4: cmp     al,bell                 ; bell (Control G)? [jrd]
        jne     outnp5                  ; ne = no
        jmp     beep                    ; use short beep, avoid char loss.
outnp5: mov     dl,al                   ; write without intervention.
        mov     ah,conout
        int     dos                     ; else let dos display char
        ret                             ; and return

outnop1:cmp     flags.vtflg,tttek       ; doing Tektronix emulation?
        je      outnop2                 ; e = yes, use Tek emulator
        cmp     tekflg,0                ; Tek submode active?
        jne     outnop2                 ; ne = yes, use Tek emulator
        jmp     anstty                  ; call terminal emulator routine & ret
outnop2:jmp     tekemu                  ; use Tek emulator and return

outtty  endp

; get shift state into al.  We care about only shift, ctl, and alt keys.
; right shift is collapsed into left shift.
; in NEC there is no left/right shift, but the right_shift code is used
;       to indicate FUNC                                        RFG
gss     proc    near
        mov     ah,2
        int     kb                      ; get current shift state
        mov     bl,al                   ; copy for a moment
        and     al,(func_shift + left_shift + alt_shift + ctl_shift)
        ret
gss     endp

;[IU2] Here to output character to port with no echo (like escape sequences
; sent by PF keys, responses to requests from the host, etc.   It is
; wrong thinking to echo these).

prtbout proc    near                    ; Global routine now.
        mov     ah,al                   ; This is where outchr expects it
	call    outchr
         nop                            ; Ignore skip return.
         nop
         nop
        ret
prtbout endp


;[IU2] Here to output an unsigned 8-bit number (in al) to the port without
; echoing. Used by terminal emulator escape sequence output.

prtnout proc    near
        mov     bl,10                   ; Output in base 10.
        jmp     prtno2                  ; Ensure at least a zero.

prtno1: cmp     al,0
        jne     prtno2                  ; Yes - do more digits
        ret                             ; No - return from recursive call.
prtno2: mov     ah,0                    ; Clear previous remainder.
        div     bl                      ; Divide off a digit
        push    ax                      ; Push remainder (in ah) on stack
        call    prtno1                  ; Recur.
        pop     ax                      ; Pop off a digit
        add     ah,'0'                  ; Make it ASCII
        call    outchr                  ; Output to port
	 nop
	 nop
	 nop
        ret
prtnout endp

; send the character in al out to the serial port; handle echoing.
; Can send an 8 bit char while displaying only 7 bits locally.
outprt  proc    near
        test    yflags,lclecho          ; echoing?
        jz      outpr1                  ; z = no, forget it
        push    ax                      ; save char
        call    outtty                  ; print it
        pop     ax                      ; restore
outpr1: mov     ah,al                   ; this is where outchr expects it
        call    outchr                  ; output to the port
         nop
         nop
         nop                            ; skip returns...
        ret
outprt  endp

; returns with carry on if a character is available

portchr proc    near
        call    prtchr                  ; character at port?
         jmp    short portc1            ; yes, go handle
         nop                            ; skip return is stupid...
portc0: clc                             ; no carry -> no character
        ret                             ; and return...
portc1: and     al,parmsk               ; apply 8/7 bit parity mask [jrd]
        stc                             ; have a character
        ret                             ; and return
portchr endp

;;; Action routines (verbs) for keyboard translator KEYBD in msuibm.
; 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.
	cmp	flags.vtflg,tttek	; Tek terminal
	je	comar0			; e = yes, use VT100 codes
        call    outprt                  ; Output, echo permitted
        cmp     flags.vtflg,ttvt100     ; VT100 terminal emulation?
        jne     comar2                  ; No, do VT52/HEATH-19 sequence.
comar0: call    ansflg                  ; Update flags all around.
        mov     al,'['                  ; Maybe this next?
        test    ansflgs,decckm          ; Cursor key mode reset?
        je      comar1                  ; Yes, output the "["
        mov     al,'O'                  ; No, set, use the "O".
comar1: call    outprt                  ; Output it (echo permitted).
comar2: pop     ax                      ; recover final char
        call    outprt                  ; Output to port (echo permitted)
        clc
        ret

pf1:    mov     al,'P'                  ; keypad function keys 1-4
        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
        call    ansflg                  ; get emulator flags
        test    ansflgs,decanm          ; ansi mode?
        jz      short compf1            ; z = no
        mov     al,'O'                  ; send an "O".
        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:  test    ansflgs,deckpam         ; keypad application mode active?
        jnz     comkp3                  ; nz = yes, use escape sequences
        sub     al,40h                  ; deduct offset to numeric symbols
        jmp     comkp0                  ; and send that single char
comkp3: push    ax                      ; save final char
        mov     al,escape                  ; Output an escape.
        call    prtbout
        mov     al,'O'                  ; Output the "O"
        cmp     flags.vtflg,ttvt100     ; VT100 mode?
        je      comkp1                  ; e = yes, use "O" code
	cmp	flags.vtflg,tttek	; Tek terminal
	je	comkp1			; e = yes, use VT100 codes
        test    ansflgs,decanm          ; ANSI (alt application keypad) mode?
        jnz     comkp1                  ; nz = yes, use "O"
comkp2: mov     al,'?'                  ; else use "?" instead of "O".
comkp1: call    prtbout
        pop     ax                      ; recover final char
comkp0: call    prtbout                 ; send it
        clc
        ret

klogon  proc    near                    ; resume logging (if any)
        test    flags.capflg,logses     ; session logging enabled?
        jz      klogn                   ; z = no, forget it
        or      argadr.flgs,capt        ; turn on capture flag
        or      yflags,capt             ; set local msy flag as well
	call	ansflg
klogn:  clc
        ret
klogon  endp

klogof  proc    near                    ; suspend logging (if any)
        and     argadr.flgs,not capt    ; stop capturing
        and     yflags,not capt         ; reset local msy flag as well
	call	ansflg
klogo:  clc
        ret
klogof  endp

snull   proc    near                    ; send a null byte
        mov     al,0                    ; the null
        call    prtbout                 ; send without logging and local echo
        clc
        ret
snull   endp
                                        ; general character out for emulator
chrout: cmp     flags.vtflg,0           ; emulating?
        je      chrou5                  ; e = no
        call    anskbi                  ; Yes, say we had keyboard input.
        cmp     al,cr                   ; A CR?
        jne     chrou5                  ; No - just output it and return
        call    ansflg                  ; Yes - update VT100 flags
        test    ansflgs,anslnm          ; ANSI new-line mode set?
        jz      chrou5                  ; No - just send the cr
        call    outprt                  ; Yes - output a carriage-return
        mov     al,lf                   ; Followed by a line feed.
chrou5: call    outprt
        clc
        ret

                                        ; these commands invoke Quit

cdos:   mov     al,'P'                  ; Push to DOS
        jmp     short cmdcom
cstatus:mov     al,'S'                  ; Status
        jmp     short cmdcom
cquit:  mov     al,'C'                  ; Exit Connect mode
        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

dmpscn  proc    near                    ; dump screen to file
        call    savescr                 ; save screen to buffer
        call    dumpscr                 ; do buffer to file
        clc                             ; do not exit Connect mode
        ret
dmpscn  endp


; Routine to toggle VT100/VT52/Heath-19 modes in VT100 emulator.

vtans52 proc    near
        cmp     flags.vtflg,0           ; emulating?
        je      vtans5                  ; e = no
        call    ans52t                  ; Call MSZ toggle-it routine.
        call    ansflg                  ; Update flags.
        clc                             ; clear c bit so don't exit Connect.
vtans5: ret
vtans52 endp
                                        ; Toggle Mode Line
trnmod: cmp     flags.modflg,0          ; is mode line enabled?
        je      trnm2                   ; e = no, don't touch it
	cmp	flags.vtflg,tttek	; Tek mode?
	je	trnm2			; yes
	cmp	tekflg,0		; Tek submode?
	jne	trnm2			; ne = yes, no mode line changes
        test    yflags,modoff           ; mode line already off?
        jnz     trnm1                   ; yes, go turn on
        call    clrmod                  ; no, clear mode line here
        or      yflags,modoff           ; turn on flag
        call    ansflg                  ; Update flags all around.
        clc                             ; clear c bit so don't exit Connect
        ret                             ; and return
trnm1:  and     yflags,not modoff       ; Clear flag first.
        call    modlin                  ; Then turn on mode line.
        call    ansflg                  ; Update flags all around.
trnm2:  clc
	ret

trnprs: push    ax                      ; toggle ^ PrtSc screen to printer
        test    anspflg,prtscr          ; are we currently printing?
        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     anspflg,prtscr          ; flip the flag
        test    yflags,modoff           ; mode line off?
        jnz     trnpr3                  ; nz = yes
        call    modlin                  ; else rewrite mode line
trnpr3: pop     ax
        clc                             ; return carry clear (don't quit)
        ret

;;;;; General screen management routines for NEC APC

; computes screen location to ax, given row and col in [dh,dl], resp.
; trashes dx
scrloc  proc    near
        mov     al,dh                   ; get row
        xor     ah,ah                   ; clear ah
        mul     crt_cols                ; multiply by number of columns
        xor     dh,dh                   ; clear row
        add     ax,dx                   ; this is current position
        shl     ax,1                    ; double for attributes
        ret
scrloc  endp

; Routine to set cursor type.  Pass cursor type in al: 0 = No cursor,
; 1 = Underline cursor, 2 = Block cursor, 3 = restore cursor,
; 5 = No blink underline, 6 = No blink block.
; modified for NEC                                  RFG

csrtype proc    near
        push    cx                      ; save the reg
        mov     ah,1                    ; Video fxn for set cursor type
        mov     cx,0707H                ; Set one line.
        cmp     al,1                    ; Underline?
        je      csrty2                  ; Right - then do it
        or      cx,0400H                ; set for no blink
        cmp     al,5                    ; is it this?
        je      csrty2                  ; Right - then do it
        mov     cx,0007H                ; set for block
        cmp     al,2                    ; Block?
        je      csrty2                  ; Right - then do it
        or      cx,0400H                ; set for no blink
        cmp     al,5                    ; no-blink underline?
        je      csrty2                  ; Right - then do it
        cmp     al,0                    ; Disable cursor?
        je      csrty3                  ; Right - then do it
        jmp     csrty4                  ; last choice is enable
csrty2: int     screen                  ; Set it.
        pop     cx
        ret
csrty3: push    bx
        mov     ah,3                    ; BIOS call to read current
        mov     bh,0                    ;    current cursor status
        int     screen
        or      ch,80H                  ; Set disable bit
        mov     ah,1                    ; And set cursor
        pop     bx
        jmp     csrty2
csrty4: push    bx
        mov     ah,3
        mov     bh,0
        int     screen
        and     ch,7FH                  ; Clear disable bit
        mov     ah,1
        pop     bx
        jmp     csrty2
csrtype endp


; Save the entire screen in a buffer so we can restore and/or dump it.
; Saves regular (80x25) screens to memory buffer scrsav and other sized
; screens to video memory page 1. Resultant save place put into savadr
; (offset then segment) and current low_rgt size info in savflg. Note,
; some Environments (TopView/Windows etc) may not permit use of page 1. [jrd]
; modified for the NEC since text/attribute pattern is different.
;       put image of Page 0 VRAM into Page 1 VRAM for the save  RFG
savescr proc    near
        push    ax
        push    bx
        push    cx
        push    dx
        push    di
        push    si
        push    ds
        push    es
        mov     ax,vram                 ; start of VRAM is A000:0000
        mov     savadr+2,ax             ; save segment in this word
        call    scrmod                  ; ascertain video mode and screen
        mov     ax,low_rgt              ; text screen lower right (typ 23,79)
        mov     savflg,ax               ; save it for screen restore
        mov     si,0                    ; this is Page 0, to be saved
        mov     di,1000H                ; this is Page 1, the save buffer
        mov     savadr,di               ; save offset in this word
        mov     cx,80*25
        mov     ax,vram
        mov     ds,ax
        mov     es,ax
        cld
        rep     movsw                   ; move the text page
        mov     si,2000H                ; this is Page 0, attributes
        mov     di,3000H                ; this is Page 1
        mov     cx,80*25
        rep     movsw                   ; move the attribute page
        pop     es
        pop     ds
        pop     si
        pop     di
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret                             ; and return
savescr endp

; restore screen from scrsav buffer. Restores all 25 lines. [jrd]
; like savescr, modified for NEC                                RFG
restscr proc    near
        push    ax
        push    bx
        push    cx
        push    dx
        push    di
        push    si
        push    ds
        push    es
        mov     ax,vram                 ; start of VRAM is A000:0000
        mov     ds,ax
        mov     es,ax
        mov     si,1000H                ; this is Page 1, to be restored
        mov     di,0                    ; this is Page 0
        mov     cx,80*25
        rep     movsw                   ; move the text page
        mov     si,3000H                ; this is Page 1, attributes
        mov     di,2000H                ; this is Page 0
        mov     cx,80*25
        rep     movsw                   ; move the attributes
        pop     es
        pop     ds
        pop     si
        pop     di
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret                             ; and return
restscr 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.
; Dumpscr reads the screen image saved by savescr so call savescr call first.
; Mod to use VRAM (see savescr)                                 RFG

dumpscr proc    near
        push    ax
        push    bx
        push    cx
        push    dx
        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     ah,3                    ; get cursor position
        xor     bx,bx                   ; page 0
        int     screen
        push    dx                      ; save it
        mov     dh,byte ptr low_rgt+1   ; go to status line
        inc     dh
        xor     dl,dl                   ; left most column
        mov     ah,2                    ; position cursor
        int     screen
        mov     dx,offset dmperr        ; say no can do
        mov     ah,prstr
        int     dos
        pop     dx                      ; get original cursor position
        mov     ah,2                    ; position cursor
        xor     bx,bx                   ; page 0
        int     screen
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret

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                      ; read screen buffer, write lines
        push    si
        push    es
        mov     cl,byte ptr low_rgt+1   ; number of lines - 2
        add     cl,2                    ; number of line on screen
        xor     ch,ch
        mov     si,savadr               ; offset in storage area
dmp2:   push    cx                      ; save outer loop counter
        mov     es,savadr+2             ; get storage segment
        mov     di,offset dumpbuf       ; data segment memory
        mov     cl,byte ptr savflg      ; number of columns on screen - 1
        inc     cl                      ; number of columns on screen
        xor     ch,ch
dmp3:   mov     ax,word ptr es:[si]     ; read char + trash
        mov     byte ptr [di],al        ; store just char, don't use es:
        inc     si                      ; update pointers
        inc     si
        inc     di
        loop    dmp3                    ; do for each column
        std                             ; set scan backward
        mov     cl,byte ptr savflg      ; number of columns on screen - 1
        inc     cl                      ; number of columns on screen
        xor     ch,ch
        push    es
        mov     ax,ds
        mov     es,ax                   ; set es to data segment for es:di
        mov     di,offset dumpbuf       ; start of line
        add     di,cx                   ; plus length of line
        dec     di                      ; minus 1 equals end of line
        mov     al,' '                  ; thing to scan over
        repe    scasb                   ; scan until non-space
        cld                             ; set direction forward
        pop     es
        jz      dmp3a                   ; z = all spaces
        inc     cx
        inc     di
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
        jc      dmp3b                   ; c = error
        loop    dmp2                    ; do next line
        mov     dx,offset dumpsep       ; put in formfeed/cr/lf
        mov     cx,3                    ; three bytes overall
        mov     ah,write2               ; write them
dmp3b:  mov     bx,dmphand              ; file handle
        int     dos
        mov     ah,close2               ; close the file now
        int     dos
dmp6:   pop     es
        pop     si
        pop     di
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret
dumpscr endp


; Get CRT mode - returns mode in variable crt_mode,
; updates crt_cols and low_rgt. [jrd]
scrmod  proc    near
        push    ax
        push    dx
        mov     ah,15                   ; Get current video state.
        int     screen
        mov     crt_mode,al             ; Store CRT mode value.
        mov     crt_cols,ah             ; store # of cols [jrd]
        mov     dl,ah                   ; # of cols again
        mov     dh,crt_lins             ; and # of rows (constant from msster)
        dec     dl                      ; max text column, count from zero
        dec     dh                      ; max text row, count from zero
        mov     low_rgt,dx              ; save away window address
        pop     dx
        pop     ax
        ret                             ; And return.
scrmod  endp


; Get screen segment - returns screen segment in ax, and full address in es:di

; modified for NEC; there is only one answer                    RFG
scrseg  proc    near
        mov     ax,vram
        mov     es,ax
        xor     di,di                   ; start at beginning of screen (0,0)
        ret
scrseg  endp

; Synchronize a Topview provided virtual screen buffer with the image
; seen by the user. Requires cx = number of words written to screen
; (char & attribute bytes) and es:di = ENDING address of screen write.
; Changes ax and di.
; Stripped out on NEC          RFG
scrsync proc    near
        ret
scrsync endp

; The following two routines are used to turn off the display while we
; are reading or writing the screen in one of the color card modes.
; Turn screen off for (known) color card modes only. All regs preserved.
; not an NEC required function                                  RFG

scroff  proc    near
        ret                             ; And return.
scroff  endp


; Turn screen on for (known) color card modes only
; All registers are preserved.

scron   proc    near
        ret                             ; And return.
scron   endp


; Screen clearing routine. [IU]
;
; Call:         ax/     coordinates of first screen location to be cleared.
;               bx/     coordinates of last location to be cleared.
; Coord: ah = row [0-24], al = column [0-79]. Preserves all registers. [jrd]
; redone for the NEC in a non-Topview manner                    RFG
atsclr: push    ax
        push    bx
        push    cx
        push    dx
        mov     cx,ax                   ; upper left corner
        mov     dx,bx                   ; lower right corner
        mov     bh,scbattr              ; attribute
        mov     al,0                    ; blank entire window
        mov     ah,6                    ; scroll the page described above
        int     screen
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret

; Scrolling routines.  vtscru scrolls up one row, vtscrd scrolls down one
; row.  atsprep is called before scrolling up to save the top line in the
; circular buffer. All registers are preserved.

; Screen-roll down. Move text down one line, for terminal emulator only.

vtscrd: push    ax                      ; Upgraded by [jrd]
        push    bx
        push    cx
        push    dx
        mov     ax,701H                 ; scroll down one line
        mov     ch,mar_top              ; top margin line
        mov     cl,0                    ; left most column
        mov     dh,mar_bot              ; bottom margin line
        mov     dl,byte ptr low_rgt     ; right most column
        mov     bh,scbattr              ; attributes
        int     screen                  ; scroll it down
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret
                                        ; worker routine for vtscru/d
atsprep:push    es                      ; upgraded from older version  [jrd]
        call    scrseg                  ; get display address in es:di
        mov     si,di                   ; si will be source
        mov     bx,offset twnd          ; this is where it goes
        call    putcirc                 ; put screen line in circular buffer
        pop     es                      ; and that
        ret                             ; and return


; Screen scroll up one line (text moves up) for terminal emulator use.

vtscru: push    ax                      ; Upgraded by  [jrd]
        push    bx
        push    cx
        push    dx
        push    si
        push    di
        cmp     mar_top,0               ; scrolling the top screen line?
        ja      scru1                   ; a = no. don't save anything
        call    atsprep                 ; save top line
scru1:  mov     ax,601H                 ; scroll up one line
        mov     dh,mar_bot              ; bottom row
        mov     dl,byte ptr low_rgt     ; right most column
        mov     ch,mar_top              ; top row of scrolling region
        mov     cl,0                    ; left most column
        mov     bh,scbattr              ; background attributes
        int     screen                  ; scroll up that region
        pop     di                      ; Restore the rest of the regs.
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        clc
        ret                             ; And return

;screen text roll up, version for manual scrolling only

mscru:  push    ax                      ; Upgraded by  [jrd]
        push    bx
        push    cx
        push    dx
        push    si
        push    di
        cmp     bwnd.lcnt,0             ; any lines in bottom window?
        je      mscru2                  ; e = no, so ignore request
        call    atsprep                 ; save top line
mscru1: mov     ax,601H                 ; scroll up one line
        mov     dx,low_rgt              ; lower right corner
        xor     cx,cx                   ; top row of scrolling region
        mov     bh,scbattr              ; background attributes
        int     screen                  ; scroll up that region
        mov     dx,low_rgt
        mov     dl,0                    ; location is lower left corner
        call    scrloc                  ; get count from display start
        push    es
        push    ax                      ; save count
        call    scrseg                  ; get screen's segment into ax, es:di
        pop     ax                      ; recover count
        add     di,ax                   ; destination memory address (es:di)
        mov     bx,offset bwnd          ; source of lines
        call    getcirc                 ; get line from circ buf to screen
        pop     es                      ; restore es
mscru2: pop     di                      ; Restore the rest of the regs.
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret


; prep for screen scroll down. [jrd]
; copies bottom scroll line from screen to bottom window buffer.
; destroys ax,cx,dx,si,di.
getbot proc near                        ; Upgraded from old version [jrd]
        push    es
        mov     dx,low_rgt              ; from screen location, row
        mov     dl,0                    ; starting in col 0
        call    scrseg                  ; get adaptor's offset into es:di
        call    scrloc                  ; get offset in display buffer in ax
        add     di,ax                   ; source addr in display buffer es:di
        mov     si,di                   ; screen is source (si)
        mov     bx,offset bwnd          ; buffer to use (bottom window)
        call    putcirc                 ; copy bottom screen line to circ buf
        pop     es
        ret
getbot endp

;screen text scroll down, for manual mode only
mscrd:  push    ax                      ; Upgraded by [jrd]
        push    bx
        push    cx
        push    dx
        push    si
        push    di
        cmp     twnd.lcnt,0             ; any lines left in top window?
        je      mscrd1                  ; e = no, ingore request
        call    getbot                  ; fetch bottom line from screen
        mov     ax,701H                 ; scroll down one line
        xor     cx,cx                   ; top left corner
        mov     dx,low_rgt              ; bottom right corner
        mov     bh,scbattr              ; attributes
        int     screen                  ; scroll it down
        push    es
        call    scrseg                  ; get segment address of screen
        mov     bx,offset twnd          ; buffer to use (top window)
        call    getcirc                 ; copy from circ buf to screen
        pop     es
mscrd1: pop     di                      ; Restore the rest of the ACs.
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret

; move viewing window down as much as possible (text moves up)
endwnd  proc    near                    ; go to end of scrolling text
	push	cx
        mov     cx,bwnd.lcnt            ; all bottom window lines [dlk]
        jmp     dnwp0                   ; and enter dwnpg
endwnd  endp

dnone   proc    near                    ; move text up one line [jrd]
	push	cx
        mov     cx,1
        jmp     dnwp0
dnone   endp

; scroll viewing window down (text moves up) one page (24 lines)
dnwpg   proc    near
	push	cx
        mov     cl,byte ptr low_rgt+1   ; number of rows, excl status
        inc     cl                      ; count from 1, not 0
        mov     ch,0
dnwp0:                                  ; additional entry point
        cmp     bwnd.lcnt,cx            ; enough lines in bottom line buffer?
        jge     dnwp1                   ; ge = we have that many lines stored
        mov     cx,bwnd.lcnt            ; do as many as we have
dnwp1:  jcxz    dnwp2                   ; z = nothing to do
	cmp	tekflg,0		; Tek mode active?
	jne	dnwp2			; ne = yes, no scrolling
        call    mscru                   ; scroll up text one line
        loop    dnwp1
dnwp2:  pop	cx
	clc
        ret
dnwpg   endp

; home viewing window
homwnd  proc    near
	push	cx
        mov     cx,twnd.lcnt            ; all top window lines [dlk]
        jmp     upwp0                   ; join upwpg
homwnd  endp

upone   proc    near                    ; move text down one line [jrd]
	push	cx
        mov     cx,1
        jmp     upwp0
upone   endp

; scroll viewing window up (text moves down) a page (24 lines)
upwpg   proc    near
	push	cx
        mov     cl,byte ptr low_rgt+1   ; number of rows, excl status line
        inc     cl                      ; count from 1, not 0
        mov     ch,0
upwp0:                                  ; additional entry point
        cmp     twnd.lcnt,cx            ; enough lines in top line buffer?
        jae     upwp1                   ; ae = at least as many as requested
        mov     cx,twnd.lcnt            ; do only as many as are stored.
upwp1:  jcxz    upwp2                   ; z = no lines to scroll
	cmp	tekflg,0		; Tek mode active?
	jne	upwp2			; ne = yes, no scrolling
        call    mscrd                   ; roll down text one line
        loop    upwp1
upwp2:  pop	cx
	clc
        ret
upwpg   endp


; Put a line into the circular buffer.  Pass the buffer structure in bx.
; Source is vram:si which is the current screen address.
; Rewritten by [jrd]
; Modified for the NEC screen attribute structure -- RFG
putcirc proc    near
        push    es
        mov     cl,crt_cols             ; 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
        push    ds                      ; save regular datas seg reg
        push    ax
        mov     ax,vram                 ; video memory segment
        mov     ds,ax                   ; use screen segment for ds:si
putci1z:                                ; NEC mod starts here -- RFG
        movsb                           ; transfer a text byte
        mov     ax,si                   ; remember 'movsb' incremented di
        add     ax,1FFFH                ; point at the attribute
        mov     si,ax
        movsb                           ; transfer an attribute byte
        dec     cx                      ; count one full character
        mov     ax,si
        sub     ax,1FFFH                ; point at the next text
        mov     si,ax
        cmp     cx,0                    ; have we done it all?
        jne     putci1z                 ; no, keep truckin'
;                                       ; end of NEC mod -- RFG
        pop     ax
        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,crt_cols             ; move bottom pointer one slot earlier
        adc     ch,0
        add     cl,crt_cols             ; 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     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,crt_cols
        xor     ch,ch
        cld                             ; set direction to forward
        push    ds                      ; save regular datas seg reg
        push    ax
        mov     ax,vram                 ; video memory segment
        mov     ds,ax                   ; use screen segment for ds:si
putci8z:                                ; NEC mod starts here -- RFG
        movsb                           ; transfer a text byte
        mov     ax,si
        add     ax,1FFFH                ; point at the attribute
        mov     si,ax
        movsb                           ; transfer an attribute byte
        dec     cx                      ; count one full character
        mov     ax,si
        sub     ax,1FFFH                ; point at the text
        mov     si,ax
        cmp     cx,0                    ; have we done it all?
        jne     putci8z                 ; no, keep truckin'
;                                       ; end of NEC mod -- RFG
        pop     ax
        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,crt_cols             ; back up top window
        sbb     ch,0
        sub     cl,crt_cols             ; by one line
        sbb     ch,0
        mov     twnd.pp,cx              ; next place to read
putci9: 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 which is the current screen address.
; 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:                                 ; top and bottom window common code
        mov     cl,crt_cols             ; # of chars to copy
        xor     ch,ch
        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
getci1z:                                ; NEC mod starts here -- RFG
        movsb                           ; transfer a text byte
        mov     ax,di                   ; remember 'movsb' incremented di
        add     ax,1FFFH                ; point at the attribute
        mov     di,ax
        movsb                           ; transfer the attribute byte
        dec     cx                      ; count one full character
        mov     ax,di
        sub     ax,1FFFH                ; point at the next text byte
        mov     di,ax
        cmp     cx,0                    ; have we done it all?
        jne     getci1z                 ; no, keep truckin'
;                                       ; NEC mod ends here -- RFG
        pop     ds                      ; recover original data segment
        pop     cx                      ; length for Topview
        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
        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
        clc                             ; make sure no carry
        ret
getcirc endp

;
; CHKDSP - procedure to check for hardware support of 132 cols [dlk]
;
chgdsp  proc    near
        ret                             ; return to caller
chgdsp  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

if1
        %out [End of pass 1]
else
        %out [End of assembly]
endif

        end