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

⟦8c4d3d3b5⟧ TextFile

    Length: 37024 (0x90a0)
    Types: TextFile
    Names: »msster.asm«

Derivation

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

TextFile

        NAME    msster
; File MSSTER.ASM
; Last edit 21 Nov 1988
; 21 Nov 1988 Version 2.32
; 1 July 1988 Version 2.31
; 12 June 1988 Add error recovery if serial port fails to initialize
; 29 May 1988 Cleanup one letter Connect dispatch routines
; 27 Feb 1988 Add capability of stdin being a file. [jrd]
; 27 Jan 1988 Remove serrst call, done now in mssker idle loop. [jrd]
; 1 Jan 1988 version 2.30

        public  clscpt, defkey, clscpi, ploghnd, sloghnd, tloghnd
        public  dopar, shokey, cptchr, pktcpt, targ
        public  kbdflg, shkadr, telnet, ttyact
        public  cnvlin, katoi, decout, valout, atoi, cnvstr
        include mssdef.h

braceop equ     7bh                     ; opening curly brace
bracecl equ     7dh                     ; closing curly brace

datas   segment public 'datas'
        extrn   flags:byte, trans:byte, buff:byte, portval:word

targ    termarg <0,1,80,24,cptchr,2dch,0,scntab,deftab,0,,parnon>
crlf    db      cr,lf,'$'
tmsg1   db      cr,lf,'(Connecting to host, type $'
tmsg3   db      ' C to return to PC)',cr,lf,cr,lf,cr,lf,'$'
erms25  db      cr,lf,'?Input must be numeric$'
erms22  db      cr,lf,'?No open logging file$'
erms23  db      cr,lf,'?Error writing session log, suspending capture.'
        db      cr,lf,'$'
erms24  db      cr,lf,'?Error writing Packet log$'
esctl   db      'Control-$'

inthlp db cr,lf,'  ?  This message                    F  Dump screen to file'
       db cr,lf,'  C  Close the connection            P  Push to DOS'
       db cr,lf,'  S  Status of the connection        Q  Quit logging'
       db cr,lf,'  M  Toggle mode line                R  Resume logging'
       db cr,lf,'  B  Send a Break                    0  Send a null'
       db cr,lf,'  L  Send a long 1.8 s Break         H  Hangup phone'
       db cr,lf,'  Typing the escape character will send it to the host'
       db 0               ; this short-form obscures less screen area [jrd]

intprm  db      'Command> $'
intclet db      'B','C','F','H','L'     ; single letter commands
        db      'M','P','Q','R','S'     ; must parallel dispatch table intcjmp
        db      '?','0'
numlet  equ     $ - intclet             ; number of entries
intcjmp dw      intchb,intchc,intchf,intchh,intchl
        dw      intchm,intchp,intchq,intchr,intchs
        dw      intchu,intchn

pktbuf  db      cptsiz dup (?)  ; packet logging buffer
pktbp   dw      pktbuf          ; buffer pointer to next free byte
pktlft  dw      cptsiz          ; number free bytes left
capbuf  db      cptsiz dup (?)  ; session logging buffer
capbp   dw      capbuf          ; buffer pointer to next free byte
caplft  dw      cptsiz          ; number free bytes left

ploghnd dw      -1              ; packet logging handle
sloghnd dw      -1              ; session logging handle
tloghnd dw      -1              ; transaction logging handle

clotab  db      4
        mkeyw   'All',logpkt+logses+logtrn
        mkeyw   'Packets',logpkt
        mkeyw   'Session',logses
        mkeyw   'Transaction',logtrn

clseslog db     cr,lf,' Closing Session log$'
clpktlog db     cr,lf,' Closing Packet log$'
cltrnlog db     cr,lf,' Closing Transaction log$'
clohlp  db      cr,lf,' One of the following log files:'
        db      cr,lf,' ALL, Packets, Session, Transaction$'
