EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

String64.htm
Macros
Compare$
Concat$
DecodeUTF8
GetLength$

This file can be included to 64bit programs written in Euro Assembler.
It contains OS-independent macros for operations with zero-terminated (ASCIIZ) strings in ANSI or WIDE (Unicode) encoding.
Unicode string must always be word aligned and terminated with the zero UNICHAR (word).

Macros may crash the process when the input string is not properly zero-terminated and the following memory is not available for reading.

All functions expect zeroed direction flag on input and they do not change it.

ANSI or WIDE functionality is selected by the current EUROASM UNICODE= boolean option. Its value is available in system variable %^UNICODE.

Similar macros with identical names for different program width are defined in string16.htm and string32.htm.


 string64 HEAD
↑ GetLength$ String, Unicode=%^UNICODE
This macro returns the size of the string in bytes.
Input
String is pointer to a zero terminated string of ANSI or WIDE characters. It may also be a literal string.
Unicode= is a logical parameter which tells whether the strings are ANSI or WIDE. By default (if not specified) it is the same as the system preprocessing variable %^UNICODE at invocation time.
Output
RCX= size of the string without the terminating NUL in bytes. The result is even for WIDE strings.
Example
SomeText DU "Hi!",0 ; SomeText was defined as WIDE characters, regardless of current UNICODE status. ; SIZE# SomeText is 8, memory contains 4800_6900_2100_0000h EUROASM UNICODE=YES GetLength$ SomeText ; RCX is now 6 (3 nonzero UNICHARS). EUROASM UNICODE=NO GetLength$ SomeText ; RCX is now 1 (1 nonzero BYTE).
GetLength$ %MACRO String, Unicode=%^UNICODE
     PUSHQ %String
     %IF %^Unicode
       CALL GetLength$W@RT::
       GetLength$W@RT:: PROC1
         PUSH  RAX,RDI
           SUB EAX,EAX
           SUB ECX,ECX
           MOV RDI,[RSP+24] ; Pointer to String$.
           DEC RCX
           REPNE SCASW
           NOT RCX
           DEC RCX
           SHL RCX,1
          POP RDI,RAX
          RET 1*8
        ENDPROC1 GetLength$W@RT::
     %ELSE ; Not %Unicode.
        CALL GetLength$A@RT::
        GetLength$A@RT:: PROC1
          PUSH  RAX,RDI
            SUB EAX,EAX
            SUB ECX,ECX
            MOV RDI,[RSP+24] ; Pointer to String$.
            DEC RCX
            REPNE SCASB
            NOT RCX
            DEC RCX
          POP RDI,RAX
          RET 1*8
        ENDPROC1 GetLength$A@RT::
     %ENDIF
    %ENDMACRO GetLength$
 
↑ Concat$ Destination, Size=, Source1, Source2,,, Unicode=%^UNICODE
Macro will concatenate one or more zero-terminated source strings (ANSI or WIDE) to a destination string.
Input
Destination is a pointer to memory where the result of concatenation will be stored as zero-terminated string.
Size= is the size in bytes allocated for the output destination buffer including the zero terminator. By default it is set to SIZE# %Destination.
Source* operands are pointers to the strings which should be concatenated. The first one (Source1) may be identical with the destination, when we need to append something to an existing string.
Unicode= is a logical parameter which tells whether the strings are ANSI or WIDE. By default (if not specified) it is the same as the system preprocessing variable %^UNICODE at invocation time.
Unicode should be FALSE when the concatenated strings are in UTF-8.
Output
CF=0, Destination is filled with concatenation, all registers are preserved.
CF=1 when the Size= is not long enough. The output buffer Size is never exceeded.
Example
Concat$ FullName$,Path$,FileName$,=".htm"
Concat$ %MACRO Destination, Source1,Source2,,, Size=, Unicode=%^UNICODE
   %IF %# < 2                                                                                  ; >>
     %ERROR ID=5930, 'Missing operand of macro "Concat$".'
     %EXITMACRO Concat$
   %ENDIF
   PUSH RBP      ; Variable number of arguments uses a special calling convention.
     MOV RBP,RSP ; Store stack pointer.
     ArgNr %FOR %#..2, STEP= -1
       PUSHQ %*{%ArgNr} ; All Source pointers, starting with the last.
     %ENDFOR ArgNr
     PUSHQ %# - 1 ; Number of pushed Source strings.
     %IF "%Size" === ""
       PUSHQ SIZE# %Destination
     %ELSE
       PUSHQ %Size
     %ENDIF
     PUSHQ %Destination
     %IF %Unicode
       CALL Concat$W@RT::
