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

⟦16de3063a⟧ TextFile

    Length: 24445 (0x5f7d)
    Types: TextFile
    Names: »msxwng.asm«

Derivation

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

TextFile

	name msxwng
; File MSXWNG.ASM
; Last mmodification: 29 Juli 1988
; MS-DOS Kermit system-dependent module for the Wang PC
; Jeff Damens, CUCCA
; Add global entry point vtstat for use by Status in mssset.
; Correct corruption of registers in GETBAUD, CLRBUF, and POSCUR.
; Add clearing of terminal emulation flag, flags.vtflg, in procedure lclini.
; 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]
; Add some dummy procedures and symbols to assemble and link with the rest
;  of the kermit release 2.31 of Juli 1st, 1988.
; Implement dobaud, so that the command SET BAUD has an immediate effect. [ve]

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

false   equ     0
true    equ     1

ctrla   equ     1               ; Control-A.
escape	equ	27		; [ve]

auxin   equ     3
auxout  equ     4
auxfil  equ     3               ; file number of aux file.
iordy   equ     6               ; input ready function
write   equ     40h
wbios   equ     88h
settrp  equ     02h
clrtrp  equ     03h
chrrdy  equ     01h
txrdy   equ     02h

rcvdat  equ     1080h
rcvstat equ     1082h
rcvmod  equ     1084h
rcvcmd  equ     1086h
trdat   equ     1088h
trmod   equ     108ch
wrcmd   equ     108eh

; mode bits
mod1    equ     4dh                     ; clock rate, 8 bits, 1 stop bit
mod2    equ     30h                     ; internal clock

; command register bits
txen    equ     01h
dtr     equ     02h
rxen    equ     04h
brk     equ     08h
clrerr  equ     10h
rts     equ     20h


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

portin  db      0
crlf    db      cr,lf,'$'
machnam db	'FIELD TEST [ve] Wang$'
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]
noimp   db      cr,lf,'Command not implemented.$'
shkmsg  db      'Not implemented.'
shklen  equ     $-shkmsg
xofsnt  db      0               ; Say if we sent an XOFF.
xofrcv  db      0               ; Say if we received an XOFF.
setktab db      0
setkhlp db      0
invseq	db	escape,'[7m$'	; Reverse video on.
nrmseq	db	escape,'[0m$'	; Reverse video off.
ivlseq  db      79 dup (' '),cr,'$'     ; Make a line inverse video
comphlp db      cr,lf,'1 (COM1)   2 (COM2)$'
delstr  db      BS,' ',BS,'$'   ; Delete string.
clrlin	db	cr,escape,'[K$'
tmp     db      ?,'$'
temp    dw      0
temp1   dw      ?               ; Temporary storage.
temp2   dw      ?               ; Temporary storage.

; Entries for choosing communications port. [19b]
comptab db      04H
        db      01H,'1$'
        dw      01H
        db      01H,'2$'
        dw      00H
        db      04H,'COM1$'
        dw      01H
        db      04H,'COM2$'
        dw      00H

termtb  db      tttypes                 ; entries for Status, not Set
        mkeyw   'Heath-19',ttheath
        mkeyw   'none',ttgenrc
        mkeyw   'Tek4010',tttek
        mkeyw   'VT102',ttvt100
        mkeyw   'VT52',ttvt52


; variables for serial interrupt handler

source  db      bufsiz DUP(?)   ; Buffer for data from port.
bufout  dw      0               ; buffer removal ptr
count   dw      0               ; Number of chars in int buffer.
bufin   dw      0               ; buffer insertion ptr
telflg  db      0               ; Are we acting as a terminal. [16] [17c]
clreol	db	escape,'[0K$'
blank	db	escape,'[H',escape,'[J$'
movcur	db	escape,'['
colno   db      20 dup (?)
ten     db      10
prthnd  dw      0
ourarg  termarg <>
; must parallel baud rate defs in pcdefs.
baudtab db      0ffh            ; 45.5 baud (not supported)
        db      0               ; 50
        db      1               ; 75
        db      2               ; 110
        db      3               ; 134.5
        db      4               ; 150
        db      5               ; 300
        db      6               ; 600
        db      7               ; 1200
        db      8               ; 1800
        db      9               ; 2000
        db      10              ; 2400
        db      12              ; 4800
        db      14              ; 9600
        db      15              ; 19.2k
        db      0ffh            ; 38.4k (ha)

nbaud   equ     $-baudtab
qid     dw      ?
prtcnt  dw      ?
trqid   dw      ?
tmqid   dw      ?
brflg   db      ?
datas   ends

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


;; Wait for the # of milliseconds in ax, for non-IBM compatibles.
;; Thanks to Bernie Eiben for this one. Modified to use adjustable
; inner loop counter (pcwcnt, adjusted by proc pcwtst) by [jrd].

