|  | DataMuseum.dkPresents historical artifacts from the history of: DKUUG/EUUG Conference tapes | 
This is an automatic "excavation" of a thematic subset of
 See our Wiki for more about DKUUG/EUUG Conference tapes Excavated with: AutoArchaeologist - Free & Open Source Software. | 
top - metrics - downloadIndex: T m
    Length: 57900 (0xe22c)
    Types: TextFile
    Names: »msuapr.asm«
└─⟦9ae75bfbd⟧ Bits:30007242 EUUGD3: Starter Kit
    └─⟦71044c191⟧ »EurOpenD3/misc/kermit.ms-2.32.tar.Z« 
        └─⟦31f2d420d⟧ 
            └─⟦this⟧ »msuapr.asm« 
        NAME    msugen
; File MSUAPR.ASM
; Kermit action verbs tied to Apricot funtion keys 26.04.88 [rwtc]
;
; Keyboard translator, by Joe R. Doupnik, Dec 1986
;  with contributions from David L. Knoell.
; For Generic keyboard reading (via DOS)
; edit history:
; Last edit 1 Jan 1988
; 1 Jan 1988 version 2.30
 
        include mssdef.h
 
        public  keybd, dfkey, shkey, msuinit
 
; some definitions
 
maxkeys equ     128                     ; maximum number of key definitions
maxstng equ     64                      ; maximum number of multi-char strings
stbuflen equ    1000                    ; length of string buffer (bytes)
 
verb    equ     8000h                   ; dirlist flag: use verb action table
strng   equ     4000h                   ; dirlist flag: use string action table
scan    equ     100h                    ; keycode flag: code is scan not ascii
braceop equ     7bh                     ; opening curly brace
bracecl equ     7dh                     ; closing curly brace
 
datas   segment public 'datas'
        extrn taklev:byte, comand:byte, intake:byte, flags:byte
        extrn shkadr:word, stkadr:word, trans:byte
                                                ; system dependent references
 
;;;     System Independent local storage
 
tranbuf db      132 dup (?)             ; 132 byte translator work buffer
crlf    db      cr,lf,'$'
dfhelp1 db    cr,lf,' Enter key',27h,'s identification as a character',cr,lf
        db      '  or as its numerical equivalent \{b##} of ascii',cr,lf
        db      '  or as its scan code \{b##}'
        db      cr,lf,'  or as SCAN followed by its scan code',cr,lf
        db      '    where b is O for octal, X for hex, or D for decimal'
        db      ' (default).',cr,lf,'    Braces {} are optional.'
        db      cr,lf,'    Follow the identification with the new definition.'
        db      cr,lf,' or CLEAR to restore initial key settings.$'
dfaskky db      cr,lf,' Push key to be defined: $'
dfaskdf db      ' Enter new definition: $'
verbbad db      cr,lf,' No such verb',cr,lf,'$'
strbad  db      cr,lf,' Not enough space for new string',cr,lf,'$'
keyfull db      cr,lf,' No more space to define keys',cr,lf,'$'
dfkopps db      cr,lf,' Opps! That is Kermit',27h,'s Escape Char.'
        db      ' Translation is not permitted.',cr,lf,'$'
shkmsg1 db      cr,lf,'Push key to be shown (? shows all): $'
shkmsg2 db      ' decimal is defined as',cr,lf,'$'
shkmsg3 db      cr,lf,'... more, push any key to continue ...$'
kwarnmsg db     cr,lf,' Notice: this form of Set Key is obsolete$'
 
ascmsg  db      ' Ascii char: $'
scanmsg db      ' Scan Code $'
strngmsg db     ' String: $'
verbmsg db      ' Verb: $'
noxmsg  db      ' Self, no translation.$'
fremsg  db      cr,lf,' Free space: $'
kyfrdef db      ' key and $'
stfrdef db      ' string definitions, $'
stfrspc db      ' string characters.',cr,lf,'$'
                                        ; translation tables
keylist dw      maxkeys dup (0)         ; 16 bit keycodes, paralled by dirlist
dirlist dw      maxkeys dup (0)         ; director {v+s} + {index | new char}
sptable dw      maxstng dup (0)         ; list of asciiz string offsets
stbuf   dw      stbuflen dup (0)        ; buffer for strings
strmax  dw      stbuf                   ; first free byte in stbuf
listptr dw      0                       ; item number for keylist and dirlist
nkeys   dw      0                       ; number of actively defined keys
keycode dw      0                       ; ascii/scan code for key
kbtemp  dw      0                       ; scratch storage for translator
brace   db      0                       ; brace detected flag byte
oldform db      0                       ; old form Set Key, if non-zero
verblen dw      0                       ; length of user's verb (work temp)
kwcnt   dw      0                       ; number of keywords (work temp)
msutake db      0                       ; if being run from take file or not
twelve  dw      12d
 
;;;     End System Independent Data Area
 
;;;     System Dependent Data Area
;       edit dfhelp2 to include nice list of verbs for this system.
dfhelp2 db      cr,lf,' Enter either \{Kverb}  for a Kermit action verb',cr,lf
        db      ' or a replacement string  (single byte binary numbers are'
        db      ' \{b##})',cr,lf,' or nothing at all to undefine a key.'
        db      cr,lf,' Braces {} are optional, and strings maybe enclosed in'
        db      ' them.',cr,lf,' Strings may not begin with the character'
        db      ' combinations of  \k  or  \{k',cr,lf
        db      '    (start with a { brace instead).',cr,lf,lf
        db      ' Verbs are as follows:',cr,lf
        db      ' Logoff (suspend logging), Logon (resume logging),'
        db      ' DOS (push to), null (send a)',cr,lf
        db      ' break, help, prtscn, status, exit'
        db      cr,lf,'$'
 
        ; Aliaskey: keys having aliases - same ascii code but more than one
        ; scan code, as on auxillary keypads. Use just scan codes with these.
        ; Alternative use: force ascii keys to report out just scan codes.
        ; Table format: high byte = scan code, low byte = ascii code.
        ; Contents are machine dependent.
aliaskey db     0
aliaslen equ    ($-aliaskey) shr 1      ; number of words in aliaskey table
 
