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

⟦b71aed8d0⟧ TextFile

    Length: 25691 (0x645b)
    Types: TextFile
    Names: »msxdm2.asm«

Derivation

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

TextFile

        name msxdm2
; File MSXDM2.ASM
; Last modification: 20 April 1986

; DECmate II MS DOS Kermit module
; Add global entry point vtstat for use by Status in mssset.
; 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 small fixups in procedure coms. [jrd]
; Revise procedure outchr to use dos 2.x file handles rather than "punout"
; which defaults to the Printer! Make proc Clrbuf read from the comms port.
; 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]
; 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]

PAGE 66,120

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

false   equ     0
true    equ     1
instat  equ     6
rddev   equ     3fH
open    equ     3dH

; external variables used:
; drives - # of disk drives on system
; flags - global flags as per flginfo structure defined in pcdefs
; trans - global transmission parameters, trinfo struct defined in pcdefs
; portval - pointer to current portinfo structure (currently either port1
;    or port2)
; port1, port2 - portinfo structures for the corresponding ports

; global variables defined in this module:
; xofsnt, xofrcv - tell whether we saw or sent an xoff.

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

machnam db      'DECmate II MS-DOS 2.0$'
erms20  db      cr,lf,'?Warning: System has no disk drives$' ; [21a]
erms40  db      cr,lf,'?Warning: Unrecognized baud rate$'
erms41  db      cr,lf,'?Warning: Cannot open com port$'
erms50  db      cr,lf,'Error reading from device$'
hnd1    db      cr,lf,'Enter a file handle.  Check your DOS manual if you are '
        db      cr,lf,'not certain what value to supply (generally 3).$'
hnd2    db      cr,lf,'Handle: $'
hnderr  db      cr,lf,'Warning: Handle not known.'
deverr  db      cr,lf,'Any routine using the communications port will'
        db      cr,lf,'probably not work.$'
hndhlp  db      cr,lf,'A four digit file handle $'
dev1    db      cr,lf,'Device: $'
devhlp  db      cr,lf,'Name for your systems auxiliary port $'
badbd   db      cr,lf,'Unimplemented baud rate$'
noimp   db      cr,lf,'Command not implemented.$'
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]
shkmsg  db      'Not implemented.'
shklen  equ     $-shkmsg
setktab db      0
setkhlp db      0
gopos   db      esc,'['
rowp    db      20 dup (?)
crlf    db      cr,lf,'$'
delstr  db      BS,' ',BS,'$'           ; Delete string. [21d]
clrlin  db      cr,'$'                  ; Clear line (just the cr part).
clreol  db      ESC,'[K$'               ; Clear line.
clrseq  db      esc,'[H',esc,'[J$'      ;clear screen home cursor.
telflg  db      0               ; non-zero if we're a terminal.
xofsnt  db      0               ; Say if we sent an XOFF.
xofrcv  db      0               ; Say if we received an XOFF.
count   dw      0               ; Number of chars in int buffer.
prthnd  dw      0               ; Port handle.
prttab  dw      com2,com1
com1    db      'COM1',0
com2    db      'COM2',0
tmp     db      ?,'$'
temp    dw      0
temp1   dw      ?               ; Temporary storage.
temp2   dw      ?               ; Temporary storage.
;;;[jrd]rdbuf   db      20 dup(?)       ; Buffer for input.
prtstr  db      20 dup(?)       ; Name of auxiliary device. [27d]

; Entries for choosing communications port. [19b]
comptab db      6               ; Number of options
        mkeyw   '1',01H
        mkeyw   '2',00H
        mkeyw   'COM1',01H
        mkeyw   'COM2',00H
        mkeyw   'DEVICE',02H
        mkeyw   'FILE-HANDLE',03H

ourarg  termarg <>

datas   ends

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

; 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                         ; Get number of drives in AL.
        mov drives,al
        ret
DODISK  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.
; Do nothing since we are not interrupt driven.  Returns normally.

CLRBUF  PROC    NEAR
        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 clreol
        int dos
        pop     dx
        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 dx                 ; Save register.
        mov al,ah               ; Parity routine works on AL.
        call dopar              ; Set parity appropriately.
                                ; Begin revised output routine. [jrd]
        cmp prthnd,0            ; Got a handle yet? [27d]
        jne outch3              ; Yup just go on. [27d]
        call opnprt             ; Else 'open' the port. [27d]
outch3: push    bx
        mov     bx,prthnd       ; port handle
        mov     cx,1            ; one byte to write
        mov     dx,offset temp  ; place where data will be found
        mov     byte ptr temp,al ; put data there
        mov     ah,write2       ; dos 2 write to file/device
        int     dos
        pop     bx              ; end of revised routine
;;;     mov dl,al
;;;     mov ah,punout           ; Output char in DL to comm port.
;;;     int dos
        pop dx
        jmp rskp