Concat$W@RT:: PROC1
       PUSH RAX,RCX,RDX,RBP,RSI,RDI
         MOV RDI,[RSP+56]    ; %Destination.
         MOV RDX,[RSP+64]    ; %Size.
         MOV RCX,[RSP+72]    ; Number of Source strings.
         LEA RBP,[RSP+80]    ; Variable pointer to 1st sourcestring.
         LEA RDX,[RDI+RDX-2] ; End of allocated Destination.
         XOR EAX,EAX
    .20: MOV RSI,[RBP]       ; Pointer to %Source.
    .30: LODSW
         TEST EAX            ; Check if it's end of source string.
         JZ .40:
         CMP RDI,RDX         ; Check if it's end of destination string.
         CMC
         JC .80:             ; If destination size overflowed.
         STOSW
         JMP .30:
    .40: ADD EBP,8           ; The next Source pointer on stack frame.
         LOOP .20:
    .80: XOR EAX,EAX         ; Finally zero-terminate the destination.
         STOSW
       POP RDI,RSI,RBP,RDX,RCX,RAX
       RET                   ; CF=overflow
      ENDPROC1 Concat$W@RT::
     %ELSE                   ; If not %Unicode.
       CALL Concat$A@RT::
Concat$A@RT:: PROC1
       PUSH RAX,RCX,RDX,RBP,RSI,RDI
         MOV RDI,[RSP+56]    ; %Destination.
         MOV RDX,[RSP+64]    ; %Size.
         MOV RCX,[RSP+72]    ; Number of Source strings.
         LEA RBP,[RSP+80]    ; Variable pointer to 1st sourcestring.
         LEA RDX,[RDI+RDX-1] ; End of allocated Destination.
         XOR EAX,EAX
    .20: MOV RSI,[RBP]       ; Pointer to %Source.
    .30: LODSB
         TEST EAX            ; Check if it's end of source string.
         JZ .40:
         CMP RDI,RDX         ; Check if it's end of destination string.
         CMC
         JC .80:             ; If destination size overflowed.
         STOSB
         JMP .30:
    .40: ADD EBP,8           ; The next Source pointer on stack frame.
         LOOP .20:
    .80: XOR EAX,EAX         ; Finally zero-terminate the destination.
         STOSB
       POP RDI,RSI,RBP,RDX,RCX,RAX
       RET                   ; CF=overflow
      ENDPROC1 Concat$A@RT::
     %ENDIF
     MOV RSP,RBP             ; Restore the stack.
   POP RBP
  %ENDMACRO Concat$
↑ Compare$ String1, String2, Unicode=%^UNICODE
Compare two zero-terminated ANSI or WIDE strings.
Input
String1 is pointer to the first ANSI or WIDE zero-terminated strings. RSI is assumed when the first operand is omitted.
String2 is pointer to the second ANSI or WIDE zero-terminated strings. RDI is assumed when the second operand is omitted.
Unicode= is a logical parameter which tells whether the strings are ANSI or WIDE. By default (if not specified) it is the same as the system preprocessing variable %^UNICODE at invocation time.
Output
ZF=1 if both string are identical,
ZF=0 otherwise.
Compare$ %MACRO String1, String2, Unicode=%^UNICODE
   %IF "%String2" === ""
      PUSHQ RDI
   %ELSE
      PUSHQ %String2
   %ENDIF
   %IF "%String1" === ""
      PUSHQ RSI
   %ELSE
      PUSHQ %String1
   %ENDIF
   %IF %Unicode
     CALL Compare$W@RT::