kverbs  db      10                      ; number of table entries below
        mkeyw   'prtscn',trnprs         ; independent of ordering and case!
        mkeyw   'break',sendbr          ; mkeyw 'name',procedure entry point
        mkeyw   'Hangup',chang
        mkeyw   'null',snull
        mkeyw   'help',cquery
        mkeyw   'status',cstatus
        mkeyw   'exit',cquit
        mkeyw   'DOS',kdos
        mkeyw   'Logoff',klogof
        mkeyw   'Logon',klogon
                                ; Initialization data.
kbdinlst equ    this byte     ; Kermit IBM initialization time keyboard setup
        mkeyw   '\x7f',8        ; Backspace key sends DEL
        mkeyw   '\Khelp',177    	; F1
        mkeyw   '\Kbreak',178           ; F2
        mkeyw   '\Kstatus',179		; F3
        mkeyw   '\Kdos',180		; F4
        mkeyw   '\Klogoff',185		; F5
        mkeyw   '\Klogon',183		; F8
        mkeyw   '\Kexit',184		; F9
        mkeyw   '\Khangup',186		; F10
        dw      0               ; end of table marker
 
datas   ends
 
code    segment public 'code'
                ; system independent external items
        extrn   comnd:near, prompt:near                 ; in msscmd
        extrn   strlen:near                             ; in mssfil
        extrn   cnvlin:near, katoi:near, decout:near    ; in msster
                ; system dependent external items
                ; these are system dependent action verbs, in msxgen
        extrn   beep:near, trnprs:near, sendbr:near
        extrn   chrout:near, cstatus:near, cquit:near, cquery:near
        extrn   klogon:near, klogof:near, kdos:near, snull:near, chang:near
 
        assume  cs:code, ds:datas, es:datas
 
; Begin system independent Keyboard Translator code
 
; MSUINIT performs Kermit startup initialization for this file.
; Note, shkadr and stkadr are pointers tested by Set/Show Key calls. If they
; are not initialized here then the older Set/Show Key procedures are called.
MSUINIT PROC    NEAR                    ; call from msx/msy init code
        call    kbdinit                 ; optional: init translator tables
        mov     shkadr,offset shkey     ; declare keyboard translator present
        mov     stkadr,offset dfkey     ; via Show and Set Key proc addresses
        ret
MSUINIT ENDP
 
; Call Keybd to read a keyboard char (just returns carry clear if none) and
; 1) send the replacement string (or original char if not translated)
;    out the serial port, or
; 2) execute a Kermit action verb.
; Returns carry set if Connect mode is to be exited, else carry clear.
; Modifies registers ax and bx.
KEYBD   PROC    NEAR                    ; active translator
        call    getkey                  ; read keyboard
        jnc     keybd1                  ; nc = data available
        jmp     keybdx                  ; else just return carry clear
keybd1: call    postkey                 ; call system dependent post processor
        cmp     nkeys,0                 ; is number of keys defined = 0?
        jz      keybd3                  ; z = none defined
        push    di                      ; search keylist for this keycode
        push    cx                      ; save some registers
        push    es
        mov     di,offset keylist       ; list of defined keycode words
        mov     ax,keycode              ; present keycode
        mov     cx,nkeys                ; number of words to examine
        push    ds
        pop     es                      ; make es:di point to datas segment
        cld
        repne   scasw                   ; find keycode in list
        pop     es                      ; restore regs
        pop     cx
        je      keybd1b                 ; e = found, work with present di
        pop     di                      ; restore original di
        test    keycode,scan            ; is this a scan code?
        jz      keybd3                  ; z = no, it's ascii, use al as char
        call    beep                    ; say key is a dead one
        clc
        ret                             ; and exit with no action
 
keybd1b:sub     di,2                    ; correct for auto increment
        sub     di,offset keylist       ; subtract start of list ==> listptr
        mov     ax,dirlist[di]          ; ax = contents of director word
        pop     di                      ; restore original di
                                        ; dispatch on Director code
        test    ax,verb                 ; verb only?
        jnz     keyvb                   ; e = yes
        test    ax,strng                ; multi-char string only?
        jnz     keyst                   ; e = yes, else single char & no xlat.
                                        ;
                                        ; do single CHAR output (char in al)
keybd3: cmp     al,trans.escchr         ; Kermit's escape char?
        je      keybd3a                 ; e = yes, handle separately
        call    chrout                  ; transmit the char
        clc                             ; return success
        ret
keybd3a:stc                             ; set carry for jump to Quit
        ret
 
keyvb:  and     ax,not(verb+strng)      ; VERB (ax=index, remove type bits)
        mov     bx,offset kverbs        ; start of verb table
        cmp     al,byte ptr [bx]        ; index > number of entries?
        jae     keybdx                  ; ae = illegal, indices start at 0
        inc     bx                      ; bx points to first entry
        push    cx                      ; save reg
        mov     cx,ax                   ; save the index in cx
        inc     cx                      ; counter, indices start at 0
keyvb1: mov     al,byte ptr [bx]        ; cnt value
        xor     ah,ah
        add     ax,4                    ; skip text and '?' and value word
        add     bx,ax                   ; look at next slot
        loop    keyvb1                  ; walk to correct slot
        sub     bx,2                    ; backup to value field
keyvb2: pop     cx                      ; restore reg
        mov     bx,[bx]                 ; get value field of this slot
        cmp     bx,0                    ; jump address defined?
        je      keybdx                  ; e = no, skip the action
        jmp     bx                      ; perform the function
 
keyst:  and     ax,not(verb+strng)      ; STRING (ax=index, remove type bits)
        shl     ax,1                    ; convert to word index
        push    si                      ; save working reg
        mov     si,ax                   ; word subscript in table
        mov     si,sptable[si]          ; memory offset of selected string
        cmp     si,0                    ; is there a string pointer present?
        je      keyst3                  ; e = no, skip operation
        cld                             ; scan forward
        lodsb                           ; get string length byte
        mov     cl,al
        xor     ch,ch                   ; to cx for looping
        jcxz    keybdx                  ; z = null length
keyst2: lodsb                           ; get new string char into al
        push    si                      ; save si and cx around call
        push    cx
        call    chrout                  ; send out the char in al
        pop     cx                      ; recover regs
        pop     si
        loop    keyst2                  ; loop through whole string
keyst3: pop     si                      ; restore reg
 