pcwcnt  dw      240             ; number of loops for 1 millisec in pcwait

pcwait  proc    near
        push    cx
pcwai0: mov     cx,pcwcnt       ; inner loop counter for 1 ms (240 @ 4.77 MHz)
pcwai1: sub     cx,1            ; inner loop takes 20 clock cycles
        jnz     pcwai1
        dec     ax              ; outer loop counter
        jnz     pcwai0          ; wait another millisecond
        pop     cx
        ret
pcwait  endp


DODISK  PROC    NEAR
        mov ah,gcurdsk                  ; Current disk value to AL.
        int dos
        mov dl,al                       ; Put current disk in DL.
        mov ah,seldsk                   ; Select current disk.
        int dos                         ; Get number of drives in AL.
        mov drives,al
        ret
DODISK  ENDP

; Clear the input buffer before sending a packet. [20e]

CLRBUF  PROC    NEAR
        push    ax              ; save regs [jrd]
        push    bx              ; [jrd]
clrb2:  mov     ah,ioctl        ; [jrd]
        mov     bx,auxfil
        mov     al,iordy
        int     dos
        cmp     al,0ffh
        jne     clrb1                   ; not ready, keep going
        mov     ah,auxin
        int     dos
;;;[jrd]        jmp     clrbuf                  ; read char and keep going.
        jmp     clrb2           ; [jrd]
clrb1:  mov     count,0
        mov ax,offset source
        mov bufin,ax
        mov bufout,ax
        pop     bx              ; restore regs [jrd]
        pop     ax              ; [jrd]
        ret
CLRBUF  ENDP

; Common routine to clear to end-of-line. [19a]

CLEARL  PROC    NEAR
        mov dx,offset clreol
        mov ah,prstr
        int dos
        ret
CLEARL  ENDP

; This routine should set the baud rate for the current port but it
; is actually done in SERINI.
; WHY??? Let's do it here and in SERINI, don't matter if the baud rate
;	 is set twice! [ve]
dobaud  proc    near
	mov dx,rcvcmd
	in al,dx		; read cmd register to reset mode ptr.
	mov dx,trmod
	mov al,mod1
	out dx,al
	push bx
	mov bx,portval
	mov si,[bx].baud
	pop bx
	mov al,baudtab[si]
	or al,mod2
	out dx,al
        ret
dobaud  endp

; Send a break out the current serial port.  Returns normally.
sendbl:
sendbr: push dx
        push ax
        push cx
        push ds                 ; preserve data segment
        mov ax,cs
        mov ds,ax               ; handler is in code segment
        mov al,settrp
        mov bx,txrdy            ; interrupt on transmitter empty
        mov cx,0                ; interrupt immediately
        mov dx,offset sendb1    ; handler routine
        int wbios
        pop ds
        mov trqid,bx
        push ds
        mov ax,cs
        mov ds,ax
        mov al,settrp
        mov bx,0                ; 10 ms timer
        mov cx,21               ; after 21 times - approx 200 ms.
        mov dx,offset sendb2    ; timer interrupt
        int wbios
        pop ds
        mov tmqid,bx

        mov brflg,1
        mov dx,rcvcmd
        in al,dx                ; Read command register.
        or al,brk+txen          ; Set send-break bit.
        mov dx,wrcmd            ; Write command register.
        out dx,al
pause:  cmp brflg,0
        jne pause               ; while non-zero, keep going
        mov al,clrtrp           ; clear the trap
        mov bx,trqid
        int wbios
        mov al,clrtrp
        mov bx,tmqid
        int wbios
        pop cx
        pop ax
        pop dx
        ret

sendb1  proc    far
        ret
sendb1  endp

sendb2  proc    far
        push ax
        push ds
        mov ax,seg datas
        mov ds,ax
        mov brflg,0
        mov dx,rcvcmd
        in al,dx
        and al,not (txen + brk)
        mov dx,wrcmd
        out dx,al
        pop ds
        pop ax
        ret
sendb2  endp


; Write a line in inverse video at the bottom of the screen...
; the line is passed in dx, terminated by a $.  Returns normally.
putmod  proc    near
        push    dx              ; preserve message
        mov     dx,24 * 100H    ; line 24
        call    poscur
        mov     dx,offset invseq ; put into inverse video
        mov     ah,prstr
        int     dos
        pop     dx
        int     dos
        mov     dx,offset nrmseq ; normal videw
        int     dos
        ret                     ; and return
putmod  endp

; Clear the mode line written by putmod.  Returns normally.
clrmod  proc    near
        mov     dx,24 * 100H
        call    poscur
        call    clearl
        ret
clrmod  endp