Compare$W@RT:: PROC1
       PUSH RAX,RCX,RDX,RBX,RSI,RDI
         SUB EAX,EAX
         SUB ECX,ECX
         MOV RDI,[RSP+64] ; %String2.
         DEC RCX
         MOV RBX,RDI
         REPNE:SCASW      ; Search for the terminator.
         SUB RDI,RBX      ; Size of String2 in bytes including the UNICHAR NUL.
         MOV RDX,RDI
         MOV RDI,[RSP+56] ; %String1.
         MOV RSI,RDI
         REPNE:SCASW      ; Search for the terminator.
         MOV RCX,RDI
         SUB RCX,RSI      ; Size of %String1 in bytes including the UNICHAR NUL.
         CMP RCX,RDX      ; Compare string sizes.
         JNE .90          ; If sizes do not match.
         MOV RDI,RBX      ; String2.
         REPE CMPSB
   .90:POP RDI,RSI,RBX,RDX,RCX,RAX
       RET 2*8
      ENDPROC1 Compare$W@RT::
     %ELSE                ; If not %Unicode.
       CALL Compare$A@RT::
Compare$A@RT:: PROC1
       PUSH RAX,RCX,RDX,RBX,RSI,RDI
         SUB EAX,EAX
         SUB ECX,ECX
         MOV RDI,[RSP+64] ; %String2.
         DEC RCX
         MOV RBX,RDI
         REPNE:SCASB      ; Search for the terminator.
         SUB RDI,RBX      ; Size of String2 in bytes including the UNICHAR NUL.
         MOV RDX,RDI
         MOV RDI,[RSP+56] ; %String1.
         MOV RSI,RDI
         REPNE:SCASB      ; Search for the terminator.
         MOV RCX,RDI
         SUB RCX,RSI      ; Size of %String1 in bytes including the UNICHAR NUL.
         CMP RCX,RDX      ; Compare string sizes.
         JNE .90          ; If sizes do not match.
         MOV RDI,RBX      ; String2.
         REPE CMPSB
   .90:POP RDI,RSI,RBX,RDX,RCX,RAX
       RET 2*8
      ENDPROC1 Compare$A@RT::
     %ENDIF
  %ENDMACRO Compare$
DecodeUTF8 Source, CallbackProc, Size=-1, Width=16

Macro DecodeUTF8 converts Source UTF-8 string to UTF-16 or UTF-32 string.
Source string is either zero-terminated, or its Size= must be specified. Conversion stops at NUL byte, which is not converted to output. Input never reads beyond Source+Size.

If Byte Order Mark (BOM, 0xEF,0xBB,0xBF ) is detected at the beginning of the Source string, it is ignored.

Invalid UTF-8 sequence will send a replacement character 0xFFFD to the output.

Byte order in output encoding is always LittleEndian, the same which is used in MS Windows WIDE functions.