; This routine blanks the screen.  Returns normally.

CMBLNK  PROC    NEAR
        mov ah,prstr
        mov dx,offset clrseq    ;erase the screen
        int dos
        ret
CMBLNK  ENDP

; Homes the cursor.  Returns normally.

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

; Write a line 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,1800h        ; now address line 24
        call    poscur
        pop     dx              ; get message back
        mov     ah,prstr
        int     dos             ; write it out
        ret                     ; and return
putmod  endp

; clear the mode line written by putmod.  Returns normally.
clrmod  proc    near
        mov     dx,1800h
        call    poscur          ; Go to bottom row.
        call    clearl          ; Clear to end of line.
        ret
clrmod  endp

; Put a help message on the screen.
; Pass the message in ax, terminated by a null.  Returns normally.
puthlp  proc    near
        push    dx              ; save regs [jrd]
        push    si
        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             ; else write to screen
        jmp     puthl3          ; and keep going
puthl4: mov     ah,prstr
        mov     dx,offset crlf
        int     dos
        pop     si              ; [jrd]
        pop     dx
        ret
puthlp  endp

; Set the baud rate for the current port, based on the value
; in the portinfo structure.  Returns normally.

DOBAUD  PROC    NEAR
        mov ah,prstr
        mov dx,offset noimp     ; Say it's not implemented.
        int dos
        push bx                 ; [jrd]
        mov bx,portval
        mov [bx].baud,0FFFFH    ; So it's not a recognized value.
        pop bx                  ; [jrd]
        ret                     ; Must be set before starting Kermit.
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
        ret                     ; Can't do this.
GETBAUD ENDP

; Use for DOS 2.0 and above.  Check the port status.  If no data, skip
; return.  Else, read in a char and return.
; Minor patch by [jrd]
PRTCHR  PROC    NEAR
        push bx
        push cx
        push si
        push bp
        cmp prthnd,0            ; Got a handle yet? [27d]
        jne prtch0              ; Yup just go on. [27d]
        call opnprt             ; Else 'open' the port. [27d]
prtch0: call chkxon
        mov bx,prthnd
        mov al,instat
        mov ah,ioctl
        int dos
        or al,al
        jz prtch4               ; not ready...
        mov bx,prthnd
        mov ah,rddev
        mov cx,1
        mov dx,offset temp
        int dos
        jnc prtch1              ; nc = no error. [jrd]
        cmp al,5                ; Error condition.
        je prt3x
        cmp al,6                ; Error condition
        je prt3x
prtch1: mov al,byte ptr temp    ; [jrd]
        mov bp,portval
        cmp ds:[bp].parflg,PARNON       ; no parity?
        je prtch3               ; then don't strip
        and al,7fh              ; else turn off parity
prtch3: pop bp
        pop si
        pop cx
        pop bx
        ret
prt3x:  mov ah,prstr
        mov dx,offset erms50
        int dos
prtch4: pop bp
        pop si
        pop cx
        pop bx
        jmp rskp                ; no chars...
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
        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    dx              ;save the register to be used
        mov     ah,03           ;class description 3 comm channel
        mov     al,0bH          ;send break to port
        mov     dl,1cH          ;send a 280 millisend break
        int     05fH            ;call extended bios to do it
        pop     dx
        ret
SENDBR  ENDP

; Position the cursor according to contents of DX:
; DH contains row, DL contains column.  Returns normally.
POSCUR  PROC    NEAR
        add     dx,101H         ;start at column 1,1
        push    ax              ; [jrd]
        push    bx
        push    cx
        push    di
        push    es
        push    dx
        cld
        mov     ax,ds
        mov     es,ax           ;address right segment
        mov     di,offset rowp  ;row comes first
        mov     al,dh
        mov     ah,0
        call    nout            ;store the characters into di
        mov     al,';'          ;separated with this
        stosb
        pop     dx              ;get back column number
        mov     al,dl
        mov     ah,0
        call    nout            ;store as ascii data
        mov     al,'H'          ;terminator for dca
        stosb
        mov     byte ptr [di],'$'       ;terminate the line
        mov     ah,prstr                ;print string to msdos
        mov     dx,offset gopos
        int     dos
        pop     es              ;clean up the stack and exit
        pop     di              ; [jrd]
        pop     cx
        pop     bx
        pop     ax
        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
        mov dx,offset comptab
        mov bx,0
        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
        cmp bl,2                ; Do they want to set device name? [27d]
        je coms2                ; Yes go get name. [27d]
        jg coms3                ; Else pick up file handle. [27d]
        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
coms2:  mov dx,offset dev1      ; Let user supply device name.
        call prompt
        mov ah,cmtxt
        mov bx,offset prtstr    ; Put name here
        mov dx,offset devhlp
        call comnd
         jmp coms21             ; Did user type ^C.
         nop
        mov comand.cmstat,cmcfm ;simulate a confirm has been requested. [jrd]
