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

⟦29dda7939⟧ TextFile

    Length: 34897 (0x8851)
    Types: TextFile
    Names: »msxz10.asm«

Derivation

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

TextFile

        name msxz10
; File MSXZ10.ASM
; Last modification: 27 April 1986

; Kermit system dependent module for Heath/Zenith Z100
; major revision of port i/o routines - now directly uses serial
;   port interrupt (supports 9600 bps without error)
; implements selection of J1/J2 port
;   from Joseph E. Rock, Jr - USAF Academy - 18 April 1986
; includes fix to SETBAUD from August Treubig of Middle South Services
; via John Voigt, Tulane Univ. Systems Group <SYSBJAV@TCSVM.BITNET>
;  21 April 1986 Geoff Mulligan, USAFA.
;
; Add global entry point vtstat for use by Status in mssset.
; Add a few register saves & restores.
; Also trimmed off trailing commas from publics. Joe R. Doupnik 12 March 1986
; Add global procedures ihosts and ihostr to handle host initialization
; when packets are to be sent or received by us,resp. 24 March 1986
; Add global procedure dtrlow (without worker serhng) to force DTR & RTS low
; in support of Kermit command Hangup. Says Not Yet Implemented. [jrd]
; Add global procedure Dumpscr, called by Ter in file msster, to dump screen
;  to a file. Just does a beep for now. 13 April 1986 [jrd]
; Correct error in pushing registers in POSCUR. From Greg Elder. 17 April 86
; In proc Outchr add override of xon from chkxon sending routine.
;  This makes a hand typed Xoff supress the xon flow control character sent
;  automatically as the receiver buffer empties. 20 April 1986 [jrd]
; Fix bad data structure in comptab; use mkeyw macro. [jrd]
; Replace emulator ontab with termtb for Set Term Heath-19 | none.  [jrd]
; Merge these changes with the rewritten code of Geoff Mulligan 27 April 86

        public  serini, serrst, clrbuf, outchr, coms, vts, vtstat, dodel
        public  ctlu, cmblnk, locate, prtchr, dobaud, clearl
        public  dodisk, getbaud, beep
        public  count, xofsnt, puthlp, putmod, clrmod, poscur
        public  sendbr, machnam, setktab, setkhlp, lclini, showkey
        public  ihosts, ihostr, dtrlow, dumpscr                 ; [jrd]
        include mssdef.h

false   equ     0
true    equ     1
mntrgh  equ     bufsiz*3/4      ; High point = 3/4 of buffer full.

; constants used by serial port handler

BRKBIT  EQU     048H            ; Send-break bit.

; 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
; monmode - color/monochrome mode of monitor

; global variables defined in this module:
; xofsnt, xofrcv - tell whether we saw or sent an xoff.
; setktab - keyword table for redefining keys (should contain a 0 if
;    not implemented)
; setkhlp - help for setktab.

BIOS_SEG SEGMENT AT 40H         ; Define segment where BIOS really is
        ORG     4*3
BIOS_PRINT  LABEL FAR
        ORG     6*3
BIOS_CONFUNC LABEL FAR          ; CON: function
BIOS_SEG ENDS

; Function codes for BIOS_xxxFUNC
CHR_WRITE       EQU     0       ; Write character
CHR_READ        EQU     1       ; Read character
CHR_STATUS      EQU     2       ; Get status
  CHR_SFGS      EQU     0       ; Get status subfunction
  CHR_SFGC      EQU     1       ; Get config subfunction
CHR_CONTROL     EQU     3       ; Control function
  CHR_CFSU      EQU     0       ; Set new configuration parameters
  CHR_CFCI      EQU     1       ; Clear input buffer

; serial port information
TSRE    EQU     004H
THBE    EQU     001H
DTR     EQU     002H
DTROFF  EQU     0fdH
DCD     EQU     040H
RDA     EQU     002H
J1_ADDR EQU     0e8H
J2_ADDR EQU     0ecH
PDATA   EQU     0
PSTATUS EQU     1
PMODE   EQU     2
PCOMM   EQU     3
TXON    EQU     001H
TXOFF   EQU     0feH
RXON    EQU     004H
RXOFF   EQU     0fbH
MODE1   EQU     04dH
MODE2   EQU     030H    ;  must be ORed with appropriate baud rate
Z8259   EQU     0f2H
EOI     EQU     020H
J1INT   EQU     68
J2INT   EQU     69
BUFILEN EQU     1200
BUFOLEN EQU     500