If you want to produce UTF-16BE, perform XCHG AL,AH in CallbackProc.
If you want to produce UTF-32BE, perform BSWAP EAX in CallbackProc.
If you want to prefix the output string with BOM, store it to destination buffer before invoking DecodeUTF8.
If you don't like replacement characters (usually displayed as little squares ), filter them out in CallbackProc.
Documented
[UTF8], [UTF16], [UTF32]
Input
Source is pointer to the first byte of UTF8-encoded string.
Size= -1 is the maximal possible size of source string in bytes. It may be left on default when the Source string is terminated with NUL byte (this NUL is not written to output).
If Size is not -1, exactly that many input bytes are decoded, including NUL bytes.
Width=16 or 32 specifies the output encoding UTF-16 or UTF-32, respectively.
CallbackProc is pointer to the procedure which stores one converted character.
CallbackProc
is called with register calling convention.
It is expected to store the UTF-16 or UTF-32 character obtained in RAX and return with CF=0.
Input
CF=DF=0
RAX= contains one converted character encoded in UTF-16 or UTF-32.
RAX may contain surrogate code 0xD800..0xDFFF when the input UTF-8 character belongs to Unicode supplementary planes (Emoji, Asian characters etc).
RAX may also contain the replacement 0x0000_FFFD when the input UTF-8 string is malformed.
RBP= original value of RBP on input to the macro. Usually it is the frame pointer of the function which expanded DecodeUTF8, thus arguments and local variables of the function can be used in CallbackProc.
RDI= original value of RDI on input to the macro. It may be used in STOS, incremented value of RDI will be supplied on the next invocation of CallbackProc.
Other registers should be considered undefined.
Output
CF=0 when a character from RAX was successfully stored to destination buffer by CallbackProc and macro should continue with parsing the next UTF-8 characters.
CF=1 signalizes that the macro should cancel further conversion. CF propagates to the output of DecodeUTF8.
RAX,RBX,RCX,RDX,RSI,RDI may be changed in Callback procedure. The value of
RDI will be saved and provided in the next call of CallbackProc, thus RDI can be used in CallbackProc as an output pointer for decoded data.
Output
CF=0, RCX=number of unprocessed bytes at the end of text (0..3) due to incompleteness of the last UTF-8 character in input text block. The caller of DecodeUTF8 should seek the input file by RCX bytes back before reading the next block of text.
RDI= as returned from CallbackProc.
All other registers are preserved.
Example
MOV RDI,DestString ; It should be long enough for the decoded string. DecodeUTF8 SourceString, Store: Store:PROC1 ; Thanks to using PROC1 instead of PROC it doesn't need bypass by JMP. STOSW ; Store UTF-16 character from AX and advance RDI to the next free room. RET ; Return to DecodeUTF-8 macro with CF=0. ENDPROC1 Store: SUB EAX,EAX STOSW ; Zero-terminate DestString. Now it can be used in TextOutW, MessageBoxW etc.
DecodeUTF8 %MACRO Source, CallbackProc, Size=-1, Width=16
    %IF %Width != 16 && %Width != 32
      %ERROR ID=5932,'Macro "DecodeUTF8" requires Width=16 or Width=32.'
      %EXITMACRO DecodeUTF8
    %ENDIF
    PUSHQ %Width, %Size, %CallbackProc, %Source
    CALL DecodeUTF8@RT::
DecodeUTF8@RT:: PROC1
    PUSH RAX,RCX,RDX,RBX,RSI,RDI
      SUB ECX,ECX
      MOV [RSP+32],RCX  ; Initialize %ReturnRCX to 0.
      MOV RDI,[RSP+56]  ; %Source.
      MOV RCX,[RSP+72]  ; %Size.
      MOV RSI,RDI
      MOV RAX,RCX
      INC RAX
      JZ .Scan:         ; If Size=-1, RAX=0 and the Source size will be scanned.
      LEA RDI,[RSI+RCX] ; Otherwise use the explicit %Size.
      JMP .No0:
.Scan:REPNE:SCASB
      JNE .No0:
      DEC RDI          ; Omit the terminator from conversion.
.No0: ; Source string without NUL is now at RSI..RDI.
 BOM  %FOR 0xEF,0xBB,0xBF ; Little-Endian BOM (0xFEFF) encoded in UTF-8.
        CMP RSI,RDI
        JNB .NoBOM:
        LODSB
        CMP AL,%BOM
        JNE .NoBOM:
      %ENDFOR BOM
      JMP .Start:       ; BOM was detected, ESI is advanced just behind it.
.NoBOM:MOV RSI,[RSP+56] ; No BOM detected, restore ESI to the start of Source again.
.Start:CMP RSI,RDI
      JNB .End:
      XOR EBX,EBX
      LODSB
      MOV BL,AL
      NOT BL
      BSR RCX,RBX ; Scan bits 7..0 of inverted first byte of 1,2,3,4 bytes long UTF-8 character.
      MOV BL,AL   ; First byte of 1,2,3,4 bytes long UTF-8 character (not inverted).
      MOV DL,0x7F ; Prepare mask for payload bits in the 1st UTF-8 byte.
      SUB RCX,7   ; RCX=7,5,4,3 change to RCX=0,-2,-3,-4.
      JZ .Out:    ; When RBX is codepoint 0..0x7F (7bit ASCII character).
      NEG RCX     ; RCX=2,3,4 (number of bytes in UTF-8 character).
      SHR DL,CL   ; DL=0x1F,0x0F,0x07 is payload mask.
      AND BL,DL   ; EBX will accumulate payload bits of codepoint.
      CMP CL,2
      JB .Bad:
      CMP CL,4
      JBE .Good:
