This file can be included to 16bit programs written in Euro Assembler.
The library contains OS-independent macroinstructions for 16bit programs with CPU 8086
with calling convention similar to the standard Intel 8086 machine instruction set.
They mostly pass operands in general-purpose registers and change
the register contents on return.
Align* performs alignment at run time,
Clear, CopyTo provide some string operations,
Lod* converts numbers from human-readable notation to a binary number,
Sto* does the opposite.
Similar macros with identical names for different program width are defined in cpuext32.htm and cpuext64.htm.
See also cpuext.htm for width-indepentent macros.
cpuext16 HEAD
; Definition of flags used by macros in this library. %cpuextMinus %SETA 0x80 %cpuextSigned %SETA 0x40 %cpuextAlignL %SETA 0x20 %cpuextLeading0 %SETA 0x10 %cpuextLowCase %SETA 0x08 ; Saved values in standard BP frame. %Par4 %SET BP+24 %Par3 %SET BP+22 %Par2 %SET BP+20 %Par1 %SET BP+18 %ReturnAX %SET BP+14 %ReturnCX %SET BP+12 %ReturnDX %SET BP+10 %ReturnBX %SET BP+08 %ReturnSP %SET BP+06 %ReturnBP %SET BP+04 %ReturnSI %SET BP+02 %ReturnDI %SET BP+00
Align2Word %MACRO Variable
ADDW %Variable, 1
ANDW %Variable, ~1
%ENDMACRO Align2Word
Align2Dword %MACRO Variable
ADDW %Variable, 3
ANDW %Variable, ~3
%ENDMACRO Align2Dword
Align2Qword %MACRO Variable
ADDW %Variable, 7
ANDW %Variable, ~7
%ENDMACRO Align2Qword
SIZE# Operand.
Clear %MACRO Operand, Size=, Filler=0
PUSHW %Filler
%IF "%Size" !=== ""
PUSHW %Size
%ELSE
PUSHW SIZE# (%Operand)
%ENDIF
PUSHW %Operand
CALL Clear16@RT::
Clear16@RT:: PROC1
PUSHAW
MOV BP,SP
MOV AX,[%Par3] ; Filler.
MOV CX,[%Par2] ; Size.
MOV DI,[%Par1] ; Operand.
MOV AH,AL
SHR CX,1
JNC .20
STOSB
.20: JCXZ .90
REP:STOSW
.90:POPAW
RET 3*2
ENDP1 Clear16@RT::
%ENDMACRO Clear
Compare %MACRO Data1Ptr,Data1Size,Data2Ptr,Data2Size
%IF %# < 3 ; >
%ERROR ID=5911, "Macro Compare requires 3 or 4 parameters."
%EXITMACRO
%ENDIF
%IF %# > 3
PUSHW %Data2Size,%Data2Ptr,%Data1Size,%Data1Ptr
%ELSE
PUSHW %Data1Size,%Data2Ptr,%Data1Size,%Data1Ptr
%ENDIF
CALL Compare16@RT::
Compare16@RT:: PROC1
PUSHAW
MOV BP,SP
MOV SI,[%Par1] ; %Data1Ptr
MOV CX,[%Par2] ; %Data1Size
MOV DI,[%Par3] ; %Data2Ptr
CMP CX,[%Par4] ; %Data2Size
JNE .90:
REPE:CMPSB
.90:POPAW
RET 4*2
ENDP1 Compare16@RT::
%ENDMACRO Compare
CopyTo %MACRO Destination, Source, Size=
%IF "%Size" !=== ""
PUSHW %Size
%ELSE
%IF TYPE# %Destination = 'R'
%ERROR ID=5912, "CopyTo Size= is not specified."
%EXITMACRO CopyTo
%ELSE
PUSHW SIZE# (%Destination)
%ENDIF
%ENDIF
PUSHW %Source, %Destination
CALL CopyTo16@RT::
CopyTo16@RT:: PROC1
PUSHAW
MOV BP,SP
MOV CX,[%Par3] ; %Size
MOV SI,[%Par2] ; %Source
MOV DI,[%Par1] ; %Destination
CLD
SHR CX,1
JNC .20:
MOVSB
.20: JCXZ .90
REP:MOVSW
.90:POPAW
RET 3*2
ENDPROC1 CopyTo16@RT::
%ENDMACRO CopyTo
LodD %MACRO Source, Size=
%IF "%Size" === ""
%IF "%Source" === "" || "%Source" == "SI"
PUSHW -1
%ELSE
PUSHW SIZE# (%Source)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Source" == ""
PUSH SI
%ELSE
PUSHW %Source
%ENDIF
CALL LodD16@RT::
LodD16@RT:: PROC1
PUSHAW
MOV BP,SP
MOV DX,[%Par2] ; Size.
MOV SI,[%Par1] ; Source.
MOV CX,DX
CLD
ADD DX,SI ; DX points to the end of Source string.
INC CX
JNZ .00:
MOV DX,-1
.00: SUB AX,AX
SUB CX,CX ; Nonzero CX signalizes negative value.
SUB BX,BX ; Output value accumulator.
MOV DI,10 ; Numeric base.
.10: CMP SI,DX
JNB .Error:
LODSB
CMP AL,' '
JBE .10: ; Skip leading white spaces.
CMP AL,'+' ; Signum or digit expected.
JE .20:
CMP AL,'-'
JNE .30:
DEC CX
.20: CMP SI,DX ; At least one digit following the signum is expected.
JNB .Error:
LODSB
.30: SUB AL,'0'
JB .Error:
CMP AL,9
JA .Error:
MOV BX,AX ; Most significant digit was loaded.
.40: CMP SI,DX ; Other digits or underscores are expexted, otherwise the parser stops.
JNB .EndOfNumber:
LODSB
CMP AL,'_'
JE .40:
SUB AL,'0'
JB .EndOfNumber1:
CMP AL,9
JA .EndOfNumber1:
XCHG AX,BX
PUSH DX
MUL DI
POP DX
JC .Error:
ADD BX,AX
JC .Error:
SUB AX,AX
JMP .40:
.Error:DEC SI
STC
JMP .95:
.EndOfNumber1:DEC SI
.EndOfNumber:
JECXZ .90:
NEG BX
.90: CLC
MOV [%ReturnAX],BX
.95: MOV [%ReturnSI],SI
POPAW
RET 2*2
ENDPROC1 LodD16@RT::
%ENDMACRO LodD
LodDD %MACRO Source, Size=
%IF "%Size" === ""
%IF "%Source" === "" || "%Source" == "SI"
PUSHW 32K
%ELSE
PUSHQ SIZE# (%Source)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Source" == ""
PUSH SI
%ELSE
PUSHW %Source
%ENDIF
CALL LodDD16@RT::
LodDD16@RT:: PROC1
PUSHAW
MOV BP,SP
MOV DX,[%Par2] ; Size.
MOV SI,[%Par1] ; Source.
MOV CX,DX
ADD DX,SI ; Parse-end limit.
JNC .10:
MOV DX,-1
.10: INC CX
JNZ .20:
MOV DX,-1
.20: SUB AX,AX
SUB CX,CX ; Signum is positive if CX=0.
SUB BX,BX ; Output value accumulator.
MOV [%ReturnAX],BX
MOV [%ReturnDX],BX
MOV DI,10 ; Numeric base.
.30: CMP SI,DX
JNB .Error:
LODSB
CMP AL,' '
JBE .30: ; Skip leading white spaces.
CMP AL,'+' ; Signum or digit expected.
JE .40:
CMP AL,'-'
JNE .50:
DEC CX ; Nonzero CX signalizes that the number is negative.
.40: CMP SI,DX ; At least one digit following the signum is expected.
JNB .Error:
LODSB
.50: SUB AL,'0'
JB .Error:
CMP AL,9
JA .Error:
MOV [%ReturnAX],AX ; Most significant digit loaded.
.60: CMP SI,DX ; Other digits or underscores expected, otherwise the parser stops.
JNB .EndOfNumber:
XOR AX,AX
LODSB
CMP AL,'_'
JE .60:
SUB AL,'0'
JB .EndOfNumber1:
CMP AL,9
JA .EndOfNumber1:
MOV BX,AX
MOV AX,[%ReturnDX]
PUSH DX
MUL DI
POP DX
JC .Error:
MOV [%ReturnDX],AX
MOV AX,[%ReturnAX]
PUSH DX
MUL DI
ADD AX,BX
MOV [%ReturnAX],AX
ADC [%ReturnDX],DX
POP DX
JC .Error:
JMP .60:
.Error:DEC SI
STC
JMP .90:
.EndOfNumber1:DEC SI
.EndOfNumber:
CLC
JCXZ .90: ; If the number is positive.
NOTW [%ReturnAX] ; Otherwise CX=1.
NOTW [%ReturnDX]
ADDW [%ReturnAX],CX
ADCW [%ReturnDX],0
.90: MOVW [%ReturnSI],SI
POPAW
RET 2*2
ENDPROC1 LodDD16@RT::
%ENDMACRO LodDD
0x is not supported (LodH would return AX=0 and SI behind the 0x.
SIZE# %Source is assumed.
Size is not limited (max.32KB) if it cannot be determined from %Source.
LodH %MACRO Source, Size=, Align=Left
%LodHflags %SETA %cpuextAlignL & "%Align[1]" == "L"
PUSHW %LodHflags
%IF "%Size" === ""
%IF "%Source" === "" || "%Source" == "SI"
PUSHW 32K
%ELSE
PUSHW SIZE# (%Source)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Source" === ""
PUSH SI
%ELSE
PUSHW %Source
%ENDIF
CALL LodH16@RT::
LodH16@RT:: PROC1 ; %1=Source, %2=Size, %3=flags.
PUSHAW
MOV BP,SP
MOV SI,[%Par1] ; Source.
MOV CX,[%Par2] ; Size.
SUB AX,AX
SUB BX,BX ; Accumulator of the result value.
CLD
JCXZ .20:
TESTW [%Par3],%cpuextAlignL
JNZ .30:
.10: LODSB ; White spaces are tolerated.
CMP AL,' '
JA .40:
LOOP .10:
.20: STC ; Error.
JMP .95:
.30: LODSB ; Signum or digit expected.
.40: CMP AL,'+'
JE .70:
CMP AL,'-'
JNE .60:
ORW [%Par3],%cpuextMinus
JMP .70:
.50: LODSB ; Digit expected.
.60: SUB AL,'0'
JB .80:
CMP AL,9
JNA .65:
SUB AL,'A'-'0'
JB .80:
CMP AL,5
JNA .64:
SUB AL,'a'-'A'
JB .80:
CMP AL,5
JA .80:
.64: ADD AL,10
.65: SAL BX,4
ADD BX,AX
ORW [%Par3],%cpuextLeading0 ; At least one digit was found.
.70: LOOP .50:
JMP .85:
.80: DEC SI
.85: TESTW [%Par3],%cpuextLeading0
JZ .20:
TESTW [%Par3],%cpuextMinus
JZ .90:
NEG BX
.90: CLC
MOV [%ReturnAX],BX
MOV [%ReturnSI],SI
.95:POPAW
RET 3*2
ENDP1 LodH16@RT::
%ENDMACRO LodH
0x is not supported (LodHD would return DX=AX=0 and SI behind the 0x.
SIZE# %Source is assumed.
Size is not limited (max. 32KB) if it cannot be determined from %Source.
LodHD %MACRO Source, Size=, Align=Left
%LodHDflags %SETA %cpuextAlignL & "%Align[1]" == "L"
PUSHW %LodHDflags
%IF "%Size" === ""
%IF "%Source" === "" || "%Source" == "SI"
PUSHW 32K
%ELSE
PUSHW SIZE# (%Source)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Source" === ""
PUSH SI
%ELSE
PUSHW %Source
%ENDIF
CALL LodHD16@RT::
LodHD16@RT:: PROC1 ; %1=Source, %2=Size, %3=flags.
PUSHAW
MOV BP,SP
MOV SI,[%Par1] ; Source.
MOV CX,[%Par2] ; Size.
SUB AX,AX
SUB DX,DX
SUB BX,BX ; DX:BX will accumulate the result value.
CLD
JCXZ .20:
TESTW [%Par3],%cpuextAlignL
JNZ .30:
.10: LODSB ; White spaces are tolerated.
CMP AL,' '
JA .40:
LOOP .10:
.20: STC ; Error.
JMP .95:
.30: LODSB ; Signum or digit expected.
.40: CMP AL,'+'
JE .70:
CMP AL,'-'
JNE .55:
ORW [%Par3],%cpuextMinus
JMP .70:
.50: LODSB ; Hexadecimal digit or underscore expected.
.55: CMP AL,'_'
JNE .60:
LOOP .50:
JMP .85:
.60: SUB AL,'0'
JB .80:
CMP AL,9
JNA .65:
SUB AL,'A'-'0'
JB .80:
CMP AL,5
JNA .64:
SUB AL,'a'-'A'
JB .80:
CMP AL,5
JA .80:
.64: ADD AL,10
.65: ; AX is now a valid nibble 0x0000..0x000F. Make room for it in DX:BX.
bit %FOR 15..12 ; SHLD would be better but this is 8086 library.
SHL BX
RCL DX
JC .20: ; Abort on overflow.
%ENDFOR bit
ADD BX,AX
ORW [%Par3],%cpuextLeading0 ; At least one digit was found.
.70: LOOP .50:
JMP .85:
.80: DEC SI
.85: TESTW [%Par3],%cpuextLeading0
JZ .20: ; Abort if no digit parsed.
TESTW [%Par3],%cpuextMinus
JZ .90:
NOT BX ; Negate the result DX:BX.
NOT DX
ADD BX,1
ADC DX,0
.90: CLC
MOV [%ReturnAX],BX
MOV [%ReturnDX],DX
MOV [%ReturnSI],SI
.95:POPAW
RET 3*2
ENDP1 LodHD16@RT::
%ENDMACRO LodHD
SIZE# %Destination
. Size is not limited if it cannot be determined from %Destination.
Size will never exceed 6 characters.
StoD %MACRO Destination, Size=, Signed=Yes, Align=Left, LeadingZeroes=No
%StoDflags %SETA %cpuextSigned & "%Signed[1]" == "Y"
%StoDflags %SETA %StoDflags | %cpuextAlignL & "%Align[1]" == "L"
%StoDflags %SETA %StoDflags | %cpuextLeading0 & "%LeadingZeroes[1]" !== "N"
%IF "%Align[1]" !== "L" && "%Size" === "" && ("%Destination" === "" || "%Destination" == "DI")
%ERROR ID=5913, "StoD cannot Align=Right when Size= is not specified."
%StoDflags %SETA %StoDflags | %cpuextAlignL
%ENDIF
PUSHW %StoDflags
%IF "%Size" === ""
%IF "%Destination" === "" || "%Destination" == "DI"
PUSHW -1
%ELSE
PUSHW SIZE# (%Destination)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Destination" === ""
PUSH DI
%ELSE
PUSHW %Destination
%ENDIF
CALL StoD16@RT::
StoD16@RT:: PROC1
PUSHAW
MOV BP,SP
PUSH ES
SUB SP,2+6 ; Word with string size + 6 bytes of temporary string.
CLD
MOV DX,AX ; Input value.
MOV DI,SP ; Temporary destination field, 6 bytes.
PUSH SS
POP ES
PUSHW 10,100,1000,10000
MOV SI,SP
MOV CX,4 ; Number of pushed constants.
TESTW [%Par3],%cpuextSigned
JZ .10:
TEST DX
JNS .10:
MOV AL,'-'
NEG DX
ORW [%Par3],%cpuextMinus
STOSB
.10: LODSW [SS:SI] ; 10^4, 10^3, 10^2, 10^1.
CMP DX,AX
JNB .20
LOOP .10:
JMP .40:
.20: XCHG BX,AX
SUB AX,AX
XCHG AX,DX
DIV BX
ADD AL,'0'
STOSB
LODSW [SS:SI]
LOOP .20:
SUB SI,2
.40: MOV AX,DX
ADD AL,'0'
STOSB ; The last digit.
SUB DI,SI ; Number of significant digits.
MOV [BP-4],DI ; Store the string size.
MOV CX,[%Par2] ; Allocated string Size.
SUB CX,DI ; Number of padding characters when Align=right.
MOV DI,[%Par1] ; Destination.
MOV ES,[BP-2] ; Pushed Destination segment.
JB .95: ; If overflowed.
TESTW [%Par3],%cpuextAlignL
JNZ .80:
CMPW [%Par2],-1
JE .80: ; If unspecified Size=.
JCXZ .80:
MOV AL,' '
TESTW [%Par3],%cpuextLeading0
JZ .70:
TESTW [%Par3],%cpuextMinus
JZ .60:
DECW [BP-4]
MOVSB [ES:DI],[SS:SI] ; Copy Minus sign.
.60: MOV AL,'0'
.70: REP STOSB ; Leading spaces or zeroes.
.80: MOV CX,[BP-4] ; Size of string with significant digits.
REP MOVSB [ES:DI],[SS:SI] ; Significant digits.
CLC
MOV [%ReturnDI],DI
.95: MOV SP,BP
POPAW
RET 3*2
ENDP1 StoD16@RT::
%ENDMACRO StoD
SIZE# %Destination
. Size is not limited if it cannot be determined from %Destination.
Size will never exceed 11 characters.
StoDD %MACRO Destination, Size=, Signed=Yes, Align=Left, LeadingZeroes=No
%StoDDflags %SETA %cpuextSigned & "%Signed[1]" == "Y"
%StoDDflags %SETA %StoDDflags | %cpuextAlignL & "%Align[1]" == "L"
%StoDDflags %SETA %StoDDflags | %cpuextLeading0 & "%LeadingZeroes[1]" !== "N"
%IF "%Align[1]"!=="L" && "%Size" === "" && ("%Destination" === "" || "%Destination" == "DI")
%ERROR ID=5913, "StoDD cannot Align=Right when Size= is not specified."
%StoDDflags %SETA %StoDDflags | %cpuextAlignL
%ENDIF
PUSHW %StoDDflags
%IF "%Size" === ""
%IF "%Destination" === "" || "%Destination" == "DI"
PUSHW -1
%ELSE
PUSHW SIZE# (%Destination)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Destination" === ""
PUSH DI
%ELSE
PUSHW %Destination
%ENDIF
CALL StoDD16@RT::
StoDD16@RT:: PROC1 ; %1=Destination, %2=Size, %3=flags.
PUSHAW
MOV BP,SP
%StoDD_Lo %SET BP-2 ; Binary absolute value, low word.
%StoDD_Hi %SET BP-4 ; Binary absolute value, high word.
%StoDDstr %SET BP-16 ; 12 bytes of temporary room for decimal string.
SUB SP,16 ; Allocate local variables.
JNSt [%Par3],%cpuextSigned,.10:
TEST DX
JNS .10:
SetSt [%Par3],%cpuextMinus ; Result will be prefixed with -.
NOT AX
NOT DX
ADD AX,1
ADC DX,0
.10:MOV [%StoDD_Lo],AX
MOV [%StoDD_Hi],DX
PUSH ES,SS
POP ES
STD ; Prepare to store decimal digits to %StoDDstr backward.
LEA DI,[%StoDDstr+12-1]
MOV CX,10 ; Divisor.
.20: MOV AX,[%StoDD_Hi]
SUB DX,DX
DIV CX
MOV [%StoDD_Hi],AX
MOV AX,[%StoDD_Lo]
DIV CX
MOV [%StoDD_Lo],AX
XCHG AX,DX ; Put the remainder to AL.
ADD AL,'0'
STOSB
TEST DX
JNZ .20: ; Repeat until quotient is zero.
POP ES
CLD
LEA CX,[%StoDDstr+12-1]
SUB CX,DI ; CX is now the number of significant digits in string.
LEA SI,[DI+1] ; SI is offset of the 1st decimal digit.
MOV DI,[%Par1] ; ES:DI is Destination.
JSt [%Par3],%cpuextAlignL, .40:
MOV DX,[%Par2] ; Size of Destination.
SUB DX,CX
JC .90: ; Abort if overflow.
JNSt [%Par3],%cpuextMinus, .30:
DEC DX
STC
JS .90: ; Abort if overflow.
.30:JSt [%Par3],%cpuextLeading0,.50:
MOV AL,' '
XCHG CX,DX
REP STOSB ; Pad with spaces.
XCHG DX,CX
.40:JNSt [%Par3],%cpuextMinus, .80:
MOV AL,'-'
STOSB
JMP .80:
.50:JNSt [%Par3],%cpuextMinus, .60:
MOV AL,'-'
STOSB
.60:MOV AL,'0'
XCHG CX,DX
REP STOSB ; Pad with unsignificant zeroes.
XCHG DX,CX
.80:REP SEGSS MOVSB ; Copy significant digits to Destination.
MOV [%ReturnDI],DI
CLC
.90:MOV SP,BP
POPAW
RET 3*2
ENDP1 StoDD16@RT::
%ENDMACRO StoDD
SIZE# %Destination.
Size is not limited if it cannot be determined from %Destination
but it will not exceed 4 characters in this case.
ABCDEF and abcdef digits.
StoH %MACRO Destination, Size=, Align=Right, Case=Upper, LeadingZeroes=Yes
%StoHflags %SETA %cpuextLowCase & "%Case[1]" !== "U"
%StoHflags %SETA %StoHflags | %cpuextAlignL & "%Align[1]" !== "R"
%StoHflags %SETA %StoHflags | %cpuextLeading0 & "%LeadingZeroes[1]" == "Y"
%IF "%Align[1]" == "R" && "%Size" === "" && ("%Destination" === "" || "%Destination" == "DI")
%ERROR ID=5915, "StoH cannot Align=Right when Size= is not specified."
%StoHflags %SETA %StoHflags | %cpuextAlignL
%ENDIF
PUSHW %StoHflags
%IF "%Size" === ""
%IF "%Destination" === "" || "%Destination" == "DI"
PUSHW -1
%ELSE
PUSHW SIZE# (%Destination)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Destination" === ""
PUSH DI
%ELSE
PUSHW %Destination
%ENDIF
CALL StoH16@RT::
StoH16@RT:: PROC1 ; %1=Destination, %2=Size, %3=flags.
PUSHAW
MOV BP,SP
%StoHstr %SET BP-4
SUB SP,4 ; Room for a temporary hexadecimal string.
MOV DI,SP
MOV DX,AX ; Copy input value.
MOV BX,0x2000
TESTW [%Par3],%cpuextLeading0
JZ .35:
MOV BH,'0'
.10:TEST DX
JNS .20:
MOV BH,'F'
.20:TESTW [%Par3],%cpuextLowCase
JZ .35:
OR BL,'x'^'X' ; Convert 'A'..'Z' to 'a'..'z' when BL=0x20.
.30:OR BH,BL ; BH is now unsignificant digit '0' or 'F' or 'f'.
.35:MOV CX,0x0404 ; CL is nibble width, CH is nibble count.
.40:ROL DX,CL
MOV AX,0x000F
AND AX,DX
ADD AL,0x90 ; Convert the nibble in AL to a hexadigit ('0'..'F').
DAA
ADC AL,0x40
DAA
OR AL,BL ; Adjust character case.
MOV [SS:DI],AL
INC DI
DEC CH
JNZ .40:
; Value from DX is now stored as 4 hexa digits in %StoHstr buffer.
; CX=4. Calculate the number of significant digits (1..4) into CX.
TEST DX
JNS .50:
NOT DX
.50:TEST DX,0xF800
JNZ .60:
DEC CX
TEST DX,0xFF80
JNZ .60:
DEC CX
TEST DX,0xFFF8
JNZ .60:
DEC CX
.60:MOV AX,[%Par2] ; Size of destination buffer.
SUB AX,CX
JB .90: ; Destination is not long enough.
MOV DI,[%Par1] ; Offset of Destination in segment ES.
MOV SI,SP ; Offset of %StoHstr.
ADD SI,4
SUB SI,CX
TESTW [%Par3],%cpuextAlignL
JZ .80:
.70:REP:SEGSS:MOVSB
JMP .85:
.80:; Right-aligned destination - store AX unsignificant characters first.
MOV DX,CX
XCHG AX,CX
MOV AL,BH
REP STOSB ; Unsignificant digits.
XCHG CX,DX
REP:SEGSS:MOVSB ; Significant digits.
.85:MOV [%ReturnDI],DI
.90:MOV SP,BP
POPAW
RET 3*2
ENDP1 StoH16@RT::
%ENDMACRO StoH
SIZE# %Destination.
Size is not limited if it cannot be determined from %Destination
but it will not exceed 8 characters in this case.
ABCDEF and abcdef digits.
StoHD %MACRO Destination, Size=, Align=Right, Case=Upper, LeadingZeroes=Yes
%StoHDflags %SETA %cpuextLowCase & "%Case[1]"!=="U"
%StoHDflags %SETA %StoHDflags | %cpuextAlignL & "%Align[1]"!=="R"
%StoHDflags %SETA %StoHDflags | %cpuextLeading0 & "%LeadingZeroes[1]"!=="N"
%IF "%Align[1]" == "R" && "%Size" === "" && ("%Destination" === "" || "%Destination" == "DI")
%ERROR ID=5915, "StoHD cannot Align=Right when Size= is not specified."
%StoHDflags %SETA %StoHDflags | %cpuextAlignL
%ENDIF
PUSHW %StoHDflags
%IF "%Size" === ""
%IF "%Destination" === "" || "%Destination == "DI"
PUSHW -1
%ELSE
PUSHW SIZE# (%Destination)
%ENDIF
%ELSE
PUSHW %Size
%ENDIF
%IF "%Destination" === ""
PUSH DI
%ELSE
PUSHW %Destination
%ENDIF
CALL StoHD16@RT::
StoHD16@RT:: PROC1 ; %1=Destination, %2=Size, %3=flags.
PUSHAW
MOV BP,SP
%StoHDstr %SET BP-8
SUB SP,8 ; Room for a temporary hexadecimal string.
MOV DI,SP
MOV BX,0x2000
TESTW [%Par3],%cpuextLeading0
JZ .35:
MOV BH,'0'
.10:TEST DX
JNS .20:
MOV BH,'F'
.20:TESTW [%Par3],%cpuextLowCase
JZ .35:
OR BL,'x'^'X' ; Convert 'A'..'Z' to 'a'..'z' when BL=0x20.
.30:OR BH,BL ; BH is now unsignificant digit '0' or 'F' or 'f'.
.35:MOV CX,0x0404 ; CL is nibble width, CH is nibble count.
.40:ROL DX,CL
MOV AX,0x000F
AND AX,DX
ADD AL,0x90 ; Convert the nibble in AL to a hexadigit ('0'..'F').
DAA
ADC AL,0x40
DAA
OR AL,BL ; Adjust character case.
MOV [SS:DI],AL
INC DI
DEC CH
JNZ .40:
MOV CH,4
MOV DX,[%ReturnAX]
.47:ROL DX,CL
MOV AX,0x000F
AND AX,DX
ADD AL,0x90 ; Convert the nibble in AL to a hexadigit ('0'..'F').
DAA
ADC AL,0x40
DAA
OR AL,BL ; Adjust character case.
MOV [SS:DI],AL
INC DI
DEC CH
JNZ .47:
; Value from DX:AX is now stored as 8 hexa digits in %StoHDstr buffer.
MOV CL,8 ; Calculate the number of significant digits (1..8) into CX.
MOV DX,[%ReturnDX]
TEST DX
JNS .50:
NOT DX
.50:TEST DX,0xF800
JNZ .60:
DEC CX
TEST DX,0xFF80
JNZ .60:
DEC CX
TEST DX,0xFFF8
JNZ .60:
DEC CX
TEST DX
JNZ .60:
DEC CX
.55:TEST DX
MOV DX,[%ReturnAX]
JNS .57:
NOT DX
.57:TEST DX
JS .60:
TEST DX,0xF800
JNZ .60:
DEC CX
TEST DX,0xFF80
JNZ .60:
DEC CX
TEST DX,0xFFF8
JNZ .60:
DEC CX
.60:MOV AX,[%Par2] ; Size of destination buffer.
SUB AX,CX ; Subtract the number of significant digits.
JB .90: ; Destination is not long enough.
MOV DI,[%Par1] ; Offset of Destination in segment ES.
MOV SI,SP ; Offset of %StoHDstr.
ADD SI,8
SUB SI,CX
TESTW [%Par3],%cpuextAlignL
JZ .80:
.70:REP:SEGSS:MOVSB
JMP .85:
.80:; Right-aligned destination - store AX unsignificant characters first.
MOV DX,CX
XCHG AX,CX
MOV AL,BH
REP STOSB ; Unsignificant digits.
XCHG CX,DX
REP:SEGSS:MOVSB ; Significant digits.
.85:MOV [%ReturnDI],DI
.90:MOV SP,BP
POPAW
RET 3*2
ENDP1 StoHD16@RT::
%ENDMACRO StoHD
ENDHEAD cpuext16