datas   segment public 'datas'
        extrn   drives:byte, flags:byte, trans:byte
        extrn   portval:word, port1:byte, port2:byte
;[jrd]        extrn   monmode:byte

setktab db      13
        mkeyw   'F0',96h
        mkeyw   'F1',97h
        mkeyw   'F2',98h
        mkeyw   'F3',99h
        mkeyw   'F4',9ah
        mkeyw   'F5',9bh
        mkeyw   'F6',9ch
        mkeyw   'F7',9dh
        mkeyw   'F8',9eh
        mkeyw   'F9',9fh
        mkeyw   'F10',0a0h
        mkeyw   'F11',0a1h
        mkeyw   'SCAN',-1

setkhlp db      cr,lf,'Keyname: f0, ... f11, "HELP" or "SCAN" follwed by '
        db      'decimal scan code$'
brkval  db      0               ; What to send for a break.
brkadr  dw      0               ; Where to send it.
badbd   db      cr,lf,'Unimplemented baud rate$'
noimp   db      cr,lf,'Not implemented$'
machnam db      'Heath-Zenith Z-100$'
hngmsg  db      cr,lf,' The phone should have hungup.',cr,lf,'$' ; [jrd]
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,'$'                                       ; [jrd]
rdbuf   db      80 dup (?)      ; temp buf [jrd]
crlf    db      cr,lf,'$'
delstr  db      BS,BS,' ',BS,'$' ; Delete string. [21d]
home    db      ESC,'H$'
eeolstr db      ESC,'K$'        ; Erase to end of line
clrstr  db      ESC,'E$'        ; Erase entire display
enamod  db      ESC,'x1$'       ; Enable 25th line
dismod  db      ESC,'y1$'       ; Disable 25th line
enascan db      ESC,'y?$'       ; Enable scan codes
disscan db      ESC,'x?$'       ; Disable scan codes
begrev  db      ESC,'p$'        ; Enter reverse video
endrev  db      ESC,'q$'        ; Exit reverse video
lin25   db      ESC,'Y8 $'      ; Column 1 row 25
savcur  db      ESC,'j$'        ; Save current cursor position
precur  db      ESC,'k$'        ; Restore cursor to previous position
clrlin  db      cr,'$'          ; Clear line (just the cr part).
monstr  db      ESC,'i0$'       ; Return montior information
xofsnt  db      0               ; Say if we sent an XOFF.
xofrcv  db      0               ; Say if we received an XOFF.
tmp     db      ?,'$'
temp1   dw      ?               ; Temporary storage.

termtb  db      2               ; two entries. Set Term Heath-19 | none  [jrd]
        mkeyw   'Heath-19',1    ; [jrd]
        mkeyw   'none',0        ; [jrd]

comptab db      04H
        mkeyw   '1',1           ; [jrd]
        mkeyw   '2',0           ; [jrd]
        mkeyw   'J1',1          ; [jrd]
        mkeyw   'J2',0          ; [jrd]

; this table is indexed by the baud rate definitions given in
; pcdefs.  Unsupported baud rates should contain FF.
bddat   label   word
        dw      0               ; 45.5 baud
        dw      1               ; 50 baud
        dw      2               ; 75 baud
        dw      3               ; 110 baud
        dw      4               ; 134.5 baud
        dw      5               ; 150 baud
        dw      6               ; 300 baud
        dw      7               ; 600 baud
        dw      8               ; 1200 baud
        dw      9               ; 1800 baud
        dw      10              ; 2000 baud
        dw      11              ; 2400 baud
        dw      12              ; 4800 baud
        dw      13              ; 9600 baud
        dw      14              ; 19200 baud
        dw      15              ; 38400 baud


; variables for serial interrupt handler

count   dw      0               ; Number of chars in int buffer.
buffin  db      BUFILEN dup(?)  ; input buffer
bufibeg dw      0
bufiend dw      0
buffout db      BUFOLEN dup(?)  ; output buffer
bufobeg dw      0
bufoend dw      0
portadr dw      0
intin   db      0               ; port int installed flag
oldseg  dw      0
oldoff  dw      0


ourarg  termarg <>

shkbuf  db      300 dup (?)     ; room for definition
shkmsg  db      '  Scan code: '
shkmln  equ     $-shkmsg
shkms1  db      cr,lf,'  Definition: '
shkm1ln equ     $-shkms1
datas   ends