.Bad: MOV EAX,0xFFFD ; Invalid UTF-8 detected, output the replacement.
      JMP .NoSg:
.Good:DEC RCX     ; RCX=1, 2 or 3 continuation bytes expected.
      LEA RAX,[RSI+RCX]
      CMP RAX,RDI ; Check if there's that many input bytes left.
      JBE .Cont:
      DEC RSI     ; Rollback, the last UTF-8 character is incomplete.
      SUB RDI,RSI ; RDI characters (1..3) were not decoded.
      MOV [RSP+32],RDI ; %ReturnRCX.
      JMP .End:   ; CF=0.
.Cont:LODSB       ; Continuation byte AL=10xxxxxxb expected.
      BTR RAX,7   ; Reset the marker bit 7.
      JNC .Bad:
      BTR RAX,6
      JC .Bad:
      SHL RBX,6   ; Make room in RBX for the next 6 bits.
      OR  BL,AL   ; Accumulate them.
      DEC RCX
      JNZ .Cont:
.Out: MOV RAX,RBX ; EAX=EBX is now the decoded codepoint 0..0x10_FFFF.
      ; Check for overlong encodings. DL=0x7F,0x1F,0x0F,0x07 for 1,2,3,4 bytes in UTF-8 character.
      CMP EBX,0x01_0000   ; Codepoint 0x01_0000..0x10_FFFF should be encoded in 4 bytes.
      JAE .NoOverlong:
      CMP EBX,0x00_0800   ; Codepoint 0x00_0800..0x00_FFFF should be encoded in 3 bytes.
      JB .2Bts:
      CMP DL,0x0F
      JE  .NoOverlong:
      JMP .Bad:
.2Bts:CMP EBX,0x00_0080   ; Codepoint 0x00_0080..0x00_07FF should be encoded in 2 bytes.
      JB .1Bts:
      CMP DL,0x1F
      JE .NoOverlong:
      JMP .Bad:
.1Bts:CMP DL,0x7F         ; Codepoint 0x00_0000..0x00_007F should be encoded in 1 byte.
      JE .NoOverlong:
      TEST EBX
      JNZ .Bad:
      CMP DL,0x1F         ; Exception: codepoint 0 may be encoded in 1 or 2 bytes.
      JNE .Bad:
.NoOverlong:
      SHR EBX,11          ; Check for surrogate codepoints.
      CMP BL,0x1B
      JE .Bad:            ; Do not accept surrogates 0xD800..0xDFFF from input.
      TEST BX,0x3E0
      JZ .NoSg:           ; If codepoint EAX is below 0x0001_0000, surrogates do not apply.
      CMPB [RSP+80],16    ; Output UTF %Width (16 or 32).
      JNE .NoSg:          ; UTF-32 does not need surrogates.
      SUB RAX,0x0001_0000 ; Codepoint RAX was not encodable in one UTF-16 character.
      MOV EBX,0x0000_03FF ; Use two surrogate Unichars.
      AND EBX,EAX
      SHR RAX,10
      ADD EBX,0x0000_DC00 ; EBX is now low surrogate.
      ADD EAX,0x0000_D800 ; EAX is now high surrogate.
      CALL .OutEAX:       ; High surrogate first.
      MOV RAX,RBX         ; Low surrogate.
      JC .End:            ; If aborted by CallbackProc.
.NoSg:CALL .OutEAX:       ; Low surrogate or BMP codepoint or UTF-32.
      JNC .Start:         ; Parse the next UTF-8 character from string ESI..EDI.
.OutEAX:PROC1             ; Send EAX to callback. Preserves EBX,ESI,EDI, updates ReturnEDI.
          PUSH RBX,RSI,RDI
            MOV RDI,[RSP+32]  ; ReturnRDI restore.
            CALL [RSP+96]    ; CallbackProc.
            MOV [RSP+32],RDI  ; ReturnRDI update.
          POP RDI,RSI,RBX
          RET
        ENDPROC1 .OutEAX:
.End:POP RDI,RSI,RBX,RDX,RCX,RAX
     RET 4*8
   ENDP1 DecodeUTF8@RT::
 %ENDMACRO DecodeUTF8
  ENDHEAD string64

▲Back to the top▲