This file can be included to 64bit programs written in Euro Assembler.
The library contains OS-independent macroinstructions
with calling convention similar to the standard Intel 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, Compare, CopyTo provide some string operations,
Lod* converts numbers from human-readable notation to a binary number,
Sto* does the opposite,
Strip* trims the string from garbage characters which may surround it.
Similar macros with identical names for different program width are defined in cpuext16.htm and cpuext32.htm.
See also cpuext.htm for width-indepentent macros.
cpuext64 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
Align2Qword %MACRO Variable ADDQ %Variable, 7 ANDQ %Variable, ~7 %ENDMACRO Align2Qword
SIZE# Operand
.
Clear %MACRO Operand, Size=, Filler=0 PUSHQ %Operand %IF "%Size" !=== "" PUSHQ %Size %ELSE PUSHQ SIZE#(%Operand) %ENDIF PUSHQ %Filler CALL Clear64@RT:: Clear64@RT:: PROC1 PUSH RAX,RCX,RDX,RDI MOV RDX,[RSP+40] ; %Filler. MOV ECX,8 .00: SHRD RAX,RDX,8 DEC ECX JNZ .00: ; Broadcast DL to all bytes or RAX. MOV RCX,[RSP+48] ; %Size. MOV RDI,[RSP+56] ; %Operand. SHR ECX,1 JNC .10 STOSB .10: SHR ECX,1 JNC .20 STOSW .20: SHR ECX,1 JNC .30: STOSD .30: JRCXZ .90 REP:STOSQ .90:POP RDI,RDX,RCX,RAX RET 3*8 ENDP1 Clear64@RT:: %ENDMACRO Clear
Compare %MACRO Data1Ptr,Data1Size,Data2Ptr,Data2Size %IF %# < 3 ; > %ERROR ID=5911, "Macro Compare requires 3 or 4 parameters." %EXITMACRO Compare %ENDIF %IF %# > 3 PUSHQ %Data2Size,%Data2Ptr,%Data1Size,%Data1Ptr %ELSE PUSHQ %Data1Size,%Data2Ptr,%Data1Size,%Data1Ptr %ENDIF CALL Compare64@RT:: Compare64@RT:: PROC1 PUSH RCX,RSI,RDI MOV RSI,[RSP+32] ; %Data1Ptr MOV RCX,[RSP+40] ; %Data1Size MOV RDI,[RSP+48] ; %Data2Ptr CMP RCX,[RSP+56] ; %Data2Size JNE .90: REPE:CMPSB .90:POP RDI,RSI,RCX RET 4*8 ENDP1 Compare64@RT:: %ENDMACRO Compare
CopyTo %MACRO Destination, Source, Size= %IF "%Size" !=== "" PUSHQ %Size %ELSE %IF TYPE# %Destination = 'R' %ERROR ID=5912, "CopyTo data size not specified." %EXITMACRO CopyTo %ELSE PUSHQ SIZE# (%Destination) %ENDIF %ENDIF PUSHQ %Source, %Destination CALL CopyTo64@RT:: CopyTo64@RT:: PROC1 PUSH RCX,RSI,RDI MOV RCX,[RSP+48] ; %Size MOV RSI,[RSP+40] ; %Source MOV RDI,[RSP+32] ; %Destination SHR ECX,1 JNC .10: MOVSB .10: SHR ECX,1 JNC .20: MOVSW .20: SHR ECX,1 JNC .30: MOVSD .30: JRCXZ .90 REP:MOVSD .90:POP RDI,RSI,RCX RET 3*8 ENDPROC1 CopyTo64@RT:: %ENDMACRO CopyTo
LodD %MACRO Source, Size= %IF "%Size" === "" %IF "%Source" === "" || "%Source" == "RSI" PUSHQ -1 %ELSE PUSHQ SIZE# (%Source) %ENDIF %ELSE PUSHQ %Size %ENDIF %IF "%Source" === "" PUSH RSI %ELSE PUSHQ %Source %ENDIF CALL LodD64@RT:: LodD64@RT:: PROC1 PUSH RCX,RDX,RBX,RDI MOV RDX,[RSP+48] ; Size. MOV RSI,[RSP+40] ; Source. MOV RCX,RDX ADD RDX,RSI ; Parse end limit. INC RCX JNZ .00: MOV RDX,-1 .00: SUB EAX,EAX SUB ECX,ECX ; Signum. SUB EBX,EBX ; Output value accumulator. MOV EDI,10 .10: CMP RSI,RDX JNB .Error: LODSB CMP AL,' ' JBE .10: ; Skip leading white spaces. ; Sign or digit expected. CMP AL,'+' JE .20: CMP AL,'-' JNE .30: DEC RCX ; RCX is Minus flag. .20: ; At least one digit expected behind the signum, otherwise error. CMP RSI,RDX JNB .Error: LODSB .30: SUB AL,'0' JB .Error: CMP AL,9 JA .Error: MOV EBX,EAX ; Most significant digit loaded. .40: ; Other digits or underscores are expected, otherwise the parsing stops. CMP RSI,RDX JNB .EndOfNumber: LODSB CMP AL,'_' JE .40: SUB AL,'0' JB .EndOfNumber1: CMP AL,9 JA .EndOfNumber1: XCHG RAX,RBX PUSH RDX MUL RDI POP RDX JC .Error: ADD RBX,RAX JC .Error: SUB EAX,EAX JMP .40: .Error:DEC RSI STC JMP .95: .EndOfNumber1:DEC RSI .EndOfNumber: TEST ECX ; Minus? JZ .90: NEG RBX .90: CLC MOV RAX,RBX .95:POP RDI,RBX,RDX,RCX RET 2*8 ENDPROC1 LodD64@RT:: %ENDMACRO LodD
0x
is not supported (LodH would return RAX=0 and RSI behind the 0x
.
SIZE# %Source
is assumed.
Size is not limited if it cannot be determined from %Source.
LodH %MACRO Source, Size=, Align=left %LodHflags %SETA %cpuextAlignL & "%Align[1]" == "L" PUSHQ %LodHflags %IF "%Size" === "" %IF "%Source" === "" || "%Source" == "RSI" PUSHQ -1 %ELSE PUSHQ SIZE# (%Source) %ENDIF %ELSE PUSHQ %Size %ENDIF %IF "%Source" === "" PUSH RSI %ELSE PUSHQ %Source %ENDIF CALL LodH64@RT:: LodH64@RT:: PROC1 PUSH RCX,RDX,RBX MOV RDX,[RSP+48] ; %LodHflags. MOV RCX,[RSP+40] ; %LodHSize. MOV RSI,[RSP+32] ; %LodHSource. SUB EAX,EAX SUB EBX,EBX ; RBX will accumulate the binary value. JRCXZ .20: TEST DL,%cpuextAlignL JNZ .30: .10: LODSB ; White spaces are tolerated when Align=right. CMP AL,' ' JA .40: DEC ECX JNZ .10: .20: STC ; Error. JMP .95: .30: LODSB ; Signum or digit expected. .40: CMP AL,'+' JE .70: CMP AL,'-' JNE .60: OR DL, %cpuextMinus JMP .70: .50: LODSB ; Digit expected. .60: CMP AL,'_' JE .70: SUB AL,'0' JB .80: CMP AL,9 JNA .65: SUB AL,'A'-'0'-10 JB .80: CMP AL,15 JNA .65 SUB AL,'a'-'A' JB .80: CMP AL,15 JA .80: .65: SAL RBX,4 ADD RBX,RAX OR DL, %cpuextLeading0 ; At least one digit was found. .70: DEC ECX JNZ .50: .80: TEST DL, %cpuextLeading0 JZ .20: ; Error if no digit was parsed. TEST DL, %cpuextMinus JZ .90: NEG RBX .90: CLC MOV RAX,RBX .95:POP RBX,RDX,RCX RET 3*8 ENDP1 LodH64@RT:: %ENDMACRO LodH
SIZE# %Destination
. Size is not limited if it cannot be determined from %Destination.
Size will never exceed 20 characters. The output string is ANSI (1byte per digit).
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" == "RDI") %ERROR ID=5913, "StoD cannot Align=Right when Size= is not specified." %StoDflags %SETA %StoDflags | %cpuextAlignL %ENDIF PUSHQ %StoDflags %IF "%Size" === "" %IF "%Destination" === "" || "%Destination" == "RDI" PUSHQ -1 %ELSE PUSHQ SIZE# (%Destination) %ENDIF %ELSE PUSHQ %Size %ENDIF %IF "%Destination" === "" PUSH RDI %ELSE PUSHQ %Destination %ENDIF CALL StoD64@RT:: StoD64@RT:: PROC1 PUSH RAX,RCX,RDX,RBX,RBP,RSI SUB RSP,20+4 ; Room for temporary destination. MOV RDI,RSP MOV RCX,[RSP+96] ; %StoDflags. MOV RBX,RAX ; The input integer number is now in RBX. TEST CL,%cpuextSigned JZ .10: TEST RBX JNS .10: NEG RBX ; Convert RBX to positive number. OR CL,%cpuextMinus ; Result will be prefixed with '-'. .10: divsr %FOR 10000000000000000000, \ 1019. 1000000000000000000, \ 1018. 100000000000000000, \ 1017. 10000000000000000, \ 1016. 1000000000000000, \ 1015. 100000000000000, \ 1014. 10000000000000, \ 1013. 1000000000000, \ 1012. 100000000000, \ 1011. 10000000000, \ 1010. 1000000000, \ 109. 100000000, \ 108. 10000000, \ 107. 1000000, \ 106. 100000, \ 105. 10000, \ 104. 1000, \ 103. 100, \ 102. 10 ; 101. MOV RBP,%divsr CALL .Divide: .Divide:PROC1 ; Divide divident RBX by divisor RBP. SUB EDX,EDX XCHG RBX,RAX ; Zero extend divident RBX to RDX:RAX. DIV RBP ; RAX is now 0..9. ADD AL,'0' ; Convert to decimal digit. STOSB ; Store to temporary destination. XCHG RDX,RBX ; Copy remainder to RBX. RET ENDP1 .Divide: %ENDFOR divsr ; Repeat with smaller divisor. MOV AL,BL ; The last remainder. ADD AL,'0' ; Convert to decimal digit. STOSB ; String of 20 digits at RSP now contains the temporary result. MOV RSI,RSP ; Pointer to temporary result with leading decimal zeros. LEA RBX,[RSP+20-1] ; Pointer to the last digit in temporary result. .20: CMP RSI,RBX JNB .30: ; If no more zeros to skip. LODSB CMP AL,'0' JE .20: ; Skip leading unsignificant zeros. DEC RSI .30: INC RBX SUB RBX,RSI ; Unsigned result without leading zeros is now in RSI,RBX. MOV RDX,[RSP+88] ; %StoDSize. MOV RDI,[RSP+80] ; %StoDDestination. TEST RDX STC JZ .Overflow: TEST CL,%cpuextMinus JZ .40: DEC RDX .40: SUB RDX,RBX ; RDX is now the number of padding bytes in destination. JC .Overflow: TEST CL,%cpuextAlignL JZ .50: TEST CL,%cpuextMinus JZ .90: MOV AL,'-' STOSB JMP .90: .50: ; Justify the result to the right. TEST CL,%cpuextMinus JZ .70: TEST CL,%cpuextLeading0 MOV ECX,EDX JZ .60: MOV AL,'-' STOSB MOV AL,'0' REP:STOSB JMP .90: .60: MOV AL,' ' REP STOSB MOV AL,'-' STOSB JMP .90: .70: TEST CL,%cpuextLeading0 MOV AL,' ' JZ .80: MOV AL,'0' .80: MOV ECX,EDX REP:STOSB .90: MOV ECX,EBX REP:MOVSB .Overflow: ; CF signalizes error. LEA RSP,[RSP+20+4] POP RSI,RBP,RBX,RDX,RCX,RAX RET 3*8 ENDP1 StoD64@RT:: %ENDMACRO StoD
SIZE# %Destination
.
Size is not limited if it cannot be determined from %Destination
but it will never exceed 16 bytes. The output string is ANSI (1byte per digit).
ABCDEF
and abcdef
digits.
StoH %MACRO Destination, Size=, Case=Upper, Align=Right, 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" == "RDI") %ERROR ID=5915, "StoH cannot Align=Right when Size= is not specified." %StoHflags %SETA %StoHflags | %cpuextAlignL %ENDIF PUSHQ %StoHflags %IF "%Size" === "" %IF "%Destination" === "" || "%Destination" == "RDI" PUSHQ -1 %ELSE PUSHQ SIZE# (%Destination) %ENDIF %ELSE PUSHQ %Size %ENDIF %IF "%Destination" === "" PUSH RDI %ELSE PUSH %Destination %ENDIF CALL StoH64@RT:: StoH64@RT:: PROC1 PUSH RAX,RCX,RDX,RBX,RBP,RSI SUB RSP,16 ; Room for temporary destination. MOV RDI,RSP MOV RDX,[RSP+88] ; %StoHflags. MOV RBX,RAX ; Input value. MOV ECX,16 ; Number of 4bit nibbles in RBX. TEST DL,%cpuextLowCase JZ .10: OR DH,'x'^'X' ; DH is 0x00 or 0x20 for upper or lower case. .10: ROL RBX,4 ; Start with the most significant nibble. MOV AL,0x0F AND AL,BL OR AL,'0' CMP AL,'9' JBE .20: ADD AL,'A'-'0'-10 ; AL='A'..'F'. OR AL,DH ; Convert to lower case if DH=0x20. .20: STOSB DEC RCX JNZ .10: TEST RBX ; 16 bytes of temporary room at RSP is filled with hexadecimal digits. JNS .25: OR DH,'F' ; Prepare DH=unsignificant digit 'F' or 'f'. JMP .30: .25: MOV DH,'0' ; Prepare DH=unsignificant digit '0'. JNZ .30: INC BL ; If input number = 0, one significant digit '0' is stored. JMP .50: .30: BSR RCX,RBX ; Find the most significat bit for both positive and negative value. NOT RBX BSR RBX,RBX CMP BL,CL JB .40: XCHG BL,CL ; Select the minimum. .40: ADD BL,5 SHR BL,2 ; RBX is now the number of significant output nibbles (1..16). .50: LEA RSI,[RSP+16] ; End of temporary room. MOV RCX,[RSP+80] ; %StoHSize. MOV RDI,[RSP+72] ; %StoHDestination. SUB RSI,RBX ; RSI now points to 1st significant digit. TEST DL,%cpuextAlignL JNZ .70: SUB RCX,RBX JC .Overflow: MOV AL,DH TEST DL,%cpuextLeading0 JNZ .60: MOV AL,' ' .60: REP:STOSB ; Store RCX spaces or unsignificant digits. .70: MOV RCX,RBX REP:MOVSB ; Store RBX significant digits. .Overflow: ; CF signalizes error. LEA RSP,[RSP+16] POP RSI,RBP,RBX,RDX,RCX,RAX RET 3*8 ENDP1 StoH64@RT:: %ENDMACRO StoH
StripColons %MACRO PtrReg, SizeReg, Unicode=%^UNICODE %IF TYPE#%PtrReg <> 'R' || TYPE#%SizeReg <> 'R' %ERROR ID=5918, "Both arguments of StripColons must be GPR." %EXITMACRO StripColons %ENDIF %IF %Unicode ; WIDE variant. StripColons1%.: CMP %SizeReg,2 JL StripColons9%.: CMPW [%PtrReg+%SizeReg-2],":" JNE StripColons2%.: SUB %SizeReg,2 JMP StripColons1%.: StripColons2%.: CMPW [%PtrReg],":" JNE StripColons9%.: ADD %PtrReg,2 CMP %SizeReg,2 JL StripColons9%.: SUB %SizeReg,2 JMP StripColons2%.: StripColons9%.: %ELSE ; ANSI variant. TEST %SizeReg JZ StripColons9%.: StripColons1%.: CMPB [%PtrReg+%SizeReg-1],':' JNE StripColons2%.: DEC %SizeReg JNG StripColons9%.: JMP StripColons1%.: StripColons2%.: CMPB [%PtrReg],':' JNE StripColons9%.: INC %PtrReg DEC %SizeReg JMP StripColons2%.: %ENDIF StripColons9%.: %ENDMACRO StripColons
StripQuotes %MACRO PtrReg, SizeReg, Unicode=%^UNICODE %IF TYPE#%PtrReg <> 'R' || TYPE#%SizeReg <> 'R' %ERROR ID=5919, "Both arguments of StripQuotes must be GPR." %EXITMACRO StripQuotes %ENDIF %IF %Unicode ; WIDE variant. CMP %SizeReg,2*2 JB StripQuotes9%.: CMPW [%PtrReg+%SizeReg-2],'"' JNE StripQuotes1%.: SUB %SizeReg,2 StripQuotes1%.: CMPW [%PtrReg],'"' JNE StripQuotes9%.: ADD %PtrReg,2 SUB %SizeReg,2 StripQuotes9%.: %ELSE ; ANSI variant. CMP %SizeReg,2 JB StripQuotes9%.: CMPB [%PtrReg+%SizeReg-1],'"' JNE StripQuotes1%.: DEC %SizeReg StripQuotes1%.: CMPB [%PtrReg],'"' JNE StripQuotes9%.: INC %PtrReg DEC %SizeReg StripQuotes9%.: %ENDIF %ENDMACRO StripQuotes
StripApostrophes %MACRO PtrReg, SizeReg, Unicode=%^UNICODE %IF TYPE#%PtrReg <> 'R' || TYPE#%SizeReg <> 'R' %ERROR ID=5917, "Both arguments of StripApostrophes must be GPR." %EXITMACRO StripApostrophes %ENDIF %IF %Unicode ; WIDE variant. CMP %SizeReg,2*2 JB StripApostrophes9%.: CMPW [%PtrReg+%SizeReg-2],"'" JNE StripApostrophes1%.: SUB %SizeReg,2 StripApostrophes1%.: CMPW [%PtrReg],"'" JNE StripApostrophes9%.: ADD %PtrReg,2 SUB %SizeReg,2 StripApostrophes9%.: %ELSE ; ANSI variant. CMP %SizeReg,2 JB StripApostrophes9%.: CMPB [%PtrReg+%SizeReg-1],"'" JNE StripApostrophes1%.: DEC %SizeReg StripApostrophes1%.: CMPB [%PtrReg],"'" JNE StripApostrophes9%.: INC %PtrReg DEC %SizeReg StripApostrophes9%.: %ENDIF %ENDMACRO StripApostrophes
StripSpaces %MACRO PtrReg, SizeReg, Unicode=%^UNICODE %IF TYPE#%PtrReg <> 'R' || TYPE#%SizeReg <> 'R' %ERROR ID=5920, "Both arguments of StripSpaces must be GPR." %EXITMACRO StripSpaces %ENDIF %IF %Unicode ; WIDE variant. StripSpaces1%.: CMP %SizeReg,2 JL StripSpaces9%.: CMPW [%PtrReg+%SizeReg-2]," " JA StripSpaces2%.: SUB %SizeReg,2 JMP StripSpaces1%.: StripSpaces2%.: CMPW [%PtrReg]," " JA StripSpaces9%.: ADD %PtrReg,2 CMP %SizeReg,2 JL StripSpaces9%.: SUB %SizeReg,2 JMP StripSpaces2%.: StripSpaces9%.: %ELSE ; ANSI variant. TEST %SizeReg JZ StripSpaces9%.: StripSpaces1%.: CMPB [%PtrReg+%SizeReg-1]," " JA StripSpaces2%.: DEC %SizeReg JNG StripSpaces9%.: JMP StripSpaces1%.: StripSpaces2%.: CMPB [%PtrReg]," " JA StripSpaces9%.: INC %PtrReg DEC %SizeReg JMP StripSpaces2%.: StripSpaces9%.: %ENDIF %ENDMACRO StripSpaces
ENDHEAD cpuext64