code    segment public
        extrn   comnd:near, dopar:near, defkey:near
        extrn   sleep:near                              ; [jrd]
        assume  cs:code,ds:datas

; local initialization

lclini  proc    near
        mov     brkval,BRKBIT   ; What to send for a break.
        push    ax
        mov     ax,offset port2
        mov     portval,ax
        call    serini
        mov     ax,portadr
        add     ax,PCOMM
        mov     brkadr,ax
        pop     ax
        mov     flags.vtflg,0   ; Turn off true Heath mode (allows key macros)
        ret
lclini  endp

; this is called by Kermit initialization.  It checks the
; number of disks on the system, sets the drives variable
; appropriately.  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
        mov     drives,al
        ret
DODISK  ENDP

; retrieve the mode of the monitor (color/monochrome)
;  sets "monmode" to 7 for monochrome and 3 for color
;GETMMODE proc   near
;        push ax
;        push dx
;        mov ah,prstr            ; do it by sending 'ESC i 0' [jer]
;        mov dx,offset monstr    ;  note that this is z-100 specific
;        int dos
;        mov ah,CONINQ            ; z100 responds with
;gm1:    int dos                  ; 'ESC i E Nn where
;        cmp al,ESC               ;   n is 32/64 K VRAM
;        je gm1                   ; and N is
;        int dos                  ;  1 = monochrome
;        mov monmode,7            ;  3 = color
;        int dos
;        cmp al,'1'
;        je gm2
;        mov monmode,3
;gm2:    int dos
;        pop dx
;        pop ax
;        ret
;getmmode endp

; show the definition of a key.  The terminal argument block (which contains
; the address and length of the definition tables) is passed in ax.
; Returns a string to print in AX, length of same in CX.
; Returns normally.
showkey proc    near
        push    bx              ; save regs. [jrd]
        push    di
        push    si
        push    es
        push    ax              ; save the ptr
        mov     bx,ds
        mov     es,bx           ; address data segment
        cld
showk1: mov     ah,prstr
        mov     dx,offset enascan ; enable scan codes
        int     dos
        mov     ah,0ch          ; char input with buffer flush
        mov     al,7
        int     dos
        push    ax
        mov     ah,prstr
        mov     dx,offset disscan ; disable scan codes
        int     dos
        pop     ax
;       push    ax              ; save the character
;       call    gss             ; get shift state
;       pop     bx
        mov     ah,0            ; shift state to ah
;       mov     al,bh           ; scan code to al
        push    ax              ; remember scan code
        mov     di,offset shkbuf
        mov     si,offset shkmsg
        mov     cx,shkmln
        rep     movsb           ; copy in initial message
        call    nout            ; write out scan code
        mov     si,offset shkms1
        mov     cx,shkm1ln      ; second message
        rep     movsb
        pop     ax              ; get scan code back
        pop     bx              ; and terminal arg block
        mov     cx,[bx].klen    ; and length
        jcxz    showk2          ; no table, not defined
        push    di              ; remember output ptr
        mov     di,[bx].ktab    ; get key table
        repne   scasw           ; search for a definition for this
        mov     si,di           ; remember result ptr
        pop     di              ; get output ptr back
        jne     showk2          ; not defined, forget it
        sub     si,[bx].ktab    ; compute offset from beginning
        sub     si,2            ; minus 2 for pre-increment
        add     si,[bx].krpl    ; get index into replacement table
        mov     si,[si]         ; pick up replacement
        mov     cl,[si]         ; get length
        mov     ch,0
        inc     si
        rep     movsb           ; copy into buffer
showk2: mov     ax,offset shkbuf ; this is buffer
        mov     cx,di
        sub     cx,ax           ; length
        pop     es
        pop     si              ; [jrd]
        pop     di
        pop     bx
        ret                     ; and return
showkey endp

; Clear the input buffer. This throws away all the characters in the
; serial interrupt buffer.  This is particularly important when
; talking to servers, since NAKs can accumulate in the buffer.
; Returns normally.

CLRBUF  PROC    NEAR
        cli
        push    bx
        xor     bx,bx
        mov     bufoend,bx
        mov     bufobeg,bx
        mov     bufiend,bx
        mov     bufibeg,bx
        pop     bx
        mov     count,0
        sti
        ret
