home *** CD-ROM | disk | FTP | other *** search
- ;****************************************************************************
- ; M A T H I O . A S M
- ;============================================================================
- ; Functions to convert binary values to ASCII (displayable) format
- ; as decimal, hexadecimal or binary integers.
- ; Functions to convert ASCII strings, representing decimal, hexadecimal
- ; or binary integers, to binary values.
- ;---------------------------------------------------------------------------
- ; Copyright (c) Simon Groes, 1994
- ;---------------------------------------------------------------------------
- ; Assemble with Borland Turbo Assembler v3.0
- ;****************************************************************************
-
- IDEAL
- DOSSEG
- MODEL small
-
- LOCALS
-
- ;----- Insert INCLUDE "filename" directives here
- INCLUDE "macro.inc"
- INCLUDE "common.inc"
-
- ;----- Insert EQU and = equates here
- hexBase = 10h
- binBase = 02h
- decBase = 0Ah
-
- DATASEG
-
- base dw 0
- wordVal dw 0
- ascDigit db '0123456789ABCDEF'
- ascBuffer db 20 DUP (0)
- ascBufLen = $ - ascBuffer
-
- ;----- Declare other variables with DB, DW, etc., here
-
- ;----- Specify any EXTRN variables here
-
- CODESEG
-
- ;----- Declare PUBLIC procedures here
- PUBLIC BinToAscii, AsciiToBin
- PUBLIC AsciiBinToBin, AsciiHexToBin, AsciiDecToBin
-
- ;----- Specify any EXTRN procedures here
- EXTRN strLength:proc, charToUpper:proc, strCopy:proc
-
- ;===============================================================
- ; Procedure: =*=BinToAscii=*=
- ;---------------------------------------------------------------
- ; Usage: Public - may be used by other asm files.
- ; Task: Convert 16-bit binary value to ascii format.
- ; Input: ax = 16-bit value
- ; bx = base (2,10,16)
- ; di = offset address of buffer to hold ascii string.
- ; cl = Minimum # of digits to output.
- ; ch = type of leading character, if cl > # digits output
- ; (usually '0' or SPACE).
- ; Output: none
- ; Registers: none
- ; Note: The buffer should be long enough to hold the ascii string
- ; representing the maximum value of a 1-word integer
- ; plus the appended 'H' plus NULL; ie 18 bytes.
- ;===============================================================
- PROC BinToAscii
-
-
- SaveRegs <es,di,si,dx,cx,bx,ax> ; Save modified register(s).
-
- ;---------------------------------------------------------------
- ; BinToAscii works by first dividing the original value in ax by the base.
- ; The remainder in dx then equals the value for the rightmost digit.
- ; Thereafter the quotients in ax are repeatedly divided by the base
- ; and the remainders in dx equal the digits from right to left.
- ;---------------------------------------------------------------
- smove es, ds ; es -> data segment
- mov si, di ; si = di = calling buffer.
- mov di, OFFSET ascBuffer ; Address buffer.
- add di, ascBufLen-3 ; di -> last digit in buffer.
- mov [BYTE di+2], NULL ; String terminator.
-
- ;----- Valid base ?
- cmp bx, binBase ; Binary ?
- jne @@Dec ; No : Is it decimal ?
- mov [BYTE di+1], 'B' ; Yes: Append 'B'
- jmp NEAR @@Valid
- @@Dec: cmp bx, decBase ; Decimal ?
- jne @@Hex ; No : Is it hexadecimal ?
- mov [BYTE di+1], NULL ; Yes: Append NULL
- jmp NEAR @@Valid
- @@Hex: cmp bx, hexBase ; Hexadecimal ?
- jne @@Return ; No : Invalid number, end.
- mov [BYTE di+1], 'H' ; Yes: Append 'H'.
- @@Valid:
- mov [base], bx ; Base in 'base' variable.
- mov bx, OFFSET ascDigit ; Address 'ascDigit' table.
- std ; Auto-decrement.
- @@Rpt:
- or cl, cl ; cl = 0 ?
- jz @@Ra ; Yes: Don't decrement.
- dec cl
- @@Ra: cmp ax, [base] ; ax >= [base] ?
- jb @@Next ; No : Exit loop.
- xor dx, dx ; Clear dx.
- div [base] ; dxax/[base]; ax=quotient,dx=rest.
- xchg ax, dx ; ax=rest,dx=quotient.
- xlat ; al = ascii digit.
- stosb ; [es:di] = al; dec di.
- xchg ax, dx ; ax = quotient, dx = rest.
- jmp NEAR @@Rpt ; Repeat sequence.
-
- @@Next:
- xlat ; al = ascii digit.
- mov [BYTE es:di], al ; [es:di] = al. di -> string.
- or cl, cl ; cl = 0 ?
- jz @@Copy ; Yes: Copy buffer to input string.
- dec di ; No : di -> next char.
- mov al, ch ; al = '0', SPACE etc.
- xor ch, ch ; Now cx = cl.
- @@Rpt2:
- repnz stosb ; [es:di] = al; dec di.
- inc di ; di -> start of string in buffer.
- @@Copy:
- xchg di, si ; di -> call buffer; si -> string.
- call strCopy ; Copy to caller's buffer.
- @@Return:
- RestoreRegs <ax,bx,cx,dx,si,di,es>
- ret
- ENDP BinToAscii
-
- ;===============================================================
- ; Procedure: =*=AsciiToBin=*=
- ;---------------------------------------------------------------
- ; Usage: Public - may be used by other asm files.
- ; Task: Convert string of ascii numeric characters
- ; to 16-bit binary value.
- ; Input: di = offset address of ascii string.
- ; Note: If the string is not decimal,
- ; it must be terminated with the following letters:
- ; h or H - hexadecimal, b or B - binary.
- ; Output: If valid number, ax = 16-bit binary value, cf = 0.
- ; If invalid number, ax = 0, cf = 1.
- ; Registers: ax changed.
- ;===============================================================
- PROC AsciiToBin
-
- ;----- Binary, Hexadecimal or Decimal ?
- call AsciiBinToBin ; Is it binary ?
- jnc @@Return ; Yes: cf = 0, ax = value, end.
- or ax, ax ; No : Not binary or invalid number?
- jnz @@Error ; Invalid: End with error.
- call AsciiHexToBin ; Is it hex ?
- jnc @@Return ; Yes: cf = 0, ax = value, end.
- or ax, ax ; No : Not hex or invalid number ?
- jnz @@Error ; Invalid: End with error.
- call AsciiDecToBin ; Is it decimal ?
- jnc @@Return ; Yes: cf = 0, ax = value, end.
- @@Error:
- xor ax, ax ; ax = 0.
- stc ; Set carry flag - error.
- @@Return:
- ret ; Return to caller.
- ENDP AsciiToBin
-
- ;===============================================================
- ; Procedure: =*=AsciiBinToBin=*=
- ;---------------------------------------------------------------
- ; Usage: Public - available to other asm files.
- ; Task: Convert ascii binary digit string to 16-bit value.
- ; Input: di = offset address of ascii string.
- ; Output: If binary, ax = 16-bit value.
- ; If not binary, cf = 1.
- ; Registers: ax is changed.
- ; Note: A 'B' or 'b' must be appended to all binary strings.
- ; If an error occurs, ax = errorcode.
- ; If ax = 0, a 'B' or 'b' was not appended (not binary).
- ; If ax = 0FFFFh, a 'B' or 'b' was appended, but
- ; an invalid digit (not '1' or '0') was encountered.
- ;===============================================================
- PROC AsciiBinToBin
-
- SaveRegs <bx,cx,dx,si> ; Save modified register(s).
-
- call strLength ; cx = length of string.
- mov si, di ; si -> ascii string.
- add si, cx ; si -> NULL.
- dec si ; si -> 'B' or 'b'.
- mov al, [BYTE si] ; al = 'B' or 'b'.
- call charToUpper ; al = 'B'.
- cmp al, 'B' ; al = 'B' ?
- jne @@NoBin ; No : End routine 'not binary'.
-
- ;---------------------------------------------------------------
- ; Binary routine reads string of '1's and '0's, starting from the
- ; least significant (left-most) character. If a '1' is encountered,
- ; the bit in dx, corresponding to the position of the '1' in the string,
- ; is switched on. If a '0' is encountered, it is left off.
- ;---------------------------------------------------------------
- dec cx ; cx = # of digits.
- cmp cx, 16 ; Too many digits ?
- ja @@Inval ; End, invalid number.
- dec si ; si -> last digit.
- xor ax, ax ; Clear ax.
- xor dx, dx ; Clear dx.
- mov bx, 0001h ; Bit 0 = 1, all other bits = 0.
- std ; Auto-decrement.
-
- ;----- Read sequence of digits and convert to single bits.
- @@Rpt1: lodsb ; al = [si], si-1.
- sub al, '0' ; al = 0 or 1.
- test al, 11111110b ; If not 1 or 0,
- jnz @@Inval ; end routine 'invalid digit'.
- or al, al ; al = 0 or 1 ?
- jz @@Bit0 ; If 0, do nothing.
- or dx, bx ; If 1, insert 1 into dx.
- @@Bit0: shl bx, 1 ; Move to next bit.
- loop @@Rpt1 ; Read next digit in string. cx-1.
- ;----- Conversion loop complete - binary value in dx.
- mov ax, dx ; Value in ax.
- clc ; cf = 0, no error.
- jmp NEAR @@Return ; End routine.
-
- @@NoBin:
- xor ax, ax ; ax = error code for 'not binary'.
- jmp NEAR @@Error
- @@Inval:
- mov ax, 0FFFFh ; ax = 'invalid digit' code.
- @@Error:
- stc ; Set carry flag.
- @@Return:
- RestoreRegs <si,dx,cx,bx> ; Restore register(s).
- ret ; Return to caller.
- ENDP AsciiBinToBin
-
- ;===============================================================
- ; Procedure: =*=AsciiHexToBin=*=
- ;---------------------------------------------------------------
- ; Usage: Public - available to other asm files.
- ; Task: Convert ascii hexadecimal digit string to 16-bit value.
- ; Input: di = offset address of ascii string.
- ; Output: If hexadecimal, ax = 16-bit value, cf = 0.
- ; If not hexadecimal, cf = 1, ax = 0.
- ; If invalid, cf = 1, ax = 0FFFFh.
- ; Registers: ax is changed.
- ; Note: An 'H' or 'h' must be appended to all hex strings.
- ; If an error occurs, ax = errorcode.
- ; If ax = 0, a 'H' or 'h' was not appended (not hex).
- ; If ax = 0FFFFh, a 'H' or 'h' was appended, but
- ; an invalid digit (not '0' to 'F') was encountered.
- ;===============================================================
- PROC AsciiHexToBin
-
- SaveRegs <es,bx,cx,dx,si> ; Save modified register(s).
-
- smove es, ds ; es -> data segment.
- mov si, di ; si -> ascii string.
- call strLength ; cx = length of string.
- add si, cx ; si -> NULL.
- dec si ; si -> 'H' or 'h'.
- std ; Auto-decrement si.
- lodsb ; ax = [si], si -> last digit.
- dec cx ; cx = # digits.
- call charToUpper ; al = 'H'.
- cmp al, 'H' ; al = 'H' ?
- jne @@NoHex ; No : End routine 'not hex'.
-
- ;---------------------------------------------------------------
- ; The hexadecimal routine converts the character placed in al
- ; into a 4-bit binary value. The value is then shifted to the
- ; nibble (4-bit unit) corresponding to the position of the ascii
- ; digit in the string. This value is then 'or'd onto the dx register.
- ;---------------------------------------------------------------
- cmp cx, 4 ; Too many digits ?
- ja @@Inval ; Yes: End, invalid number.
- xor ax, ax ; Clear ax.
- xor dx, dx ; Clear dl - counter.
- xor bx, bx ; To hold integer.
- std ; Auto-decrement.
-
- ; Read single digits and convert to 4-bit values.
- @@Rpt1: lodsb ; al = [si], si-1.
- cmp al, '0' ; digit >= '0' ?
- jb @@Inval ; No : Invalid digit, end.
- cmp al, '9' ; digit <= '9' ?
- jbe @@Sub0 ; Yes: Goto @@Sub0.
- call charToUpper ; Convert to uppercase.
- cmp al, 'A' ; digit >= 'A' ?
- jb @@Inval ; No : Invalid digit, end.
- cmp al, 'F' ; digit <= 'F' ?
- ja @@Inval ; No : Invalid digit, end.
- sub al, 'A'- ('9'+ 1) ; 'A'-('9'+1)=# chars between.
- @@Sub0: sub al, '0' ; Sub0: Subtract '0' from al.
- ; AL register now holds an increment into hex0toF table.
- or dl, dl ; dl = 0 ?
- jz @@R1a ; Yes: Don't shift ax.
- xchg cx, dx ; dx = cx; cx = dx.
- shl ax, cl ; Shift 4-bit value into position.
- xchg cx, dx ; Restore cx & dx.
- @@R1a: or bx, ax ; Insert 4-bit value into word.
- add dl, 4 ; dl = dl + 4.
- loop @@Rpt1 ; dec cx; If cx=0, exit loop.
- ; Conversion complete.
- mov ax, bx ; 16-bit value in ax.
- clc ; Reset (clear) carry flag.
- jmp NEAR @@Return ; End without error.
- @@NoHex:
- xor ax, ax ; ax = error code for 'not hex'.
- jmp NEAR @@Error
- @@Inval:
- mov ax, 0FFFFh ; ax = 'invalid digit' code.
- @@Error:
- stc ; Set carry flag.
- @@Return:
- RestoreRegs <si,dx,cx,bx,es> ; Restore register(s).
- ret ; Return to caller.
- ENDP AsciiHexToBin
-
- ;===============================================================
- ; Procedure: =*=AsciiDecToBin=*=
- ;---------------------------------------------------------------
- ; Usage: Public - available to other asm files.
- ; Task: Convert decimal digit string to 16-bit value.
- ; Input: di = offset address of string.
- ; Output: If decimal, ax = 16-bit value, cf = 0.
- ; If not decimal, cf = 1, ax = 0.
- ; If invalid digit, cf = 1, ax = 0FFFFh.
- ; Registers: ax is changed.
- ;===============================================================
- PROC AsciiDecToBin
-
- SaveRegs <es,bx,cx,dx,si> ; Save modified register(s).
-
- smove es, ds ; es = data segment.
- mov si, di ; si -> ascii string.
- call strLength ; cx = length of string (# digits).
- add si, cx ; si -> NULL.
- dec si ; si -> last digit.
- std ; Auto-decrement si.
- lodsb ; al = '0'->'9', si->2nd last digit.
- dec cx ; cx = # digits - 1.
- cmp al, '0' ; al >= '0' ?
- jb @@NoDec ; No : Not decimal, end.
- cmp al, '9' ; al <= '9' ?
- ja @@NoDec ; No : Not decimal, end.
-
- ;----- String is decimal number.
- xor ah, ah ; Clear ah.
- xor dx, dx ; Clear dx.
- mov bx, 10 ; bx = 10^1.
- mov [wordVal], 0000h ; Clear [wordVal].
- mov [base], 10 ; Base must be in word variable.
- sub al, '0' ; Convert to integer 0->9.
- or [wordVal], ax ; OR 1st (leftmost) digit onto var.
- @@Rpt1:
- jcxz @@Success ; No need for loop if only 1 digit.
- xor ax, ax ; Clear ax.
- lodsb ; al = [si], dec si.
- cmp al, '0' ; al >= '0' ?
- jb @@Inval ; No : Invalid digit, end.
- cmp al, '9' ; al <= '9' ?
- ja @@Inval ; No : Invalid digit, end.
- sub al, '0' ; Yes: al = 0 to 9.
- mul bx ; axdx = ax * bx(10^x).
- or dx, dx ; dx > 0 (number too large) ?
- jnz @@Inval ; Yes: Invalid number, end.
- add [wordVal], ax ; [wordVal] = [wordVal] + ax.
- jc @@Inval ; Number too large (invalid), end.
- mov ax, bx ; ax = 10^x.
- mul [base] ; ax = 10^(x+1).
- mov bx, ax ; bx = 10^(x+1).
- loop @@Rpt1 ; dec cx; If cx=0, exit loop.
- ;----- Conversion complete.
- @@Success:
- mov ax, [wordVal] ; ax = 16-bit value.
- clc ; Reset carry flag.
- jmp NEAR @@Return ; End without error.
- @@NoDec:
- xor ax, ax ; ax = error code for 'not decimal'.
- jmp NEAR @@Error
- @@Inval:
- mov ax, 0FFFFh ; ax = 'invalid number' code.
- @@Error:
- stc ; Set carry flag.
- @@Return:
- RestoreRegs <si,dx,cx,bx,es> ; Restore register(s).
- ret ; Return to caller.
- ENDP AsciiDecToBin
-
-
- END ; End of module.
-