scntab  dw      0
deftab  dw      0
sttmsg  db      cr,lf,'Type space to continue ...$'
kbdflg  db      0                       ; non-zero means char here from Term
ttyact  db      0                       ; Connect mode active, if non-zero
shkadr  dw      0                       ; offset of replacement Show Key cmd
ten     dw      10                      ; multiplier for setatoi
nbase   dw      ?                       ; currently active number base
numset  db      '0123456789ABCDEF'      ; number conversion alphabet
tmp     db      ?
datas   ends

code    segment public 'code'
        extrn   comnd:near, outchr:near, stat0:near, iseof:near
        extrn   clrbuf:near, term:near, strlen:near
        extrn   prtchr:near, ihostr:near
        extrn   beep:near, puthlp:near, getbaud:near, serhng:near
        extrn   serini:near,serrst:near, sendbr:near, showkey:near
        extrn   fpush:near, dumpscr:near, pcwait:near, sendbl:near
        assume  cs:code, ds:datas

; the show key command
shokey  proc    near
        cmp     shkadr,0                ; keyboard translator present?
        je      shokey1                 ; e = no, use regular routines
        mov     bx,shkadr               ; get offset of replacement routine
        jmp     bx                      ; and execute it rather than us
shokey1:jmp     rskp                    ; and return
shokey  endp
; enter with ax/scan code to define, si/ pointer to definition, cx/ length
; of definition.  Defines it in definition table. Obsolete.
defkey  proc    near
        ret
defkey  endp

; This is the CONNECT command

TELNET  PROC    NEAR
        mov     ah,cmcfm
        call    comnd                   ; Get a confirm
         jmp    r                       ;  Didn't get a confirm
        mov     ah,prstr                ; Output
        mov     dx,offset crlf          ; a crlf
        int     dos
        cmp     flags.vtflg,0           ; emulating a terminal?
        jne     teln1                   ; ne= yes, skip flashing message
        call    domsg                   ; Reassure user
teln1:  mov     al,0                    ; initial flags
        mov     ttyact,1                ; say telnet is active
        cmp     flags.modflg,0          ; mode line enabled?
        jne     tel010                  ; yes, go on
        or      al,modoff               ; no, make sure it stays off

tel010: or      al,havtt                ; defaults (!)
        test    flags.debug,logses      ; debug mode?
        jz      tel0                    ; z = no, keep going
        or      al,trnctl               ; yes, show control chars
tel0:   cmp     flags.vtflg,0           ; emulating a terminal?
        je      tel1                    ; e = no
        or      al,emheath              ; say emulating some kind of terminal
tel1:   mov     bx,portval
        cmp     [bx].ecoflg,0           ; echoing?
        jz      tel2
        or      al,lclecho
tel2:   call    getbaud                 ; pickup current baud rate for port
        mov     targ.flgs,al            ; store flags
        mov     ah,flags.comflg         ; COMs port identifier
        mov     targ.prt,ah             ; Port 1 or 2, etc
        mov     ah,trans.escchr         ; escape character
        mov     targ.escc,ah
        mov     ah,[bx].parflg          ; parity flag
        mov     targ.parity,ah
        mov     ax,[bx].baud            ; baud rate identifier
        mov     targ.baudb,al
        xor     ah,ah
        test    flags.capflg,logses     ; select session logging flag bit
        jz      tel3                    ; z = no logging
        mov     ah,capt                 ; set capture flag
tel3:   or      targ.flgs,ah

TEM:    call    serini                  ; init serial port
        jnc     tem0                    ; nc = success
        mov     ttyact,0                ; say we are no longer active
        jmp     rskp                    ; and exit Connect mode

tem0:   mov     dx,offset crlf          ; give user an indication that we are
        mov     ah,prstr                ; entering terminal mode
        int     dos
        mov     ax,offset targ          ; Point to terminal arguments
        call    term                    ; Call the main Terminal procedure
        or      targ.flgs,scrsam        ; assume screen is the same
tem1:   mov     al,kbdflg               ; get the char from Term, if any
        mov     kbdflg,0                ; clear the flag
        cmp     al,0                    ; was there a char from Term?
        jne     intch2                  ; ne = yes, else ask for one from kbd