CLRBUF  ENDP

; Clear to the end of the current line.  Returns normally.

CLEARL  PROC    NEAR
        push    ax                      ; save regs. [jrd]
        push    dx
        mov     ah,prstr
        mov     dx,offset eeolstr       ; Erase to end of line
        int     dos
        pop     dx                      ; [jrd]
        pop     ax
        ret
CLEARL  ENDP

; Put the char in AH to the serial port.  This assumes the
; port has been initialized.  Should honor xon/xoff.  Skip returns on
; success, returns normally if the character cannot be written.

outchr: mov     bp,portval
        cmp     ds:[bp].floflg,0 ; Are we doing flow control.
        je      outch2          ; No, just continue.
        xor     cx,cx           ; clear counter
        cmp ah,byte ptr [bp].flowc      ; sending xoff? [jrd]
        jne outch1              ; ne = no
        mov xofsnt,false        ; supress xon from chkxon buffer routine
outch1: cmp     xofrcv,true     ; Are we being held?
        jne     outch2          ; No - it's OK to go on.
        loop    outch1          ; held, try for a while
        mov     xofrcv,false    ; timed out, force it off and fall thru.
outch2: push    bx              ; Save register.
        mov     al,ah           ; Parity routine works on AL.
        call    dopar           ; Set parity appropriately.

        mov     bx,bufoend      ; get pointer to end of que
        mov     byte ptr buffout[bx],al  ; put char in it
        inc     bx              ; point to next spot in que
        cmp     bx,BUFOLEN      ; looking at end of que ?
        jne     outch3          ; no, OK
        xor     bx,bx           ; yes, reset pointer
outch3: cli
        mov     bufoend,bx      ; store new value
        mov     bx,dx
        mov     dx,portadr
        add     dx,PCOMM
        in      al,dx
        test    al,TXON         ; TX already on ?
        jnz     outch4          ; yes, OK
        or      al,TXON         ; no, turn it on
        out     dx,al           ;   it's on
outch4: mov     dx,bx
        sti                     ; done with 2661
        pop     bx
        jmp     rskp

; This routine blanks the screen.  Returns normally.

CMBLNK  PROC    NEAR
        mov     ah,prstr
        mov     dx,offset clrstr
        int     dos
        ret
CMBLNK  ENDP

; Locate: homes the cursor.  Returns normally.

LOCATE  PROC    NEAR
        mov     ah,prstr
        mov     dx,offset home  ; Go to top left corner of screen.
        int     dos
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     ah,prstr
        mov     dx,offset savcur
        int     dos
        mov     dx,offset enamod
        int     dos
        mov     dx,offset lin25
        int     dos
        mov     dx,offset begrev
        int     dos
        pop     dx              ; get message back
        int     dos             ; write it out
        mov     dx,offset endrev
        int     dos
        mov     dx,offset precur
        int     dos
        ret                     ; and return
putmod  endp

; clear the mode line written by putmod.  Returns normally.
clrmod  proc    near
        mov     ah,prstr
        mov     dx,offset dismod
        int     dos
        ret
clrmod  endp

BEEP    PROC    NEAR
        mov     dl,BELL         ; ASCII BEL
        mov     ah,dconio
        int     dos             ; Ring it
        ret
BEEP    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              ; preserve this
        mov     ah,prstr
        mov     dx,offset crlf
        int     dos
        pop     si              ; point to string again
puthl3: lodsb                   ; get a byte
        cmp     al,0            ; end of string?
        je      puthl4          ; yes, stop
        mov     dl,al
        mov     ah,dconio
        int     dos
        jmp     puthl3          ; and keep going
puthl4: mov     ah,prstr
        mov     dx,offset crlf
        int     dos
        ret
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              ; save regs. [jrd]
        push    es
        mov     bp,portval
        mov     temp1,ax        ; Don't overwrite previous rate. [25]
        mov     ax,ds:[bp].baud ; Check if new rate is valid. [25]
        shl     ax,1            ; Get index into baud table. (times 2)
        mov     bx,offset bddat ; Start of table.
        add     bx,ax
        mov     ax,[bx]         ; The data to output to port.
        cmp     ax,0FFH         ; Unimplemented baud rate.
        jne     dobd0
        mov     ax,temp1        ; Get back orginal value.
        mov     ds:[bp].baud,ax ; Leave baud rate as is.
        mov     ah,prstr
        mov     dx,offset badbd ; Give an error message.
        int     dos
        pop     es              ; [jrd]
        pop     bx
        ret