;[jrd]  mov al,0                ; Need a null
;[jrd]  mov [bx],al             ; To terminate string
        mov dx,offset prtstr    ; Point to string
        mov ah,open             ; Open port
        mov al,2                ; For reading and writing
        int dos
        jnc coms22              ; Success
coms21: mov ah,prstr
        mov dx,offset erms41
        int dos
        mov dx,offset deverr
        int dos
        ret
coms22: mov prthnd,ax           ; Save handle.
        ret
coms3:  mov dx,offset hnd2      ; Let user supply file handle.
        call prompt
        mov ah,cmtxt
        mov bx,offset rdbuf     ; Where to put input.
        mov dx,offset hndhlp    ; In case user wants help.
        call comnd
         jmp coms31             ; No go.
         nop
        cmp ah,4                ; Right amount of data?
        ja coms31               ; Too many chars.
        mov si,offset rdbuf
        call atoi               ; Convert to real number
         jmp coms31             ; Keep trying.
         nop
        mov prthnd,ax           ; Value returned in AX
        ret
coms31: mov ah,prstr            ; Else, issue a warning.
        mov dx,offset hnderr
        int dos
        ret                     ; Yes, fail.
COMS    ENDP

; Set heath emulation on/off.

VTS     PROC    NEAR
        jmp notimp
VTS     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

VTSTAT  PROC    NEAR    ; For Status display [jrd]
        ret             ; no emulator status to display
VTSTAT  ENDP

; Initialize variables to values used by the generic MS DOS version.

lclini: mov flags.vtflg,0       ; Don't to terminal emulation.
        mov prthnd,3            ; No handle yet. [27d][28a d.rice]
;       call opnprt             ; Get file handle for comm port.
        ret

; Get a file handle for the communications port.  Use DOS call to get the
; next available handle.  If it fails, ask user what value to use (there
; should be a predefined handle for the port, generally 3).  The open
; will fail if the system uses names other than "COM1" or "COM2".
opnprt: mov al,flags.comflg
        mov ah,0
        mov si,ax
        shl si,1                ; double index
        mov dx,prttab[si]
        mov ah,open
        mov al,2
        int dos
        jnc opnpr2
        mov ah,prstr            ; It didn't like the string.
        mov dx,offset erms41
        int dos
        mov dx,offset hnd1
        int dos
opnpr0: mov dx,offset hnd2      ; Ask user to supply the handle.
        call prompt
        mov ah,cmtxt
        mov bx,offset rdbuf     ; Where to put input.
        mov dx,offset hndhlp    ; In case user wants help.
        call comnd
         jmp opnpr3             ; Maybe user typed a ^C.
         nop
        mov si,offset rdbuf
        call atoi               ; Convert to real number
         jmp opnpr0             ; Keep trying.
         nop
        mov prthnd,ax           ; Value returned in AX
        ret
opnpr2: mov prthnd,ax           ; Call succeeded.
        ret
opnpr3: cmp flags.cxzflg,'C'    ; Did user type a ^C?
        jne opnpr4              ; No, don't say anything.
        mov ah,prstr            ; Else, issue a warning.
        mov dx,offset hnderr
        int dos
opnpr4: ret                     ; Yes, fail.

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

; Initialization for using serial port.  Returns normally.
SERINI  PROC    NEAR
        cld                     ; Do increments in string operations
        call clrbuf             ; Clear input buffer.
        ret                     ; We're done.
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
        ret                     ; All done.
SERRST  ENDP

; Produce a short beep.  The PC DOS bell is long enough to cause a loss
; of data at the port.  Returns normally.

BEEP    PROC    NEAR
        mov dl,bell
        mov ah,dconio
        int dos
        ret
BEEP    ENDP

;
;put the number in ax into the buffer pointed to by di. di is updated.
;

nout    proc    near
        mov     dx,0            ;high order is always zero
        mov     bx,10
        div     bx              ;divide to get digit
        push    dx              ;save remainder till later
        or      ax,ax           ;test the quotient
        jz      noutl           ;zero, no more number
        call    nout            ;else call for rest of number
noutl:  pop     ax              ;get digit back
        add     al,'0'          ;make it displayable
        stosb                   ;drop it off
        ret                     ;and exit
nout    endp


; Dumb terminal emulator.  Doesn't work too well above 1200 baud (and
; even at 1200 baud you sometimes lose the first one or two characters
; on a line).
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:  push ax
        and al,7fh              ; mask off parity for terminal
        mov dl,al
        mov ah,conout
        int dos                 ; go print it
        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
        jz term1                ; no character, go on
        cmp al,ourarg.escc      ; escape char?
        je term4                ; yes, exit
        push ax                 ; save char
        mov ah,al
;[jrd]  or ah,80H               ; turn on hi bit so DOS doesn't interfere
        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

; 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