; Put a help message one the screen in reverse video.  Pass
; the message in AX, terminated by a null.  Returns normally.
; The message is put wherever the cursor currently is located.
puthlp  proc    near
        push ax
        mov ah,prstr            ; Leave some room before the message.
        mov dx,offset crlf
        int dos
        mov dx,offset invseq    ; Put into reverse video.
        int dos
        pop si                  ; Put message address here.
puth0:  mov ah,prstr
        mov dx,offset ivlseq    ; Make line inverse video
        int dos
puth1:  lodsb
        cmp al,0                ; Terminated with a null.
        je puth2
        mov dl,al
        mov ah,conout
        int dos
        cmp al,lf               ; Line feed?
        je puth0                ; Yes, clear the next line.
        jmp puth1               ; Else, just keep on writing.
puth2:  mov dx,offset nrmseq    ; Normal video.
        mov ah,prstr
        int dos
        mov dx,offset crlf
        int dos
        ret
puthlp  endp

outchr: push dx                 ; Save register.
        mov al,ah
        call dopar
        mov dl,al
        mov ah,auxout
        int dos
        pop     dx
        jmp rskp


; This routine blanks the screen.

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

LOCATE  PROC    NEAR
        mov dx,0                ; Go to top left corner of screen.
        jmp poscur              ; callret...
LOCATE  ENDP

GETBAUD PROC    NEAR
        push    ax              ; save regs [jrd]
        push    bx              ; [jrd]
        push    cx              ; [jrd]
        push    dx              ; [jrd]
        push    di              ; [jrd]
        push    es              ; [jrd]
        cld
        mov dx,rcvmod
        in al,dx
        in al,dx                ; get second mode word
        and     al,0fh          ; isolate baud rate
        mov cx,nbaud
        mov di,offset baudtab
        mov bx,ds
        mov es,bx               ; address correct segment
        mov bx,portval
        repne scasb             ; look for baud rate
        jne getb1               ; mystery baud rate...
        sub di,offset baudtab + 1
        mov [bx].baud,di        ; store baud rate in comm area
        jmp getb2       ; [jrd]
;;;[jrd]        ret                     ; and return
getb1:  mov [bx].baud,-1        ; unknown baud rate
getb2:  pop     es      ; restore regs. [jrd]
        pop     di      ; [jrd]
        pop     dx      ; [jrd]
        pop     cx      ; [jrd]
        pop     bx      ; [jrd]
        pop     ax      ; [jrd]
        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
prtchx: cmp count,0
        je prtch4               ; empty buffer, forget it.
        push si                 ; save reg. [jrd]
        mov si,bufout
        lodsb
        cmp si,offset source + bufsiz
        jb prtch1
        mov si,offset source
prtch1: mov bufout,si
        pop si                  ; [jrd]
        dec count
        push bx
        mov bx,portval
        cmp [bx].parflg,PARNON ; no parity?
        je prtch3               ; then don't strip
        and al,7fh              ; else turn off parity
prtch3: mov dx,count            ; chars left in buffer
        pop bx
        ret
prtch4: jmp rskp                ; no chars...
PRTCHR  ENDP

; IHOSTS - Initialize the host by sending XON, or equivalent, and enter the
; cycle of clear input buffer, wait 1 second, test if buffer empty then exit
; else repeat cycle. Requires that the port be initialized before hand.
; Ihosts is used by the local send-file routine just after initializing
; the serial port.
; 22 March 1986 [jrd]

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]
; 5 April 1987 Add 500 millisec wait with lines low before returning. [jrd]
; Calling this twice without intervening calls to serini should be harmless.
; If network then call nethangup procedure to hangup the session without
; losing local name information.
; Returns normally.

serhng  proc    near    ; clear modem's delta status bits and lower DTR & RTS
; SERHNG is Not Yet Implemented, just do a quick return
        ret
serhng  endp

; Position the cursor according to contents of DX.

POSCUR  PROC    NEAR
        push    es              ; save regs. [jrd]
        push    ax              ; [jrd]
        push    dx              ; [jrd]
        push    di              ; [jrd]
        mov     ax,ds
        mov     es,ax                   ; address data segment!!!
        cld
        mov     di,offset colno
        mov     al,dh                   ; row
        inc     al
        call    nout
        mov     al,';'
        stosb
        mov     al,dl                   ; col
        inc     al
        call    nout
        mov     al,'H'
        stosb
        mov     al,'$'
        stosb
        mov     dx,offset movcur
        mov     ah,prstr
        int     dos                     ; print the sequence
        pop     di              ; restore regs [jrd]
        pop     dx              ; [jrd]
        pop     ax              ; [jrd]
        pop     es              ; [jrd]
        ret
POSCUR  ENDP

NOUT    PROC    NEAR
        cbw                     ; extend to word
        div     byte ptr ten    ; divide by 10
        or      al,al           ; any quotient?
        jz      nout1           ; no, forget this
        push    ax              ; save current result
        call    nout            ; output high order
        pop     ax              ; restore