dobd0:  push    dx              ; need to use it
        push    ax              ; save baud rate
        mov     dx,portadr      ; get addr to send it
        add     dx,PMODE
        mov     al,MODE1
        cli                     ; none while setting 2661
        out     dx,al           ; mode reg 1/2
        pop     ax              ; get baud back
        and     al,0fH          ; make sure it's clean
        or      al,MODE2        ; make complete mode 2/2 command
        out     dx,al           ; set mode reg 2/2
        sti                     ; done with 2661
        pop     dx              ; restore it
        pop     es              ; [jrd]
        pop     bx
        ret
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
        push    dx
        mov     dx,portadr              ; get addr to retrieve mode from
        add     dx,PMODE
        in      al,dx                   ; read and discard mode 1/2
        in      al,dx                   ; mode 2/2 has baud rate
        and     ax,000fH                ; clean it up
        mov     bp,portval
        mov     ds:[bp].baud,ax         ; put it in portinfo struct
        pop     dx
        pop     ax
        ret
GETBAUD ENDP

; skip returns if no character available at port,
; otherwise returns with char in al, # of chars in buffer in dx.
PRTCHR  PROC    NEAR
        call    chkxon          ; see if we need to xon
        mov     dx,bufiend      ; compute number of chars in
        sub     dx,bufibeg      ;   input que
        jge     prtch1          ; is it wrapped around
        add     dx,BUFILEN      ; yes, make it +
prtch1: cmp     dx,0            ; anything in there ?
        jne     prtch3          ; ne = yes. [jrd]
        jmp     rskp            ; no, return skip [jrd]
prtch3: push    bx              ; yes, get the char
        mov     bx,bufibeg      ; get the position
        mov     al,byte ptr buffin[bx]  ; get the char
        inc     bx              ; bump the position ptr
        cmp     bx,BUFILEN      ; wrap it ?
        jne     prtch2
        xor     bx,bx           ; yes, reset pointer
prtch2: mov     bufibeg,bx      ; store new value
        dec     dx              ; we took one char out
        mov     count,dx        ; save (does anyone use this??)
        pop     bx
        ret
PRTCHR  ENDP

; local routine to see if we have to transmit an xon
chkxon  proc    near
        push    bx
        mov     bx,portval
        cmp     [bx].floflg,0   ; doing flow control?
        je      chkxo1          ; no, skip all this
        cmp     xofsnt,false    ; have we sent an xoff?
        je      chkxo1          ; no, forget it
        cmp     count,mntrgh    ; below trigger?
        jae     chkxo1          ; no, forget it
        mov     ax,[bx].flowc   ; ah gets xon
        call    outchr          ; send it
        nop
        nop
        nop                     ; in case it skips
        mov     xofsnt,false    ; remember we've sent the xon.
chkxo1: pop     bx              ; restore register
        ret                     ; and return
chkxon  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]

IHOSTS  PROC    NEAR
        push    ax              ; save the registers
        push    bx
        push    cx
        push    dx
        mov     bx,portval      ; port indicator
        mov     ax,[bx].flowc   ; put Go-ahead flow control char in ah
        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     bx
        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]
