Btw, if you want to optimize for shorter-encodings, couldn't you do
asm
cmp: asm EAX with: 16r80;
jl: oneByte;
cmp: asm EAX with: 16r800;
jl: twoBytes;
cmp: asm EAX with:16r1000;
jl: threeBytes;
label: fourBytes;
...
jmp end;
label: threeBytes;
...
jmp end;
label: twoBytes;
...
jmp: end;
label: oneByte;
label: end
ie only one cmp/jmp for 1-byte chars (1 less jump than current),
and n cmp/2 jmp's for n > 1.
Or do the conditional jumps relying on last instruction stall enough
that it doesn't really matter?
Cheers,
Henry
On 13.06.2012 04:44, Igor Stasenko wrote:
Hi, hardcore hackers.
please take a look at the code and tell if it can be improved.
The AsmJit snippet below transforms an unicode integer value
to 1..4-byte sequence of utf-8
then the outer piece of code (which is not yet written) will
accumulate the results of this snippet
to do a memory-aligned (4byte) writes..
like that, if 4 unicode characters can be encoded into 4 utf-8 bytes
(which mostly the case for latin-1 char range), then there will be
4 memory reads (to read four 32-bit unicode values) but only single
memory write (to write four 8-bit utf-8 encoded values).
The idea is to make utf-8 encoding speed close to memory copying speed :)
convertUnicode: asm
"
input:
- EAX 32-bit unicode value to convert
output:
- EAX - utf-8 encoded character (in little-endian byte order) max 4 bytes
- EDX - number of encoded bytes
"
| moreThanOne moreThanTwo moreThanThree end |
moreThanOne := asm uniqueLabelName: 'moreThanOne'.
moreThanTwo := asm uniqueLabelName: 'moreThanTwo'.
moreThanThree := asm uniqueLabelName: 'moreThanThree'.
end := asm uniqueLabelName: 'end'.
asm
cmp: asm EAX with: 16r7F;
jg: moreThanOne;
"one byte"
mov: 1 to: asm EDX;
jmp: end;
label: moreThanOne;
cmp: asm EAX with: 16r7FF;
jg: moreThanTwo;
"two bytes 80 .. 7FF"
" AH AL "
"00000aaa aabbbbbb"
"110aaaaa 10bbbbbb
AL AH (little endian order)
"
shr: asm EAX with: 2;
shl: asm AL with: 2;
or: asm AX with: 2r1100000010000000;
xchg: asm AL with: asm AH;
mov: 2 to: asm EDX;
jmp: end;
label: moreThanTwo;
cmp: asm EAX with: 16rFFFF;
jg: moreThanThree;
"three bytes 800 ... FFFF"
" AH AL "
"aaaabbbb bbcccccc"
" => 1110aaaa 10bbbbbb 10cccccc"
shl: asm EAX with: 4;
shr: asm AX with: 2;
shr: asm AL with: 2;
" EAX = ...aaaa xxbbbbbb xxcccccc "
or: asm EAX with: 2r111000001000000010000000; "16rE08080"
shl: asm EAX with: 8;
bswap: asm EAX;
mov: 3 to: asm EDX;
jmp: end;
"four bytes 1000 ... 10FFFF"
" AH AL "
"000aaabb bbbbcccc ccdddddd"
"=> 11110aaa 10bbbbbb 10cccccc 10dddddd"
mov: asm EAX to: asm EDX;
shl: asm EAX with: 4;
shr: asm AX with: 2;
shr: asm AL with: 2;
" EAX = 0000000a aabbbbbb xxcccccc xxdddddd "
and: asm EAX with: 16r3F3F3F;
bswap: asm EAX;
shr: asm EDX with: 18; "6*3"
or: asm DL with: 16r11110000;
mov: asm DL to: asm AL;
mov: 4 to: asm EDX;
label: end