intchar:call    iseof                   ; stdin at eof?
        jnc     intch1                  ; nc = not eof, get more
        mov     al,'C'                  ; use C when file is empty
        jmp     intchc                  ;  to provide an exit
intch1: mov     ah,coninq               ; read keyboard, no echo
        int     dos                     ; get a char
        cmp     al,0                    ; scan code indicator?
        jne     intch2                  ; ne = no, ascii
        mov     ah,coninq               ; read and discard scan code
        int     dos
        jmp     short intch1            ; try again
intch2: cmp     al,' '                  ; space?
        je      tem                     ; e = yes, ignore it
        cmp     al,cr                   ; check ^M (cr) against plain ascii M
        je      tem                     ; exit on cr
        cmp     al,trans.escchr         ; Is it the escape char?
        jne     intch3                  ; ne = no
        mov     ah,al
        call    outchr
         nop
         nop
         nop
        jmp     tem                     ; Return, we are done here
intch3: push    es
        push    ds
        pop     es
        mov     di,offset intclet       ; command letters
        mov     cx,numlet               ; quantity of them
        cmp     al,' '                  ; control code?
        jae     intch3a                 ; ae = no
        or      al,40H                  ; convert control chars to printable
intch3a:cmp     al,96                   ; lower case?
        jb      intch3b                 ; b = no
        and     al,not (20h)            ; move to upper case
intch3b:cld
        repne   scasb                   ; find the matching letter
        pop     es
        jne     intch4                  ; ne = not found, beep and get another
        dec     di                      ; back up to letter
        sub     di,offset intclet       ; get letter number
        shl     di,1                    ; make it a word index
        jmp     intcjmp[di]             ; dispatch to it
intch4: call    beep                    ; say illegal character
        jmp     intchar

intchb: call    sendbr                  ; 'B' send a break
        jmp     tem                     ; And return

intchc: mov     ttyact,0                ; 'C' say we are no longer active
;;;     call    serrst                  ; reset serial port
        jmp     rskp                    ; and exit Connect mode

intchf: call    dumpscr                 ; 'F' dump screen, use msy routine
        jmp     tem                     ; and return

intchh: call    serhng                  ; 'H' hangup phone
        call    serrst                  ; turn off port
        jmp     tem

intchl: call    sendbl                  ; 'L' send a long break
        jmp     tem

intchm: cmp     flags.modflg,1          ; 'M' toggle mode line, enabled?
        jne     intchma                 ; ne = no, leave it alone
        xor     targ.flgs,modoff        ; enabled, toggle its state
intchma:jmp     tem                     ; and reconnect

intchp: push    bx                      ; 'P' push to DOS
        mov     bx,portval
        mov     ah,byte ptr [bx].flowc  ; get XOFF char, or null
        pop     bx
        or      ah,ah                   ; check for null (no flow control)
        jz      intchpa                 ; z = null, don't send one
        call    outchr                  ; send XOFF to host while we are away
         nop
         nop
         nop
intchpa:call    serrst                  ; turn off serial interrupts
        call    fpush                   ; try pushing
         nop
         nop
         nop
        mov     dx,offset sttmsg        ; say we have returned
        mov     ah,prstr
        int     dos
        call    serini                  ; init serial port again
        jc      intchc                  ; nc = failure
        call    ihostr                  ; XON the host (if using flow control)
        jmp     intchsb                 ; wait for a space

intchq: test    targ.flgs,capt          ; 'Q' suspend logging. Logging active?
        jz      intchq1                 ; z = no
        and     targ.flgs,not capt      ; stop capturing
intchq1:jmp     tem                     ; and resume

intchr: test    flags.capflg,logses     ; 'R' resume logging. Can we capture?
        jz      intchr1                 ; z = no
        test    targ.flgs,capt          ; already capturing?
        jnz     intchr1                 ; yes, can't toggle back on then
        or      targ.flgs,capt          ; else turn flag on
intchr1:jmp     tem                     ; and resume

intchs: call    stat0                   ; 'S' status, call stat0
        call    puthlp                  ; put help on screen
        mov     dx,offset sttmsg
        mov     ah,prstr
        int     dos