IHOSTR  PROC    NEAR
        push    ax              ; save regs
        push    bx
        push    cx
        mov     bx,portval      ; port indicator
        mov     ax,[bx].flowc   ; put Go-ahead flow control char in ah
        call    outchr          ; send it (release Host's output queue)
         nop                    ; outchr can do skip return
         nop
         nop
        pop     cx
        pop     bx
        pop     ax
        ret
IHOSTR  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
; not yet imp.  call serhng             ; drop DTR and RTS
        mov ah,prstr            ; give a nice message
; not yet imp.  mov dx,offset hngmsg
        mov dx,offset noimp     ; for now
        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 is Not Yet Implemented.
; Send a break out the current serial port.  Returns normally.
SENDBR  PROC    NEAR
        push    cx
        push    dx
        push    ax
        xor     cx,cx           ; Clear loop counter.
        mov     dx,brkadr       ; Port address.  [19b]
        in      al,dx           ; Get current setting.
        or      al,brkval       ; Set send-break bit(s).
        out     dx,al           ; Start the break.
pause:  loop    pause           ; Wait a while.
        xor     al,brkval       ; Clear send-break bit(s).
        out     dx,al           ; Stop the break.
        pop     ax
        pop     dx
        pop     cx
        ret                     ; And return.
SENDBR  ENDP

; Position the cursor according to contents of DX:
; DH contains row, DL contains column.  Returns normally.

POSCUR  PROC    NEAR
        push    ax              ; [jrd]
        push    dx
        mov     ah,CONOUT
        mov     dl,ESC
        int     dos
        mov     dl,'Y'
        int     dos
        pop     dx
        push    dx
        mov     dl,dh
        add     dl,' '
        int     dos
        pop     dx
        add     dl,' '
        int     dos
        pop     ax              ; [jrd]
        ret
POSCUR  ENDP

; Delete a character from the terminal.  This works by printing
; backspaces and spaces.  Returns normally.

DODEL   PROC    NEAR
        mov     ah,prstr
        mov     dx,offset delstr ; Erase weird character.
        int     dos
        ret
DODEL   ENDP

; Move the cursor to the left margin, then clear to end of line.
; Returns normally.

CTLU    PROC    NEAR
        mov     ah,prstr
        mov     dx,offset clrlin
        int     dos
        call    clearl
        ret
CTLU    ENDP

; set the current port.

COMS    PROC    NEAR
;        jmp     notimp
        mov     dx,offset comptab
        mov     bx,0
        mov     ah,cmkey
        call    comnd
        jmp     r
        nop
        push    bx
        mov     ah,cmcfm
        call    comnd              ; Get a confirm.
        jmp     comx               ;  Didn't get a confirm.
        nop
        pop     bx
        mov     flags.comflg,bl     ; Set the comm port flag.
        cmp     flags.comflg,1      ; Using J1?
        jne     coms0               ; Nope.
        mov     ax,offset port1
        mov     portval,ax
        jmp     coms1
coms0:  mov     ax,offset port2
        mov     portval,ax
coms1:  call    serini
        ret
comx:   pop     bx
        ret
COMS    ENDP

; Set heath emulation on/off.

VTS     PROC    NEAR
        mov     dx,offset termtb        ; [jrd] ontab
        mov     bx,0
        mov     ah,cmkey
        call    comnd
         jmp    r
        push    bx
        mov     ah,cmcfm
        call    comnd                   ; Get a confirm.
         jmp    vt0                     ; didn't get a confirm.
         nop
        pop     bx
        mov     flags.vtflg,bl          ; Set the Heath emulation flag
        ret
vt0:    pop     bx
        ret
VTS     ENDP

notimp: mov     ah,prstr
        mov     dx,offset noimp
        int     dos
        jmp     rskp

VTSTAT  PROC    NEAR    ; For Status display [jrd]
        ret             ; no emulator status to display
VTSTAT  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 PROC    NEAR    ; Dumps screen contents to a file. Just Beeps here
        call beep       ; [jrd]
        ret
DUMPSCR ENDP

; simple routine to insure that the port has RXON and DTR high
;  assumes int are off
porton  proc    near
        push    dx
        push    ax
        mov     dx,portadr
        add     dx,PCOMM
        in      al,dx
        or      al,RXON+DTR
        out     dx,al
        pop     ax
        pop     dx
        ret
porton  endp

; routine to retrieve current int vector
;  inputs:  al = int number
;  outputs: cx = seg for current isr
;           dx = offset for current isr
getivec proc    near
        push es                 ; save registers
        push bx
        mov ah,35H              ; Int 21H, function 35H = Get Vector.
        int dos                 ; get vector in es:bx
        mov     cx,es           ; addr of org vector (seg)
        mov     dx,bx           ;   and offset
        pop bx
        pop es
        ret
getivec endp

; routine to set int vector
;  inputs:  ah = int number
;           cx = seg for isr
;           dx = offset for isr
setivec proc    near
        push    ds              ; save ds around next DOS call.
        mov     ds,cx
        mov     ah,25H          ; set interrupt address from ds:dx
        int     dos
        pop     ds
        ret
setivec 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
        mov     ax,portval
        cmp     ax,offset port1
        je      seri2           ; setup for J1
        cmp     intin,2
        jne     seri0
        ret                     ; J2 already set up
seri0:  cmp     intin,1
        jne     seri1           ; J1 currently installed
        call    serrst          ; de-install current int
seri1:  mov     al,J2INT
        call    getivec
        mov     oldseg,cx
        mov     oldoff,dx
        mov     cx,cs
        mov     dx,offset serisr
        mov     al,J2INT
        call    setivec
        mov     portadr,J2_ADDR
        mov     brkadr,J2_ADDR+PCOMM
        call    clrbuf
        call    porton
        mov     intin,2         ; show J2 installed
        ret
seri2:  cmp     intin,1
        jne     seri3
        ret                     ; J1 already set up
seri3:  cmp     intin,2
        jne     seri4           ; J2 currently installed
        call    serrst          ; de-install current int
seri4:  mov     al,J1INT
        call    getivec
        mov     oldseg,cx
        mov     oldoff,dx
        mov     cx,cs
        mov     dx,offset serisr
        mov     al,J1INT
        call    setivec
        mov     portadr,J1_ADDR
        call    clrbuf
        call    porton
        mov     intin,1         ; show J1 installed
        ret
SERINI  ENDP

; Reset the serial port.  This is the opposite of serini.  Calling
; this twice without intervening calls to serini should be harmless.
; Returns normally.

SERRST  PROC    NEAR
        push    dx
        cmp     intin,0         ; is any isr installed
        je      serr2           ; no, all done
        push    ax
        push    cx
        mov     ax,J2INT        ; guess it's J2
        cmp     intin,2         ; yes,
        je      serr1           ;   reset it
        mov     ax,J1INT        ; no, must be J1
serr1:  mov     cx,oldseg       ; original isr
        mov     dx,oldoff       ;   address
        call    setivec         ; do it
        mov     intin,0         ; show nothing installed
        pop     cx
        pop     ax
serr2:  pop     dx
        ret                     ; All done.
SERRST  ENDP


; put the number in ax into the buffer pointed to by di.  Di is updated
nout    proc    near
        mov     dx,0            ; high order is always 0.
        mov     bx,10
        div     bx              ; divide to get digit
        push    dx              ; save remainder digit
        or      ax,ax           ; test quotient
        jz      nout1           ; zero, no more of number
        call    nout            ; else call for rest of number
nout1:  pop     ax              ; get digit back
        add     al,'0'          ; make printable
        stosb                   ; drop it off
        ret                     ; and return
nout    endp


; the serial port interrupt service routine
;  this routine does int driven input and output
;   once installed, it displaces the Z-100 serial isr
serisr: push    ax                      ; Save regs
        push    bx
        push    cx
        push    dx
        push    ds                      ; save data seg
        mov     ax,seg datas            ; set our
        mov     ds,ax                   ;  data seg

        mov     dx,portadr
        mov     cx,dx
        add     dx,PSTATUS
        in      al,dx           ; Get port status
        mov     ah,al           ; Save it
        test    ah,RDA          ; check for data available
        jz      isr2            ;   No, skip

        mov     dx,cx
        in      al,dx           ; get the data
        mov     bx,bufiend      ; get where to put it
        mov     byte ptr buffin[bx],al ; stick it in the que
        inc     bx              ; bump que pointer
        cmp     bx,BUFILEN      ; pointing to end of que?
        jne     isr1
        xor     bx,bx           ; reset pointer
isr1:   mov     bufiend,bx      ; store new pointer

isr2:   test    ah,TSRE+THBE    ; ready to send a char?
        jz      isr5            ;  no, almost done
        mov     bx,bufobeg      ; get pointer to end of output buffer
        cmp     bx,bufoend      ; buffer empty?
        jz      isr4            ; yes, turn transmitter off
        mov     al,byte ptr buffout[bx] ; get char to send
        mov     dx,cx
        out     dx,al           ; send it
        inc     bx              ; point to next char to send
        cmp     bx,BUFOLEN      ; pointing to end of que?
        jne     isr3
        xor     bx,bx           ; reset pointer
isr3:   mov     bufobeg,bx      ; save it
        jmp     isr5

isr4:   mov     dx,cx
        add     dx,PCOMM
        in      al,dx           ; get current mode
        and     al,TXOFF        ; turn xmitter off
        out     dx,al           ; do it.

isr5:   mov     al,EOI          ; Tell interrupt controller
        out     Z8259,al        ;   that interrupt serviced

        pop     ds
        pop     dx
        pop     cx
        pop     bx              ; restore regs
        pop     ax

        iret


; 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
-------
-------