keybdx: clc                             ; return success
        ret
KEYBD   ENDP
 
; SET KEY - define a key   (procedure dfkey)
; SET KEY <key ident><whitespace><new meaning>
; Call from Kermit level. Returns as ret if failure or as rskp if success.
;
DFKEY   PROC    NEAR                    ; define a key as a verb or a string
        mov     keycode,0               ; clear keycode
        mov     oldform,0               ; say no old form Set Key yet
        mov     dx,offset tranbuf       ; our work space
        mov     word ptr tranbuf,0      ; insert terminator
        mov     bx,offset dfhelp1       ; first help message
        mov     ah,cmfile               ; parse a word
        call    comnd                   ; get key code or original ascii char
         nop
         nop
         nop
        mov     al,intake               ; reading from Take file indirectly
        or      al,taklev               ; ditto, directly
        mov     msutake,al              ; save here
        or      ah,ah                   ; any text given?
        jnz     dfkey12                 ; nz = yes, so don't consider prompts
                                        ; interactive key request
        cmp     intake,0                ; in a Take file?
        je      dfkey10                 ; e = no, prompt for keystroke
        jmp     dfkey0                  ;  else say bad syntax
dfkey10:mov     ah,prstr
        mov     dx,offset dfaskky       ; ask for key to be pressed
        int     dos
dfkey11:call    getkey                  ; read key ident from keyboard
        jc      dfkey11                 ; c = no response, wait for keystroke
        mov     ah,prstr                ; display cr/lf
        mov     dx,offset crlf
        int     dos
        call    shkey0                  ; show current definition (in SHKEY)
        jmp     dfkey1e                 ; prompt for and process definition
 
dfkey12:                                ; Look for word SCAN and ignore it
        mov     dx,word ptr tranbuf     ; get first two characters
        or      dx,2020h                ; map upper to lower case
        cmp     dx,'cs'                 ; first two letters of word "scan"?
        je      dfkey                   ; e = yes, skip the word
        cmp     dx,'lc'                 ; first two letters of word "clear"?
        je      dfkeyc                  ; e = yes, reinit keyboard
        cmp     ah,1                    ; number of characters received
        ja      dfkey1                  ; a = more than one, decode
        mov     ah,byte ptr tranbuf     ; get the single char
        mov     byte ptr keycode,ah     ; store as ascii keycode
        jmp     dfkey1b                 ; go get definition
 
dfkey0: mov     dx,offset dfhelp1       ; say bad definition command
        mov     ah,prstr
        int     dos
        jmp     rskp
 
dfkeyc:                                 ; CLEAR key defs, restore startup defs
        mov     cx,maxkeys              ; size of keycode tables
        push    es                      ; save register
        push    ds
        pop     es                      ; make es point to datas segment
        mov     ax,0                    ; null, value to be stored
        mov     di,offset dirlist       ; director table
        cld
        rep     stosw                   ; clear it
        mov     cx,maxkeys
        mov     di,offset keylist       ; keycode table
        rep     stosw                   ; clear it
        mov     cx,maxstng
        mov     di,offset sptable       ; string pointer table
        rep     stosw                   ; clear it
        pop     es                      ; recover register
        mov     strmax,offset stbuf     ; clear string buffer
        mov     stbuf,0                 ;
        mov     nkeys,0                 ; clear number of defined keys
        call    msuinit                 ; restore startup definitions
        jmp     rskp
                                        ; Multi-char key identification
dfkey1: mov     si,offset tranbuf       ; point to key ident text
        cmp     byte ptr [si],'0'       ; is first character numeric?
        jb      dfkey1a                 ; b = no
        cmp     byte ptr [si],'9'       ; in numbers?
        ja      dfkey1a                 ; a = no
        mov     keycode,scan            ; setup keycode for scan value
        mov     dx,si                   ; get length of string in cx
        call    strlen
        push    ds
        pop     es                      ; make es point to datas segment
        push    si
        add     si,cx                   ; point at string terminator
        mov     di,si
        inc     di                      ; place to store string (1 byte later)
        inc     cx                      ; include null terminator
        std                             ; work backward
        rep     movsb                   ; move string one place later
        cld
        pop     si
        mov     byte ptr [si],'\'       ; make ascii digits into \nnn form
        mov     oldform,0ffh            ; set old form flag
        mov     dx,offset kwarnmsg      ; tell user this is old form
        mov     ah,prstr
        int     dos
dfkey1a:call    katoi                   ; convert ascii number to binary in ax
        jc      dfkey0                  ; c = no number converted
        or      keycode,ax              ; store in keycode
 
dfkey1b:                                ; Get Definition proper
        test    oldform,0ffh            ; old form Set Key active?
        jz      dfkey1f                 ; z = no
        mov     bx,offset tranbuf       ; get new definition on main cmd line
        mov     word ptr [bx],0         ; insert terminator
        mov     dx,offset dfhelp2       ; help for definition of key
        mov     ah,cmtxt                ; read rest of line into tranbuf
        call    comnd
         nop                            ; allow null definitions
         nop
         nop
        or      ah,ah                   ; char count zero?
        jz      dfkey1e                 ; z = zero, prompt for definition
        jmp     dfkey1g                 ; process definition
 
dfkey1e:mov     ah,prstr
        mov     dx,offset crlf
        int     dos
        mov     dx,offset dfaskdf       ; prompt for definition string
        call    prompt                  ; Kermit prompt routine
        mov     comand.cmcr,1           ; permit bare carriage returns
dfkey1f:mov     bx,offset tranbuf       ; get new definition
        mov     word ptr [bx],0         ; insert terminator
        mov     dx,offset dfhelp2       ; help for definition of key
        mov     ah,cmtxt                ; read rest of line into tranbuf
        call    comnd
         jmp r                          ; exit now on ^C from user
         nop
        cmp     comand.cmcr,0           ; prompting for definition?
        je      dfkey1g                 ; e = no, trim leading whitespace
        mov     comand.cmcr,0           ; turn off allowance for bare c/r's
        jmp     dfkey2                  ; interactive, allow leading whitespace