intchsa:call    iseof                   ; is stdin at eof?
        jnc     intchsb                 ; nc = not eof, get more
        jmp     tem                     ; resume if EOF
intchsb:mov     ah,coninq               ; console input, no echo
        int     dos
        cmp     al,' '                  ; space?
        jne     intchsa
        and     targ.flgs,not scrsam    ; remember screen changed
        jmp     tem

intchu: mov     ax,offset inthlp        ; '?' get help message
        call    puthlp                  ; write help msg
        mov     dx,offset intprm
        mov     ah,prstr                ; Print it
        int     dos
        and     targ.flgs,not scrsam    ; remember screen changed
        jmp     intchar                 ; Get another char

intchn: mov     ah,0                    ; '0' send a null
        call    outchr
         nop
         nop
         nop
        jmp     tem
TELNET  ENDP
; Reassure user about connection to the host. Tell him what escape sequence
; to use to return and the communications port and baud; rate being used

DOMSG   PROC    NEAR
        mov     ah,prstr
        mov     dx,offset tmsg1
        int     dos
        call    escprt
        mov     ah,prstr
        mov     dx,offset tmsg3
        int     dos
        ret
DOMSG   ENDP

; print the escape character in readable format.

ESCPRT  PROC    NEAR
        mov     dl,trans.escchr
        cmp     dl,' '
        jge     escpr2
        push    dx
        mov     ah,prstr
        mov     dx,offset esctl
        int     dos
        pop     dx
        add     dl,040H         ; Make it printable
escpr2: mov     ah,conout
        int     dos
        ret
ESCPRT  ENDP


; Set parity for character in Register AL

dopar:  push    bx
        mov     bx,portval
        mov     bl,[bx].parflg          ; get parity flag byte
        cmp     bl,parnon               ; No parity?
        je      parret                  ; Just return
        and     al,07FH                 ; Strip parity. Same as Space parity
        cmp     bl,parspc               ; Space parity?
        je      parret                  ; e = yes, then we are done here
        cmp     bl,parevn               ; Even parity?
        jne     dopar0                  ; ne = no
        or      al,al
        jpe     parret                  ; pe = even parity now
        xor     al,080H                 ; Make it even parity
        jmp     short parret
dopar0: cmp     bl,parmrk               ; Mark parity?
        jne     dopar1                  ; ne = no
        or      al,080H                 ; Turn on the parity bit
        jmp     short parret
dopar1: cmp     bl,parodd               ; Odd parity?
        or      al,al
        jpo     parret                  ; Already odd, leave it
        xor     al,080H                 ; Make it odd parity
parret: pop     bx
        ret

cptchr  proc    near                    ; session capture routine, char in al
        push    di
        mov     di,capbp                ; buffer pointer
        mov     byte ptr [di],al
        inc     capbp
        pop     di
        dec     caplft                  ; decrement chars remaining
        jg      cptch1                  ; more room, forget this part
        call    cptdmp                  ; dump the info
cptch1: ret
cptchr  endp

cptdmp  proc    near                    ; empty the capture buffer
        push    ax
        push    bx
        push    cx
        push    dx
        mov     bx,sloghnd              ; get file handle
        cmp     bx,0                    ; is file open?
        jle     cptdm1                  ; le = no, skip it
        mov     cx,cptsiz               ; original buffer size
        sub     cx,caplft               ; minus number remaining
        jl      cptdm2                  ; means error
        jcxz    cptdm1                  ; z = nothing to do
        mov     dx,offset capbuf        ; the capture routine buffer
        mov     ah,write2               ; write with filehandle
        int     dos                     ; write out the block
        jc      cptdm2                  ; carry set means error
        mov     capbp,offset capbuf
        mov     caplft,cptsiz           ; init buffer ptr & chrs left
        jmp     short cptdm1
cptdm2: and     targ.flgs,not capt      ; so please stop capturing
        mov     dx,offset erms23        ; tell user the bad news
        mov     ah,prstr
        int     dos
cptdm1: pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret
cptdmp  endp