nout1:  mov     al,ah           ; get digit
        add     al,'0'          ; make printable
        stosb
        ret                     ; put in buffer and return
NOUT    endp

; Perform a delete.

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

; Perform a Control-U.

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

COMS    PROC    NEAR
        mov dx,offset comptab
        mov bx,offset comphlp
        mov ah,cmkey
        call comnd
         jmp r
        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 Com 1?
        jne coms0               ; Nope.
        mov ax,offset port1
        mov portval,ax
        ret
coms0:  mov ax,offset port2
        mov portval,ax
        ret
comx:   pop bx
        ret
COMS    ENDP

VTS     PROC    NEAR
        jmp notimp
VTS     ENDP

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


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

lclini: mov trans.escchr,ctrla  ; Use Control-A as escape char.
        mov flags.vtflg,0       ; no terminal emulation. [jrd]
        ret

showkey:
        mov ax,offset shkmsg
        mov cx,shklen
        ret

; SHOW MODEM, displays current status of lines DSR, CD, and CTS.
; Uses byte mdmhand, the modem line status register. [jrd]
shomodem proc   near
 ; NOT YET IMPLEMENTED, just do a quick return:
	  ret
shomodem endp

; Get modem status and set global byte mdmhand. Preserve all registers.
getmodem proc   near                    ; gets modem status upon request
 ; NOT YET IMPLEMENTED, just do a quick return:
        ret
getmodem endp


;     Common initialization for using serial port.

SERINI  PROC    NEAR
        cmp portin,0            ; already inited?
        jne serin1              ; yes, skip it
        mov portin,1            ; remember inited
        mov dx,rcvcmd
        in al,dx                ; read cmd register to reset mode ptr.
        mov dx,trmod
        mov al,mod1
        out dx,al
        push bx
        mov bx,portval
        mov si,[bx].baud
        pop bx
        mov al,baudtab[si]
        or al,mod2
        out dx,al
        mov dx,wrcmd
        mov al,txen+dtr+rxen+clrerr+rts
        out dx,al               ; enable transmit and receive
        call clrbuf             ; empty buffer
        mov al,settrp
        mov bx,chrrdy           ; interrupt on character ready
        mov cx,0                ; interrupt immediately
        mov dx,offset serint    ; handler routine
        mov prtcnt,0            ; no characters in yet
        push ds
        mov si,cs
        mov ds,si
        int wbios
        pop ds
        or al,al
        jne serin1
        mov qid,bx              ; preserve trap identification
serin1: ret                     ; We're done. [21c]
SERINI  ENDP

SERRST  PROC    NEAR
        cmp portin,0            ; already de-inited?
        je serrs1               ; yes, skip this
        push bx                 ; save reg. [jrd]
        mov portin,0
        mov al,clrtrp
        mov bx,qid
        int wbios
        pop bx                  ; [jrd]
serrs1: ret
SERRST  ENDP

; serial interrupt handler
serint  proc    far
        push ds
        push ax
        push dx
        push di
        mov ax,seg datas
        mov ds,ax
        mov di,bufin
        mov dx,rcvdat
        in al,dx
        mov [di],al
        inc di
        cmp di,offset source + bufsiz
        jb sernt1
        mov di,offset source
sernt1: mov bufin,di
        inc count
        pop di
        pop dx
        pop ax
        pop ds
        ret
serint  endp


; Generate a short beep.

BEEP    PROC    NEAR
        mov dl,bell
        mov ah,conout
        int dos
        ret
BEEP    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

term    proc    near
        mov si,ax               ; this is source
        mov di,offset ourarg    ; place to store arguments
        mov ax,ds
        mov es,ax               ; address destination segment
        mov cx,size termarg
        rep movsb               ; copy into our arg blk
term1:  call prtchr
        jmp short term2         ; have a char...
        nop
        nop
        jmp short term3         ; no char, go on
term2:  and al,7fh
        push ax
        mov dl,al
        mov ah,dconio
        int dos                 ; write out the character
        pop ax
        test ourarg.flgs,capt   ; capturing output?
        jz term3                ; no, forget it
        call ourarg.captr       ; else call the routine
term3:  mov ah,dconio
        mov dl,0ffh
        int dos
        or al,al
        jz term1                ; no character, go on
	cmp al,ourarg.escc	; escape char?
        je term4                ; yes, exit
        push ax                 ; save char
        mov ah,al
        call outchr             ; output the character
        nop
        nop
        nop
        pop ax
        test ourarg.flgs,lclecho ; echoing?
        jz term1                ; no, continue loop
        mov dl,al
        mov ah,dconio
        int dos
        jmp term1               ; else echo and keep going
term4:  ret
term    endp
code    ends
        end
        end