dfkey1g:xchg    ah,al                   ; put byte count in al
        xor     ah,ah                   ; clear high byte
        mov     kbtemp,ax               ; and save count in kbtemp
        mov     ah,cmcfm                ; get a confirm
        call    comnd
         jmp    r                       ; none so declare parse error
         nop                            ; round out to three bytes
        mov     cx,kbtemp               ; string length
        jcxz    dfkey2                  ; z = empty string
        push    si
        push    di
        mov     si,offset tranbuf       ; strip leading white space
dfkey1c:cld                             ; work forward
        lodsb                           ; read string char into al
        dec     cx                      ; number of chars left to read
        cmp     al,' '                  ; a space?
        je      dfkey1c                 ; e = yes, keep going
        cmp     al,tab                  ; tab?
        je      dfkey1c                 ; e = yes, keep going
        dec     si                      ; offset inc si in lodsb
        add     cx,2                    ; include terminator, offset dec above
        jcxz    dfkey1d                 ; z = nothing to move
        mov     di,offset tranbuf       ; destination is start of buffer
        push    ds
        pop     es
        cld
        rep     movsb                   ; copy text part of string
dfkey1d:pop     di
        pop     si
 
dfkey2:                                 ; Examine translation
        mov     al,trans.escchr         ; current escape char (port dependent)
        cmp     al,byte ptr keycode     ; is this Kermit's escape char?
        jne     dfkey2a                 ; ne = no
        test    keycode,scan            ; see if scan code
        jnz     dfkey2a                 ; nz = scan, so not ascii esc char
        mov     dx,offset dfkopps       ; Opps! msg
        mov     ah,prstr                ; complain and don't redefine
        int     dos
        jmp     rskp
 
dfkey2a:push    di                      ; get a director code for this key
        push    cx
        mov     di,offset keylist       ; list of keycodes
        mov     cx,nkeys                ; number currently defined
        mov     ax,keycode              ; present keycode
        jcxz    dfkey2b                 ; cx = 0 means none defined yet
        cld
        push    ds
        pop     es
        repne   scasw                   ; is current keycode in the list?
        jne     dfkey2b                 ; ne = not in list
        sub     di,2                    ; correct for auto increment
        sub     di,offset keylist
        mov     listptr,di              ; list pointer for existing definition
        pop     cx
        pop     di
        jmp     dfkey3                  ; go process definition
 
dfkey2b:pop     cx                      ; key not currently defined so
        pop     di                      ;  make a new director entry for it
        mov     bx,nkeys                ; number of keys previously defined
        cmp     bx,maxkeys              ; enough space?
        jae     dfkey2c                 ; ae = no, complain
        shl     bx,1                    ; count words
        mov     listptr,bx              ; index into word list
        mov     ax,keycode              ; get key's code
        mov     keylist[bx],ax          ; store it in list of keycodes
        mov     dirlist[bx],0           ; clear the new director entry
        inc     nkeys                   ; new number of keys
        jmp     dfkey3                  ; go process definition
 
dfkey2c:mov     dx,offset keyfull       ; say key space is full already
        mov     ah,prstr
        int     dos
        jmp     rskp                    ; tell parser we are happy
; listptr has element number in keylist or dirlist; keycode has key's code.
 