pktcpt  proc    near                    ; packet log routine, char in al
        push    di
        mov     di,pktbp
        mov     [di],al                 ; store char in buffer
        inc     pktbp                   ; move pointer to next free byte
        pop     di
        dec     pktlft                  ; decrement chars remaining
        jg      pktcp1                  ; more room, forget this part
        call    pktdmp                  ; dump the info
pktcp1: ret
pktcpt  endp

pktdmp  proc    near                    ; empty the capture buffer
        push    ax
        push    bx
        push    cx
        push    dx
        mov     bx,ploghnd              ; get file handle
        cmp     bx,0                    ; is file open?
        jle     cptdm1                  ; le = no, skip it
        mov     cx,cptsiz               ; original buffer size
        sub     cx,pktlft               ; minus number remaining
        jl      pktdm2                  ; l means error
        jcxz    pktdm1                  ; z = nothing to do
        mov     dx,offset pktbuf        ; the capture routine buffer
        mov     ah,write2               ; write with filehandle
        int     dos                     ; write out the block
        jc      pktdm2                  ; carry set means error
        mov     pktbp,offset pktbuf
        mov     pktlft,cptsiz           ; init buffer ptr & chrs left
        jmp     short pktdm1
pktdm2: and     targ.flgs,not capt      ; so please stop capturing
        mov     dx,offset erms24        ; tell user the bad news
        mov     ah,prstr
        int     dos
        call    clscp4                  ; close the packet log
pktdm1: pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret
pktdmp  endp

; CLOSE command

clscpt  proc    near
        mov     ah,cmkey
        mov     dx,offset clotab        ; close table
        mov     bx,offset clohlp        ; help
        call    comnd
         jmp    r
         nop
        mov     tmp,bl
        mov     ah,cmcfm
        call    comnd
         jmp    r
        mov     bl,tmp
        test    flags.capflg,0FFH       ; are any kinds active?
        jz      clscp1                  ; z = no
        cmp     bl,logpkt+logses+logtrn ; close all?
        je      clscpi                  ; e = yes
        cmp     bl,logpkt               ; just packet?
        je      clscp4
        cmp     bl,logses               ; just session?
        je      clscp6
        cmp     bl,logtrn               ; just session?
        je      clscp8
clscp1: mov     dx,offset erms22        ; say none active
        mov     ah,prstr
        int     dos
        jmp     rskp
                                        ; CLSCPI called at Kermit exit
CLSCPI: call    clscp4                  ; close packet log
        call    clscp6                  ; close session log
        call    clscp8                  ; close transaction log
        jmp     rskp                    ; return success

clscp4: push    bx                      ; PACKET LOG
        mov     bx,ploghnd              ; packet log handle
        cmp     bx,0                    ; is it open?
        jle     clscp5                  ; e = no
        call    pktdmp                  ; dump buffer
        mov     ah,close2
        int     dos
        mov     ah,prstr
        mov     dx,offset clpktlog      ; tell what we are doing
        int     dos
clscp5: mov     ploghnd,-1              ; say handle is invalid
        pop     bx
        and     flags.capflg,not logpkt ; say this log is closed
        ret

clscp6: push    bx                      ; SESSION LOG
        mov     bx,sloghnd              ; session log handle
        cmp     bx,0                    ; is it open?
        jle     clscp7                  ; e = no
        call    cptdmp                  ; dump buffer
        mov     ah,close2
        int     dos
        mov     ah,prstr
        mov     dx,offset clseslog      ; tell what we are doing
        int     dos
clscp7: mov     sloghnd,-1              ; say handle is invalid
        pop     bx
        and     flags.capflg,not logses ; say this log is closed
        ret

clscp8: push    bx                      ; TRANSACTION LOG
        mov     bx,tloghnd              ; transaction log handle
        cmp     bx,0                    ; is it open?
        jle     clscp9                  ; e = no
        mov     ah,close2
        int     dos
        mov     ah,prstr
        mov     dx,offset cltrnlog      ; tell what we are doing
        int     dos
clscp9: mov     tloghnd,-1              ; say handle is invalid
        pop     bx
        and     flags.capflg,not logtrn ; say this log is closed
        ret