; Parse new definition. First look for Kermit verbs as a line beginning
; as \K or \{K. Otherwise, consider the line to be a string.
; In any case, update the Director table for the new definition.
 
dfkey3: mov     brace,0                 ; assume not using braces
        mov     si,offset tranbuf       ; start of definition text
        cmp     byte ptr [si],'\'       ; starts with escape char?
        jne     dfkey5                  ; ne = no, so we have a string
        inc     si                      ; skip the backslash
        cmp     byte ptr [si],braceop   ; starts with \{?
        jne     dfkey3a                 ; ne = no
        inc     si                      ; skip the opening brace
        mov     brace,bracecl           ; expect closing brace
dfkey3a:cmp     byte ptr [si],'K'       ; starts with \{K or \K?
        je      dfkey3b                 ; e = yes
        cmp     byte ptr [si],'k'       ; starts as \{k or \k?
        jne     dfkey5                  ; ne = no, then it's a string
dfkey3b:inc     si                      ; yes, skip the K too
                                        ; Kermit action VERBS
        push    si                      ; save verb name start address
dfkey4a:cld
        lodsb                           ; scan til closing brace or w/s or end
        cmp     al,0                    ; premature end?
        je      dfkey4b                 ; e = yes, accept without brace
        cmp     al,brace                ; closing brace?
        je      dfkey4b                 ; e = yes
        cmp     al,spc                  ; white space or control char?
        ja      short dfkey4a           ; a = no, so not at end yet
dfkey4b:mov     byte ptr[si-1],0        ; insert null terminator
        pop     si                      ; recover start address
        call    tstkeyw                 ; find keyword, kw # returned in kbtemp
        jc      dfkey4d                 ; c = no keyword found, complain
        call    remstr                  ; clear old string, if string
        mov     ax,kbtemp               ; save keyword number
        and     ax,not(verb+strng)      ; clear verb / string field
        or      ax,verb                 ; set verb ident
        mov     si,listptr
        mov     dirlist[si],ax          ; store info in Director table
        jmp     dfkey7                  ; show results and return success
 
dfkey4d:mov     dx,offset verbbad       ; say no such verb
        mov     ah,prstr
        int     dos
        jmp     rskp
 
; Here we are left with the definition string; si points to its start, and
; kbtemp holds its length (number of bytes). Null termination. If the string
; begins with an opening brace it terminates on a matching closing brace
; or the end of line, whichever occurs first. Trailing whitespace removed
; before examining braces.
; Null length strings mean define key as Self.
                                        ; STRING definitions
dfkey5: call    remstr                  ; first, clear old string, if any
        mov     si,offset tranbuf       ; si=source, di=dest, convert in-place
        mov     di,si
        call    cnvlin                  ; convert numbers, cx gets line length
        mov     si,offset tranbuf       ; provide address of new string
        cmp     cx,1                    ; just zero or one byte to do?
        jbe     dfkey6                  ; e = yes, do as a char
        call    insertst                ; insert new string, returns reg cx.
        jc      dfkey5h                 ; c = could not do insert
        mov     si,listptr              ; cx has type and string number
        mov     dirlist[si],cx          ; update Director table from insertst
        jmp     dfkey7                  ; show results and return success
 
dfkey5h:mov     dx,offset strbad        ; display complaint
        mov     ah,prstr
        int     dos
dfkeyx: jmp     rskp
 
                ; define SINGLE CHAR replacement or CLEAR a key definition.
                ; cx has char count 1 (normal) or 0 (to undefine the key).
dfkey6: jcxz    dfkey6c                 ; z = cx= 0, clear definition
        mov     al,byte ptr [si]        ; get first byte from definition
        xor     ah,ah                   ; set the type bits to Char
        mov     si,listptr
        mov     dirlist[si],ax          ; store type and key's new code
        jmp     dfkey7                  ; return success
 
dfkey6c:push    si                      ; clear a definition,
        push    di                      ; listptr points to current def
        mov     si,listptr              ; starting address to clear
        add     si,offset dirlist
        mov     di,si                   ; destination
        add     si,2                    ; source is next word
        mov     cx,nkeys                ; current number of keys defined
        add     cx,cx                   ; double for listptr being words
        sub     cx,listptr              ; cx = number of words to move
        shr     cx,1                    ; convert to actual number of moves
        jcxz    dfkey6d                 ; z = none, just remove last word
        push    es
        push    ds
        pop     es                      ; make es:di point to datas segment
        cld
        push    cx                      ; save cx
        rep     movsw                   ; move down higher list items
        pop     cx
        mov     si,listptr              ; do keylist too, same way
        add     si,offset keylist
        mov     di,si
        add     si,2
        rep     movsw
        pop     es
dfkey6d:mov     si,nkeys                ; clear old highest list element
        shl     si,1                    ; address words
        mov     dirlist[si],0           ; null the element
        mov     keylist[si],0           ; null the element
        dec     nkeys                   ; say one less key defined now
        pop     di                      ; restore saved registers
        pop     si
 
dfkey7: mov     ah,msutake              ; Finish up. In a Take file?
        or      ah,taklev               ; or even directly
        cmp     ah,0
        je      dfkey7a                 ; e = no
        cmp     flags.takflg,0          ; echo Take commands?
        je      dfkey7b                 ; e = no
dfkey7a:mov     ah,prstr                ; display cr/lf
        mov     dx,offset crlf
        int     dos
        call    shkey0                  ; show new definition (in SHKEY)
        call    shkfre                  ; show free string space
dfkey7b:jmp     rskp                    ; return success
DFKEY   ENDP
 
; SHOW KEY <cr> command. Call from Kermit level. Vectored here by SHOW
; command. Replaces obsolete procedure in msx---.
; Prompts for a key and shows that key's (or all if ? entered) keycode,
; definition, and the key definition free space remaining.
 
SHKEY   PROC    NEAR                    ; Show key's definition command
        mov     ah,cmcfm                ; get a confirm
        call    comnd
         nop                            ; ignore any additional text
         nop
         nop
        push    bx
        mov     dx,offset shkmsg1       ; ask for original key
        mov     ah,prstr
        int     dos
shky0:  call    getkey                  ; read keyboard, output to keycode
        jc      shky0                   ; wait for a key (c = nothing there)
        cmp     byte ptr keycode,'?'    ; query for all keys?
        jne     shky0a                  ; ne = no, not a query
        test    keycode,scan            ; is this a scan code, vs ascii query?
        jz      shky0c                  ; z = no Scan, so it is a query
 
shky0a: mov     ah,prstr                ; show single key. Setup display
        mov     dx,offset crlf
        int     dos
        call    shkey0                  ; show just one key
shky0b: call    shkfre                  ; show free string space
        jmp     shkeyx                  ; exit
 
shky0c: mov     cx,nkeys                ; Show all keys. nkeys = number defined
        jcxz    shky0b                  ; z = none to show
        mov     si,offset keylist       ; list of definitions
        push    si                      ; save pointer
shky1:  pop     si                      ; recover pointer
        cld
        lodsw                           ; get a keycode
        push    si                      ; save pointer
        push    cx                      ; save counter
        mov     keycode,ax              ; save new keycode
        mov     ah,prstr
        mov     dx,offset crlf
        int     dos
        call    shkey0                  ; show this keycode
 
        pop     cx                      ; pause between screens, recover cntr
        push    cx                      ; save it again
        dec     cx                      ; number yet to be shown
        jcxz    shky1b                  ; z = have now shown all of them
        mov     ax,nkeys                ; number of defined keys
        sub     ax,cx                   ; minus number yet to be displayed
        xor     dx,dx                   ; clear extended numerator
        div     twelve                  ; two lines per definition display
        or      dx,dx                   ; remainder zero (12 defs shown)?
        jnz     shky1b                  ; nz = no, not yet so keep going
        mov     ah,prstr
        mov     dx,offset shkmsg3       ; "push any key to continue" msg
        int     dos
shky1a: call    getkey                  ; get any key
        jc      shky1a                  ; c = nothing at keyboard yet, wait
shky1b: pop     cx                      ; resume loop
        loop    shky1
        pop     si                      ; clean stack
        call    shkfre                  ; show free string space
        jmp     shkeyx                  ; exit
 
                ; show key worker routine, called from above
                                        ; SHKEY0 called by DFKEY just above
SHKEY0: test    keycode,scan            ; scan code?
        jz      shkey1                  ; z = no, regular ascii
 
                                        ; SCAN codes
        mov     dx,offset scanmsg       ; say Scan Code:
        mov     ah,prstr
        int     dos
        mov     ah,conout
        mov     dl,'\'                  ; add backslash before number
        int     dos
        mov     ax,keycode              ; get key's code again
        call    decout                  ; display 16 bit decimal keycode
        jmp     shkey2                  ; go get definition
 
shkey1: mov     dx,offset ascmsg        ; say ASCII CHAR
        mov     ah,prstr
        int     dos
        mov     dl,byte ptr keycode     ; get ascii code (al part of input)
        mov     ah,conout
        cmp     dl,spc                  ; control code?
        jae     shkey1a                 ; ae = no
        push    dx                      ; save char
        mov     dl,5eh                  ; show caret first
        int     dos
        pop     dx
        add     dl,'A'-1                ; ascii bias
shkey1a:cmp     dl,del                  ; DEL?
        jne     shkey1b                 ; ne = no
        mov     dl,'D'                  ; spell out DEL
        int     dos
        mov     dl,'E'
        int     dos
        mov     dl,'L'
shkey1b:int     dos
        mov     dl,spc                  ; add a couple of spaces
        int     dos
        int     dos
        mov     dl,'\'                  ; add backslash before number
        int     dos
        mov     ax,keycode              ; show 16 bit keycode in decimal
        call    decout                  ; and go get definiton
 
                                        ; Display defintion
shkey2: mov     dx,offset shkmsg2       ; intermediate part of reply
        mov     ah,prstr                ; " is defined as "
        int     dos
        push    di                      ; get a director code for this key
        push    cx
        mov     di,offset keylist       ; list of keycodes
        mov     cx,nkeys                ; number currently defined
        jcxz    shkey2a                 ; z = none
        mov     ax,keycode              ; present keycode
        push    ds
        pop     es                      ; use datas segment for es:di
        cld
        repne   scasw                   ; is current keycode in the list?
        jne     shkey2a                 ; ne = not in list
        sub     di,2                    ; correct for auto increment
        sub     di,offset keylist
        mov     listptr,di              ; list pointer for existing definition
        pop     cx
        pop     di
        jmp     shkey3                  ; go process definition
 
shkey2a:pop     cx
        pop     di
        mov     dx,offset noxmsg        ; say Self (no translation)
        mov     ah,prstr
        int     dos
        ret                             ; return to main show key loop
 
shkey3:                                 ; translations, get kind of.
        mov     si,listptr
        test    dirlist[si],verb        ; defined as verb?
        jnz     shkey6                  ; nz = yes, go do that one
        test    dirlist[si],strng       ; defined as string?
        jz      shkey3a                 ; z = no
        jmp     shkey8                  ; yes, do string display
shkey3a:
        mov     dx,offset ascmsg        ; CHAR. say 'Ascii char:'
        mov     ah,prstr
        int     dos
        mov     ax,dirlist [si]         ; get type and char
        mov     dl,al                   ; put char here for display
        push    ax                      ; save here too
        mov     ah,conout
        cmp     dl,spc                  ; control code?
        jae     shkey4                  ; ae = no
        push    dx
        mov     dl,5eh                  ; show caret
        int     dos
        pop     dx
        add     dl,'A'-1                ; add ascii bias
shkey4: cmp     dl,del                  ; DEL?
        jne     shkey4a                 ; ne = no
        mov     dl,'D'                  ; spell out DEL
        int     dos
        mov     dl,'E'
        int     dos
        mov     dl,'L'
shkey4a:int     dos
        mov     dl,spc                  ; add a couple of spaces
        mov     ah,conout
        int     dos
        int     dos
        mov     dl,'\'                  ; add backslash before number
        int     dos
        pop     ax                      ; recover char
        xor     ah,ah                   ; clear high byte
        call    decout                  ; show decimal value
        ret                             ; return to main show key loop
 
shkey6: mov     ah,prstr                ; VERB
        mov     dx,offset verbmsg       ; say 'verb'
        int     dos
        mov     si,listptr              ; get verb index from director
        mov     dx,dirlist[si]
        and     dx,not(verb+strng)      ; remove type bits, leaves verb number
        mov     bx,offset kverbs        ; table of verbs & actions
        mov     al,byte ptr [bx]        ; number of keywords
        xor     ah,ah
        dec     ax
        mov     kwcnt,ax                ; save number of last one here
        cmp     dx,ax                   ; asking for more than we have?
        ja      shkeyx                  ; a = yes, exit bad
        inc     bx                      ; point to first slot
        mov     cx,0                    ; current slot number
shkey6b:cmp     cx,dx                   ; this slot?
        je      shkey6c                 ; e = yes, print the text part
        ja      shkeyx                  ; a = beyond, exit bad
        mov     al,byte ptr [bx]        ; get cnt (keyword length)
        xor     ah,ah
        add     ax,4                    ; skip over '$' and two byte value
        add     bx,ax                   ; bx = start of next keyword slot
        inc     cx                      ; current keyword number
        jmp     short shkey6b           ; try another
shkey6c:inc     bx                      ; look at text field
        mov     dx,bx                   ; offset for printing
        mov     ah,prstr
        int     dos
        mov     ah,conout
        mov     dl,spc                  ; add a couple of spaces
        int     dos
        int     dos
        mov     dl,'\'                  ; show verb name as \Kverb
        int     dos
        mov     dl,'K'
        int     dos
        mov     ah,prstr
        mov     dx,bx                   ; show name part again
        int     dos
        ret                             ; return to main show key loop
 
shkey8: mov     ah,prstr                ; STRING
        mov     dx,offset strngmsg      ; say String:
        int     dos
        mov     si,listptr              ; get index from director
        mov     bx,dirlist[si]
        and     bx,not(verb+strng)      ; remove type bits
        shl     bx,1                    ; index words
        mov     si,sptable[bx]          ; table of string offsets
        mov     cl,byte ptr [si]        ; get string length byte
        xor     ch,ch
        inc     si                      ; point to string text
        mov     ah,conout
shkey8a:cld
        lodsb                           ; get a byte
        cmp     al,spc                  ; control code?
        jae     shkey8b                 ; ae = no
        push    ax
        mov     dl,5eh                  ; show caret first
        int     dos
        pop     ax
        add     al,40h                  ; convert to printable for display
shkey8b:mov     dl,al
        int     dos                     ; display it
        loop    shkey8a                 ; do another
        ret                             ; return to main show key loop
 
shkeyx: pop     bx                      ; restore reg
        jmp     rskp                    ; return success
SHKEY   ENDP
 
;;;     keyboard translator local support procedures, system independent
 
; Tstkeyw checks text word pointed to by si against table of keywords (pointed
; to by kverbs, made by mkeyw macro); returns in bx either action value or 0.
; Returns in kbtemp the number of the keyword and carry clear, or if failure
; returns kbtemp zero and carry set.
; Keyword structure is:         db      cnt     (length of string 'word')
;                               db      'word'  (keyword string)
;                               db      '$'     (printing terminator)
;                               dw      value   (value returned in bx)
; Make these with macro mkeyw such as   mkeyw 'test',15   with the list of
; such keywords headed by a byte giving the number of keywords in the list.
tstkeyw proc    near
        push    ax
        push    cx
        push    si
        mov     verblen,0               ; verblen will hold verb length
        push    si                      ; save user's verb pointer
tstkw1: cld
        lodsb                           ; get a verb character
        cmp     al,spc                  ; verbs are all non-spaces and above
        jbe     tstkw2                  ; be = done (space or control char)
        inc     verblen                 ; count verb length
        jmp     short tstkw1            ; printable char, look for more
tstkw2: pop     si                      ; pointer to verb
        mov     bx,offset kverbs        ; table of Kermit verb keywords
        mov     al,byte ptr [bx]        ; number of keywords
        xor     ah,ah
        mov     kwcnt,ax                ; save number of keywords here
        inc     bx                      ; point bx to first slot
        mov     kbtemp,0                ; remember which keyword
 
tstkw3:                                 ; match table keyword and text word
        mov     cx,verblen              ; length of user's verb
        cmp     byte ptr [bx],cl        ; compare length vs table keyword
        jne     tstkw4                  ; ne = not equal lengths, try another
        push    si                      ; lengths match, how about spelling?
        push    bx
        inc     bx                      ; point at start of keyword
tstkw3a:mov     ah,byte ptr [bx]        ; keyword char
        mov     al,byte ptr [si]        ; text char
        cmp     ah,'A'
        jb      tstkw3b                 ; b = control chars
        cmp     ah,'Z'
        ja      tstkw3b                 ; a = not upper case alpha
        add     ah,'a'-'A'              ; convert upper case to lower case
tstkw3b:cmp     al,'A'
        jb      tstkw3c
        cmp     al,'Z'
        ja      tstkw3c
        add     al,'a'-'A'              ; convert upper case to lower case
tstkw3c:cmp     al,ah                   ; test characters
        jne     tstkw3d                 ; ne = no match
        inc     si                      ; move to next char
        inc     bx
        loop    tstkw3a                 ; loop through entire length
tstkw3d:pop     bx
        pop     si
        jcxz    tstkw5                  ; z: cx = 0, exit with match;
                                        ;  else select next keyword
tstkw4: inc     kbtemp                  ; number of keyword to test next
        mov     cx,kbtemp
        cmp     cx,kwcnt                ; all done? Recall kbtemp starts at 0
        jae     tstkwx                  ;ae = exhausted search, unsuccessfully
        mov     al,byte ptr [bx]        ; cnt (keyword length from macro)
        xor     ah,ah
        add     ax,4                    ; skip over '$' and two byte value
        add     bx,ax                   ; bx = start of next keyword slot
        jmp     tstkw3                  ; do another comparison
 
tstkw5:                                 ; get action pointer
        mov     al,byte ptr [bx]        ; cnt (keyword length from macro)
        xor     ah,ah
        add     ax,2                    ; skip over '$'
        add     bx,ax                   ; now bx points to dispatch value
        mov     bx,[bx]                 ; bx holds dispatch value
        clc                             ; carry clear for success
        jmp     short tstkwxx           ; exit
        ret
tstkwx: xor     bx,bx                   ; exit when no match
        mov     kbtemp,bx               ; make verb number be zero too
        stc                             ; carry set for failure
tstkwxx:pop     si
        pop     cx
        pop     ax
        ret
tstkeyw endp
 
; Insert asciiz string pointed to by si into string buffer stbuf.
; Reg cx has string length upon entry.
; Success: returns offset of first free byte (strmax) in string buffer stbuf,
; cx = type and Index of new string, and carry clear.
; Failure = carry set.
insertst proc   near
        push    bx
        push    dx
        push    si
        push    di
        push    kbtemp          ; save this variable too
        mov     dx,cx           ; save length of incoming string in dx
        mov     bx,offset sptable ; table of string offsets
        mov     kbtemp,0        ; slot number
        mov     cx,maxstng      ; number of entries, find an empty slot
insert1:cmp     word ptr[bx],0  ; slot empty?
        je      insert2         ; e = yes
        inc     kbtemp          ; remember slot number
        add     bx,2            ; look at next slot
        loop    insert1         ; keep looking
        jmp     short insert4   ; get here if no empty slots
insert2:                        ; see if stbuf has sufficient space
        mov     cx,dx           ; length of new string to cx
        mov     di,strmax       ; offset of first free byte in stbuf
        add     di,cx           ; di = address where this string would end
        cmp     di,offset stbuf+stbuflen ; beyond end of buffer?
        jae     insert4         ; ae = yes, not enough room
        mov     di,strmax       ; point to first free slot in stbuf
        mov     [bx],di         ; fill slot with address offset of buffer
        push    es
        push    ds
        pop     es              ; point es:di to datas segment
        cld
        mov     byte ptr [di],cl ; length of text for new string
        inc     di              ; move to next storage slot
        rep     movsb           ; copy string text
        pop     es
        mov     strmax,di       ; offset of next free byte
        mov     cx,kbtemp       ; return new slot number with Director Index
        and     cx,not(strng+verb) ; clear type bits
        or      cx,strng        ; say type is multi-char string
        clc                     ; say success
        jmp     short insertx   ; exit
insert4:stc                     ; say no-can-do
insertx:pop     kbtemp
        pop     di
        pop     si
        pop     dx
        pop     bx
        ret
insertst endp
 
; Remove (delete) string. Enter with listptr preset for director entry.
; Acts only on existing multi-char strings; recovers freed space.
; All registers preserved.
remstr  proc    near
        push    si
        mov     si,listptr              ; list pointer
        test    dirlist[si],strng       ; multi-char string?
        pop     si
        jnz     remst1                  ; nz = a multi-char string
        ret                             ; else do nothing
remst1: push    ax
        push    bx
        push    cx
        push    dx
        push    si
        mov     si,listptr
        mov     ax,dirlist[si]          ; Director table entry
        and     ax,not(strng+verb) ; clear type bits, leave string's pointer
        mov     dirlist[si],0           ; clear Director table entry
        shl     ax,1                    ; index words not bytes
        mov     si,offset sptable       ; list of string offsets in stbuf
        add     si,ax                   ; plus index = current slot
        mov     bx,[si]                 ; get offset of string to be deleted
        mov     dx,bx                   ; save in dx for later
        mov     cl,byte ptr [bx]        ; get length byte
        xor     ch,ch                   ; get length of subject string
        inc     cx                      ; length byte too, cx has whole length
        sub     strmax,cx       ; count space to be freed (adj end-of-buf ptr)
        mov     word ptr [si],0 ; clear sptable of subject string address
        push    cx                      ; save length of purged string
        push    di                      ; save di
        push    si
        push    es                      ; save es
        push    ds
        pop     es              ; setup es:di to be ds:offset of string
        mov     di,dx           ; destination = start address of purged string
        mov     si,dx           ; source = start address of purged string
        add     si,cx           ;  plus string length of purged string.
        mov     cx,offset stbuf+stbuflen ; 1 + address of buffer end
        sub     cx,si                   ; 1 + number of bytes to move
        dec     cx                      ; number of bytes to move
        jcxz    remst2                  ; z = none
        cld                             ; direction is forward
        rep     movsb                   ; move down preserved strings
remst2: pop     es                      ; restore regs
        pop     di
        pop     si
        pop     ax              ; recover length of purged string (was in cx)
        mov     bx,offset sptable       ; string pointer table
        mov     cx,maxstng              ; max mumber of entries
remst4: cmp     [bx],dx         ; does this entry occur before purged string?
        jbe     remst5          ; be = before or equal, so leave it alone
        sub     [bx],ax         ; recompute address (remove old string space)
remst5: add     bx,2                    ; look at next list entry
        loop    remst4                  ; do all entries in sptable
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret
remstr  endp
 
shkfre  proc    near                    ; show free key & string defs & space
        push    ax                      ; preserves all registers.
        push    bx
        push    cx
        push    dx
        push    kbtemp
        mov     dx,offset fremsg
        mov     ah,prstr
        int     dos
        mov     ax,maxkeys              ; max number of key defs
        sub     ax,nkeys                ; number currently used
        call    decout                  ; show the value
        mov     ah,prstr
        mov     dx,offset kyfrdef       ; give key defs msg
        int     dos
        mov     bx,offset sptable       ; table of string pointers
        mov     cx,maxstng              ; number of pointers
        mov     kbtemp,0                ; number free
shkfr1: cmp     word ptr [bx],0         ; slot empty?
        jne     shkfr2                  ; ne = no
        inc     kbtemp                  ; count free defs
shkfr2: add     bx,2                    ; look at next slot
        loop    shkfr1                  ; do all of them
        mov     ax,kbtemp               ; number of free defs
        call    decout                  ; display
        mov     dx,offset stfrdef       ; say free string defs
        mov     ah,prstr
        int     dos
        mov     ax,offset stbuf+stbuflen ; 1 + last byte in stbuf
        sub     ax,strmax               ; offset of last free byte in stbuf
        call    decout
        mov     dx,offset stfrspc       ; give free space part of msg
        mov     ah,prstr
        int     dos
        pop     kbtemp
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret
shkfre  endp
; Initialize the keyboard tables at Kermit startup time. Optional procedure.
; Requires kbdinlst to be configured with mkeyw macro in the form
;       mkeyw   'definition',keytype*256+keycode
; keytype is 0 for scan codes and non-zero for ascii.
; Returns normally.
kbdinit proc    near                    ; read keyword kbdinlst and setup
        push    ds                      ;  initial keyboard assignments.
        pop     es                      ; set es:di to datas segment
        mov     taklev,1                ; pretend that we are in Take file
        mov     si,offset kbdinlst      ; start of list of definitions
kbdini1:mov     cl,byte ptr [si]        ; cnt field (keyword length of macro)
        xor     ch,ch
        jcxz    kbdinix                 ; z = null cnt field = end of list
        inc     si                      ; look at text field
        mov     di,offset tranbuf       ; where defkey expects text
        cld
        rep     movsb                   ; copy cx chars to tranbuf
        mov     byte ptr [di],0         ; insert null terminator
        inc     si                      ; skip '$' field
        mov     ax,word ptr [si]        ; get value field
        mov     keycode,ax              ; set key ident value
        push    si
        call    dfkey2                  ; put dfkey to work
         nop
         nop
         nop
        pop     si
        add     si,2                    ; point to next entry
        jmp     kbdini1                 ; keep working
kbdinix:mov     taklev,0                ; reset Take file level
        ret
kbdinit endp
;;;     End of System Independent Procedures
 
;;;     Begin System Dependent Procedures
 
; Read keyboard. System dependent.
; Return carry set if nothing at keyboard.
; If char present return carry clear with key's code in Keycode.
; If key is ascii put that in the low byte of Keycode and clear bit Scan in
; the high byte; otherwise, put the scan code in the lower byte and set bit
; Scan in the high byte.
; Bit Scan is set if key is not an ascii code.
; Modifies register ax.
getkey  proc    near
        mov     keycode,0
        mov     ah,dconio               ; check console
        mov     dl,0ffh                 ; input desired
        int     dos
        jnz     getky1                  ; nz = char available
        stc                             ; carry set = nothing available
        jmp     short getkyx            ; exit on no char available
getky1: cmp     al,0                    ; scan code being returned?
        jne     getky1a                 ; ne = no
        mov     ah,dconio               ; read second byte (scan code)
        mov     dl,0ffh
        int     dos
        jz      getkyx                  ; z = nothing there
        mov     ah,al                   ; scan code goes here
        mov     al,0                    ; ascii code goes here
getky1a:
        push    di                      ; check key (ax) for aliases
        push    cx
        push    es
        mov     di,offset aliaskey      ; list of aliased keys
        mov     cx,aliaslen             ; number of entries
        jcxz    getky2                  ; z = no entries
        push    ds
        pop     es                      ; make es:di point to datas segment
        cld
        repne   scasw                   ; look for a match
        jne     getky2                  ; ne = not there
        mov     al,0                    ; force use of scan code (in ah)
getky2: pop     es
        pop     cx
        pop     di
        or      al,al                   ; scan code being returned?
        jnz     getky3                  ; nz = no
        xchg    ah,al                   ; put scan code in ident area
        or      keycode,scan            ; set scan flag (vs ascii)
getky3: mov     byte ptr keycode,al     ; return key's code (usually ascii)
        clc                             ; carry clear = got a char
getkyx: ret
getkey  endp
 
 
postkey proc    near                    ; do sys dep action after reading
        ret                             ; key during active translation
postkey 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