clscpt  endp

; worker: copy line from si to di, first removing trailing spaces, second
; parsing out curly braced strings, then third converting \{b##} in strings
; to binary numbers. Returns carry set if error; else carry clear, with byte
; count in cx. Braces are optional but must occur in pairs.
; Items which cannot be converted to legal numbers are copied verbatium
; to the output string (ex: \{c}  is copied as \{c}  but \{x0d} is hex 0dh).
cnvlin  proc    near
        push    ax
        push    si                      ; source ptr
        push    di                      ; destination ptr
        push    es                      ; end of save regs
        push    ds                      ; move ds into es
        pop     es                      ; use datas segment for es:di
        call    cnvstr                  ; trim trailing, parse curly braces
        xor     cx,cx                   ; initialize returned byte count
cnvln1: cmp     byte ptr [si],0         ; at end of string?
        je      cnvln2                  ; e = yes, exit
        call    katoi                   ; read char, convert ascii to binary
        cld
        stosb                           ; save the char
        inc     cx                      ; and count it
        or      ah,ah                   ; is returned number > 255?
        jz      cnvln1                  ; z = no, do more chars
        push    ax
        stosb                           ; save high order byte next
        pop     ax
        inc     cx
        jmp     short cnvln1            ; do more chars
cnvln2: mov     byte ptr [di],0         ; plant terminator
        clc                             ; clear c bit, success
cnvlnx: pop     es                      ; restore regs
        pop     di                      ; destination ptr
        pop     si                      ; source ptr
        pop     ax
        ret
cnvlin  endp

; Convert string by first remove trailing spaces and then removing surrounding
; curly brace delimiter pair. Converts text in place.
; Enter with source ptr in si.
; Preserves all registers, uses byte tmp. 9 Oct 1987 [jrd]
;
cnvstr  proc    near
        push    ax
        push    cx
        push    dx
        push    si                      ; save start of source string
        push    di
        push    es
                                        ; 1. Trim trailing spaces
        mov     dx,si                   ; source address
        call    strlen                  ; get current length to cx
        jcxz    cnvst4                  ; z = nothing there
        mov     di,si                   ; set di to source address
        add     di,cx                   ; start at end of string
        dec     di                      ; ignore terminator
        mov     al,spc                  ; scan while spaces
        push    ds
        pop     es                      ; set es to datas segment
        std                             ; search backward
        repe    scasb                   ; scan off trailing spaces
        mov     byte ptr [di+2],0       ; terminate string after last text
        cld
        mov     di,si                   ; set destination address to source
                                        ; 2. Parse off curly brace delimiters
        cmp     byte ptr [si],braceop   ; opening brace?
        jne     cnvst4                  ; ne = no, ignore brace-matching code
        inc     si                      ; skip opening brace
        mov     dl,braceop              ; opening brace (we count them up)
        mov     dh,bracecl              ; closing brace (we count them down)
        mov     tmp,1                   ; we are at brace level 1
cnvst1: cld                             ; search forward
        lodsb                           ; read a string char
        stosb                           ; store char (skips opening brace)
        cmp     al,0                    ; at end of string?
        je      cnvst4                  ; e = yes, we are done
        cmp     al,dl                   ; an opening brace?
        jne     cnvst2                  ; ne = no
        inc     tmp                     ; yes, increment brace level
        jmp     short cnvst1            ;  and continue scanning

cnvst2: cmp     al,dh                   ; closing brace?
        jne     cnvst1                  ; ne = no, continue scanning
        dec     tmp                     ; yes, decrement brace level
        cmp     byte ptr [si],0         ; have we just read the last char?
        jne     cnvst3                  ; no, continue scanning
        mov     tmp,0                   ; yes, this is the closing brace
cnvst3: cmp     tmp,0                   ; at level 0?
        jne     cnvst1                  ; ne = no, #opening > #closing braces
        mov     byte ptr [di-1],0       ; plant terminator on closing brace

cnvst4: pop     es                      ; recover original registers
        pop     di
        pop     si
        pop     dx
        pop     cx
        pop     ax
        ret
cnvstr  endp

; Convert ascii strings of the form "\{bnnn}" to a binary word in ax.
; The braces are optional but must occur in pairs. Numeric base indicator "b"
; is O or o or X or x or D or d or missing, for octal, hex, or decimal (def).
; Enter with si pointing at "\".
; Returns binary value in ax with carry clear and si to right of "}" or at
; terminating non-numeric char if successful; otherwise, a failure,
; return carry set with si = entry value + 1 and first read char in al.

katoi   proc    near
        cld
        lodsb                           ; get first char
        xor     ah,ah                   ; clear high order field
        push    cx                      ; save working reg
        push    si                      ; save entry si+1
        push    bx
        push    ax                      ; save read char
KATOI1: cmp     al,0                    ; end of text? ENTRY POINT FOR ATOI
        je      katoi1a                 ; e = yes, exit failure
        cmp     al,'\'                  ; escape char?
        je      katoi1b                 ; e = yes
katoi1a:jmp     katoix                  ; common jump point to exit failure
katoi1b:lodsb                           ; get next char, maybe brace
        cmp     al,0                    ; premature end?
        je      katoi1a                 ; e = yes, exit failure
        xor     bx,bx                   ; no conv yet, assume no opening brace
        cmp     al,braceop              ; opening brace?
        jne     katoi2                  ; ne = no, have number or base
        mov     bl,bracecl              ; remember a closing brace is needed
        lodsb                           ; get number base, if any
katoi2: xor     cx,cx                   ; temporary place for binary value
        mov     nbase,10                ; assume decimal numbers
        cmp     al,0                    ; premature end?
        je      katoix                  ; e = yes, exit failure
        cmp     al,'a'                  ; lower case?
        jb      katoi3                  ; b = no
        cmp     al,'z'                  ; in range of lower case?
        ja      katoi3                  ; a = no
        and     al,5fh                  ; map to upper case
katoi3: cmp     al,'O'                  ; octal?
        jne     katoi4                  ; ne = no
        mov     nbase,8                 ; set number base
        jmp     short katoi6
katoi4: cmp     al,'X'                  ; hex?
        jne     katoi5                  ; ne = no
        mov     nbase,16
        jmp     short katoi6
katoi5: cmp     al,'D'                  ; decimal?
        jne     katoi7                  ; ne = no base char, assume decimal
        mov     nbase,10
katoi6: lodsb                           ; get a digit
katoi7: cmp     al,0                    ; premature end?
        je      katoi8a                 ; e = yes, use it as a normal end
        cmp     al,bl                   ; closing brace?
        je      katoi9                  ; e = yes
        call    cnvdig                  ; convert ascii to binary digit
        jc      katoi8                  ; c = cannot convert
        inc     bh                      ; say we did a successful conversion
        xor     ah,ah                   ; clear high order value
        push    ax                      ; save this byte's value
        xchg    ax,cx                   ; put binary summation in ax
        mul     nbase                   ; scale up current sum
        xchg    ax,cx                   ; put binary back in cx
        pop     ax                      ; recover binary digit
        add     cx,ax                   ; form running sum
        jc      katoix                  ; c = overflow error, exit
        cmp     dx,0                    ; overflow?
        jne     katoix                  ; ne = yes, exit with error
        jmp     short katoi6            ; get more

katoi8: cmp     bl,0                    ; closing brace needed?
        jne     katoix                  ; ne = yes, but not found
katoi8a:dec     si                      ; backup to reread terminator
katoi9: cmp     bh,0                    ; did we do any conversion?
        je      katoix                  ; e = no, exit failure
        pop     ax                      ; throw away old saved ax
        pop     bx                      ; restore bx
        pop     ax                      ; throw away starting si, keep current
        mov     ax,cx                   ; return final value in ax
        pop     cx                      ; restore old cx
        clc                             ; clear carry for success
        ret
katoix: pop     ax                      ; restore first read al
        pop     bx
        pop     si                      ; restore start value + 1
        pop     cx                      ; restore old cx
        stc                             ; set carry for failure
        ret
katoi   endp

cnvdig  proc    near                    ; convert ascii code in al to binary
        push    cx                      ; return carry set if cannot
        push    es                      ; nbase has numeric base
        push    di
        push    ax
        cmp     al,'a'                  ; lower case?
        jb      cnvdig1                 ; b = no
        cmp     al,'f'                  ; highest hex digit
        ja      cnvdigx                 ; a = illegal symbol
        sub     al,'a'-'A'              ; convert 'a' to 'f' to upper case
cnvdig1:mov     di,offset numset        ; set of legal number symbols
        mov     cx,nbase                ; number of legal symbols in this base
        cmp     cx,cx                   ; preset z flag
        push    ds
        pop     es                      ; point es at data segment
        cld                             ; scan forward
        repne   scasb                   ; find character in set
        jne     cnvdigx                 ; ne = not found
cnvdig2:inc     cx                      ; offset auto-dec of repne scasb above
        sub     cx,nbase                ; counted off minus length
        neg     cx                      ; two's complement = final value
        pop     ax                      ; saved ax
        mov     ax,cx                   ; return binary in al
        clc                             ; c clear for success
        jmp     short cnvdixx           ; exit
cnvdigx:stc                             ; c set for failure
        pop     ax
cnvdixx:pop     di
        pop     es
        pop     cx
        ret
cnvdig  endp

decout  proc    near            ; display decimal number in ax
        push    ax
        push    cx
        push    dx
        mov     cx,10           ; set the numeric base
        call    valout          ; convert and output value
        pop     dx
        pop     cx
        pop     ax
        ret
decout  endp

valout  proc    near            ; output number in ax using base in cx
                                ; corrupts ax and dx
        xor     dx,dx           ; clear high word of numerator
        div     cx              ; (ax / cx), remainder = dx, quotient = ax
        push    dx              ; save remainder for outputting later
        or      ax,ax           ; any quotient left?
        jz      valout1         ; z = no
        call    valout          ; yes, recurse
valout1:pop     dx              ; get remainder
        add     dl,'0'          ; make digit printable
        cmp     dl,'9'          ; above 9?
        jbe     valout2         ; be = no
        add     dl,'A'-1-'9'    ; use 'A'--'F' for values above 9
valout2:mov     ah,conout
        int     dos
        ret
valout  endp

; Convert input in buffer pointed to by SI to real number which is returned
; in AX.  Enter with string size in AH.
; Return on failure, return skip on success.      Revised by [jrd]
ATOI    PROC    NEAR
        mov     bx,0            ; high order of this stays 0
        mov     tmp,0           ; No input yet
        mov     cl,ah           ; Number of chars of input
        mov     ch,0            ; size of string
        mov     ax,0            ; init sum
        cld
atoi0:  jcxz    atoi4           ; Fail on no input
        lodsb                   ; get an input char
        dec     cx              ; count number remaining
        cmp     al,' '          ; leading space?
        je      atoi0           ; e = yes, skip it
        cmp     al,','          ; comma separator?
        je      atoi0           ; e = yes, skip it
        dec     si              ; back up source pointer for reread below
        inc     cx              ; and readjust byte counter
        mov     ax,0            ; clear sum
atoi1:  push    ax              ; save sum
        lodsb                   ; read a byte into al
        mov     bl,al           ; put it into bl
        pop     ax              ; regain sum
        cmp     bl,'9'          ; check range for '0' to '9'
        ja      atoi2           ; above '9'
        cmp     bl,'0'
        jb      atoi2           ; below '0'
        sub     bl,'0'          ; take away ascii bias
        mul     ten             ; sum * 10. dx = high, ax = low
        add     ax,bx           ; add current value
        mov     tmp,1           ; say have sum being computed
        loop    atoi1
        inc     si              ; inc for dec below
atoi2:  dec     si              ; point at terminator
        cmp     tmp,0           ; were any digits discovered?
        je      atoi4           ; e = no, fail
atoi3:  jmp     rskp            ; success exit, sum is in ax
atoi4:  mov     dx,offset erms25 ; Input must be numeric
        ret
ATOI    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