flat assembler
Message board for the users of flat assembler.
Index
> Programming Language Design > [FASMG] Writing Intel Instructions |
Author |
|
codestar 21 May 2015, 07:23
Is Register?
Code: ;;;;;;;;;;;;;;;;;;; REGISTERS ;;;;;;;;;;;;;;;;;;;; numeric al, cl, dl, bl, ah, ch, dh, bh numeric ax, cx, dx, bx, sp, bp, si, di numeric eax, ecx, edx, ebx, esp, ebp, esi, edi its_type=0 its_size=0 its_index=0 its_half=0 its_mode=0 macro is_in is, name, p& is=0 irp q, p match =name, q is=1 its_index=%-1 break end match end irp end macro macro is_r is, name local n n=0 is=0 its_size=0 its_half=0 name_length name, n if n=3 is_in is, name, eax, ecx, edx, ebx,\ esp, ebp, esi, edi if is is=4 end if else if n=2 is_in is, name, al, cl, dl, bl if is is=1 its_half='l' else is_in is, name, ah, ch, dh, bh if is is=1 its_half='h' else is_in is, name, ax, cx, dx, bx,\ sp, bp, si, di if is is=2 end if end if end if end if its_size=is end macro Code: ;;;;;;;;;;;;;; OPCODE, TYPE, OPERAND ;;;;;;;;;;;;; d_bit=0 s_bit=0 macro put_code opcode db (opcode or (d_bit shl 1) or s_bit) end macro macro get_type p& local is,\ type, size, index is=0 type=0 size=0 index=0 match [m], p type='m' else match t[m], p type='m' get_size_t size, t else match name, p is_r is, name if is type='r' size=its_size index=its_index else if name eqtype 0 type='i' else err 'Unknown type' end if end match its_type=type its_size=size its_index=index end macro macro get_type_x type, size, index, p& get_type p type=its_type size=its_size index=its_index end macro ;;;;;;;;;;;;;;;;;; OPERAND MODE ;;;;;;;;;;;;;;;;;; ; * 'i' = 0-9, A-F ; $1234ABCD ; * 'r' = eax..edi ; eax ; * 'rm' = [eax..edi] ; [esi] ; * 'im' = [#] ; [$12345678] ; * '+r' = [r+r] ; [eax+ecx] ; * '+i' = [r+i] ; [ecx+$1234] ; * '-i' = [r-i] ; [ebp-16] ; * '*' = [r*s] ; [eax*4] ; * '&+*' = [i+r*s] ; [$ABCD1234+eax*4] ; * '+*' = [r+r*s] ; [edi+ecx*4] ; * '+*+' = [r+r*s+i] ; [edi+ecx*8+$BABE] define the_mode 0 define the_base 0 define the_index 0 define the_scale 0 define the_number 0 macro get_mode_m p local is is=0 match a+b*c+d, p redefine the_mode '+*+' redefine the_base a redefine the_index b redefine the_scale c redefine the_number d else match a+b*c, p redefine the_base a redefine the_index b redefine the_scale c is_r is, a if is redefine the_mode '+*' else redefine the_mode '&+*' end if else match a+b, p redefine the_base a redefine the_index b is_r is, b if is redefine the_mode '+r' else redefine the_mode '+i' end if else match a-b, p redefine the_mode '-i' redefine the_base a redefine the_index b else match a*b, p redefine the_mode '*' redefine the_base a redefine the_scale b else match name, p get_type name is=its_type redefine the_base name if is='r' redefine the_mode 'rm' else if is='i' redefine the_mode 'im' else err '' end if end match end macro macro get_mode p local is is=0 redefine the_mode 0 redefine the_base 0 redefine the_index 0 redefine the_scale 0 redefine the_number 0 match [m], p get_mode_m m its_size=0 else match t[m], p get_mode_m m get_size_t is, t its_size=is else match name, p ; 'r', 'i', 'm' get_type name ; (not [memory]) is=its_type redefine the_mode is redefine the_base name end match end macro macro put_mode a, b, c db ((a shl 6) or (b shl 3) or c) end macro macro write_number n if n>=-$80 & n<$80 db n else dd n end if end macro macro get_scale mode if the_scale=2 mode=01b else if the_scale=4 mode=10b else if the_scale=8 mode=11b else err 'Invalid scale' end if end macro macro write_mode a local n, mode n=0 mode=0 if the_mode='rm' if the_base<>ebp put_mode 00b, a, the_base else put_mode 01b, a, the_base db 0 end if else if the_mode='im' put_mode 00b, a, 101b dd the_base else if the_mode='+r' put_mode 00b, a, 100b put_mode 00b, the_index, the_base else if the_mode='+*' put_mode 00b, a, 100b get_scale mode put_mode mode, the_index, the_base else if the_mode='&+*' ; = r*s+i put_mode 00b, a, 100b get_scale mode put_mode mode, the_index, 101b dd the_base else if the_mode='+*+' n=the_number if n>=-$80 & n<$80 mode=01b else mode=10b end if put_mode mode, a, 100b get_scale mode put_mode mode, the_index, the_base write_number n else if the_mode='+i' | the_mode='-i' n=the_index if the_mode='-i' n=-n end if if n>=-$80 & n<$80 mode=01b else mode=10b end if put_mode mode, a, the_base write_number n else err 'Invalid mode' end if end macro macro display_mode p display '* ', `p, ': ' get_mode p display 'Mode: ', the_mode if its_size display '. Size=', its_size+'0' end if display '. Base=', the_base+'0' if the_index display '. Index=', the_index+'0' end if if the_scale display '. Scale=', the_scale+'0' end if if the_number display '. Number=', the_number+'0' end if display RET end macro macro test_modes display RET display_mode ecx display_mode 8 display_mode [edi] display_mode [8] display_mode [ecx+edx] display_mode [ebp+8] display_mode [ecx-4] display_mode [ebx*4] display_mode [edi*2+8] display_mode [ecx+edx*4] display_mode [edi+ebx*4+8] end macro macro get_operands a, b,\ type1, size1, index1,\ type2, size2, index2 get_type_x type1, size1, index1, a get_type_x type2, size2, index2, b if size1 & size2 & size1<>size2 ; err 'Operands must be same size' end if if type1='m' & size1=0 if type2='i' err 'Size must be specified' end if size1=size2 end if end macro Code: ;;;;;;;;;;;;;;;;; INSTRUCTIONS ;;;;;;;;;;;;;;;;;;; irp <name,value>,\ aaa,$37, aas,$3F, cbw,$98, clc,$F8,\ cld,$FC, cli,$FA, cmc,$F5, cmpsb,$A6,\ cmps,$A7, cwd,$99, daa,$27, das,$2F,\ hlt,$F4, int3,$CC, lodsb,$AC, lods,$DC,\ movsb,$A4, movs,$A5, popf,$9D, pushf,$9C,\ sahf,$9E, scasb,$AE, scas,$AF, stc,$F9,\ std,$FD, sti,$FB, stosb,$AA,\ stos,$AB, xlat,$D7 macro name db value end macro end irp irp <name,value>,\ aso,$67, lock,$F0, oso,$66,\ rep,$F3, repne,$F2, wait,$9B macro name p& db value match next, p next end match end macro end irp macro aam i:10 db $D4, i end macro macro aad i:10 db $D5, i end macro macro nop n match , n db $90 else repeat n db $90 end repeat end match end macro Code: ;;;;;;;;;;;;;;;;;;;;; BRANCH ;;;;;;;;;;;;;;;;;;;;; ; jcc i8 ; 70+cc i8 ; jcc ix ; 0F 80+cc ix irp <name,opcode>,\ jo,$70, jno,$71, jc,$72, jb,$72,\ jnae,$72, jnc,$73, jnb,$73, jae,$73,\ jz,$74, je,$74, jnz,$75, jne,$75,\ jna,$76, jbe,$76, ja,$77, jnbe,$77,\ js,$78, jns,$79, jp,$7A, jpe,$7A,\ jnp,$7B, jpo,$7B, jl,$7C, jnge,$7C,\ jnl,$7D, jge,$7D, jng,$7E, jle,$7E,\ jg,$7F, jnle,$7F macro name i local n n=(i-$) if n<$80 & n>=-$80 db opcode jxx i, 1 else db $0F, (opcode+$10) jxx i, 4 end if end macro end irp Code: ;;;;;;;;;;;;;;;;;;;; PUSH, POP ;;;;;;;;;;;;;;;;;;; ; push rx ; oso 50+r ; push rmx ; oso FF /6 ; push i8 ; 6A ib ; push ix ; oso 68 ix ; pop rx ; oso 58+r ; pop rmx ; oso 8F /0 macro push x local type type=0 get_type x type=its_type if type='r' db $50+x else if type='i' if x<$80 & x>=-$80 db $6A, x else db $68 dd x end if else if type='m' db $FF get_mode x write_mode 6 end if end macro macro push p& irp x, p push x end irp end macro macro pushr p& irp x, p indx (1+%%-%) push x end irp end macro macro pop x local type type=0 get_type x type=its_type if type='r' db $58+x else if type='m' db $8F get_mode x write_mode 0 else err 'Invalid operand' end if end macro macro pop p& irp x, p pop x end irp end macro macro popr p& irp x, p indx (1+%%-%) pop x end irp end macro macro test_push_pop push eax push $77 push $12345678 push [edx] push [esi] push [ebp] push [$12345678] push [edi+8] push [edi+$CAFEBABE] push [ecx+edx] push [esi+ecx*2] push [ecx+edx*4] push [ecx+edx*4+$77] push [ecx+edx*8+$BABE1234] pop ecx pop [edi+8] pop [edi+$CAFEBABE] end macro Code: ;;;;;;;;;;;;;;;;;;;; MOVEMENT ;;;;;;;;;;;;;;;;;;;; ; mov rm8,r8 ; 88 /r ; mov rmx,rx ; oso 89 /r ; mov r8,rm8 ; 8A /r ; mov rx,rmx ; oso 8B /r ; mov r8,i8 ; B0+r ib ; mov rx,ix ; oso B8+r ix ; mov rm8,i8 ; C6 /0 ib ; mov rmx,ix ; oso C7 /0 ix macro mov a, b local opcode, i_size, ext,\ type1, type2, size1, size2,\ index1, index2 d_bit=0 s_bit=0 opcode=0 i_size=0 get_operands a, b,\ type1, size1, index1,\ type2, size2, index2 i_size=size1 if size1=2 | size2=2 oso end if if size1>=2 s_bit=1 end if if type1='r' & type2='r' d_bit=1 opcode=$88 put_code opcode put_mode 11b, a, b else if type1='r' & type2='i' put_code $C7 put_mode 11b, 0, a put_dx b, i_size else if type1='r' & type2='m' d_bit=1 opcode=$8A put_code opcode get_mode b write_mode a else if type1='m' & type2='r' opcode=$88 put_code opcode get_mode a write_mode b else if type1='m' & type2='i' put_code $C6 get_mode a write_mode 0 put_dx b, i_size end if end macro macro test_mov mov eax, ecx mov edx, $12345678 mov ah, cl mov cx, bx mov ecx, [edi] mov edx, [ebp+8] mov ebx, [edi-32] mov esp, [ecx+edx*4] mov edi, [edx+ebx*8+$CAFEBABE] mov ecx, [esi] mov edx, [ebp] mov edi, [$12345678] mov eax, [edi+8] mov ecx, [edi+$CAFEBABE] mov eax, [ecx+edx] mov ecx, [esi+ecx*2] mov edx, [ecx+edx*4] mov ebx, [ecx+edx*4+$77] mov edi, [ecx+edx*8+$BABE1234] mov ax, [edx] mov bx, [$12345678] mov ch, [edi-$AAAAAA] mov al, [ecx+edx*8+$BABE1234] mov [ecx], ah mov [ecx+edx], cx mov [ecx+edx*4], ebx mov byte [eax], $FF mov word [ecx+edx], $FFFF mov dword [ecx+edx*8], $ABCD1234 mov ecx, [$CAFEBABE+edi*8] end macro ;;;;;;;;;;;;;;;;;; MOVZX, MOVSX ;;;;;;;;;;;;;;;;;; ; movzx r32,rm8 ; oso 0F B6 /r ; movzx r32,rm16 ; oso 0F B7 /r ; movsx r32,rm8 ; oso 0F BE /r ; movsx r32,rm16 ; oso 0F BF /r macro movx sign, a, b local opcode, i_size, ext,\ type1, type2, size1, size2,\ index1, index2 d_bit=0 s_bit=0 i_size=0 get_operands a, b,\ type1, size1, index1,\ type2, size2, index2 i_size=size1 if size2=2 s_bit=1 end if db $0F opcode=$B6 if sign=1 opcode=$BE end if if type1='r' & type2='r' d_bit=1 put_code opcode put_mode 11b, a, b else if type1='r' & type2='m' d_bit=1 put_code opcode get_mode b write_mode a else err 'Invalid operands' end if end macro macro movsx a, b movx 1, a, b end macro macro movzx a, b movx 0, a, b end macro macro test_movx movzx esp, word [ecx+edx*4] movzx edi, word [edx+ebx*8+$CAFEBABE] movzx eax, cx movsx ecx, byte [edi] movsx edx, byte [ebp+8] movsx ebx, ah end macro ;;;;;;;;;;;;;;;;;;;;;; LEA ;;;;;;;;;;;;;;;;;;;;;;; ; lea rx,m ; oso 8D /r macro lea r, m db $8D get_mode m write_mode r end macro macro test_lea lea ecx, [edi] lea edx, [ebp+8] lea ebx, [edi-32] lea esp, [ecx+edx*4] lea edi, [edx+ebx*8+$CAFEBABE] end macro Code: ;;;;;;;;; BASIC: ADD, SUB, CMP, XOR, ETC ;;;;;;;;; ; opcode rm8,r8 ; 30 /r ; opcode rmx,rx ; oso 31 /r ; opcode r8,rm8 ; 32 /r ; opcode rx,rmx ; oso 33 /r ; opcode rm8,i8 ; 80 /6 ib ; opcode rmx,ix ; oso 81 /6 ix ; opcode rmx,i8 ; oso 83 /6 ib ; opcode al,i8 ; 34 ib ; opcode eax,ix ; oso 35 ix macro write_basic opcode, a, b local i_size, ext,\ type1, type2, size1, size2,\ index1, index2 d_bit=0 s_bit=0 i_size=0 ext=((opcode shr 3) and 111b) get_operands a, b,\ type1, size1, index1,\ type2, size2, index2 i_size=size1 if size1=2 | size2=2 oso end if if size1>=2 s_bit=1 end if if type1='r' & type2='r' d_bit=1 put_code opcode put_mode 11b, a, b else if type1='r' & type2='i' put_code $80 put_mode 11b, ext, a put_dx b, i_size else if type1='r' & type2='m' d_bit=1 put_code opcode get_mode b write_mode a else if type1='m' & type2='r' put_code opcode get_mode a write_mode b else if type1='m' & type2='i' put_code $80 get_mode a write_mode ext put_dx b, i_size end if end macro irp <name, opcode>,\ adc,$10, add,0, and,$20, cmp,$38,\ or,$8, sbb,$18, sub,$28, xor,$30 macro name a, b write_basic opcode, a, b end macro end irp macro test_basic add eax, ecx adc cl, dl sub dh, bh sbb cx, dx cmp bx, dx and eax, esi or ecx, edx xor esp, edi add ecx, $12345678 sub edx, $ABCD1234 adc ebx, $CAFEBABE sbb cx, $1234 cmp dx, $ABCD and bx, $BABE or ah, $77 xor cl, $77 add ecx, [esi] adc edx, [ebp] sub edi, [$12345678] sbb eax, [edi+8] cmp ecx, [edi+$CAFEBABE] and eax, [ecx+edx] or ecx, [esi+ecx*2] xor edx, [ecx+edx*4] add ebx, [ecx+edx*4+$77] adc edi, [ecx+edx*8+$BABE1234] sub ax, [edx] sbb bx, [$12345678] cmp ch, [edi-$AAAAAA] and al, [ecx+edx*8+$BABE1234] or [ecx], ah xor [ecx+edx], cx add [ecx+edx*4], ebx adc byte [eax], $FF sub word [ecx+edx], $FFFF sbb dword [ecx+edx*8], $ABCD1234 cmp ecx, [$CAFEBABE+edi*8] end macro Code: ;;;;;;;;;;;;;;;;;;;; INC, DEC ;;;;;;;;;;;;;;;;;;;; ; inc rx ; oso 40+r ; inc rm8 ; FE /0 ; inc rmx ; oso FF /0 ; dec rx ; oso 48+r ; dec rm8 ; FE /1 ; dec rmx ; oso FF /1 macro inc_dec name, p local type, opcode, digit type=0 opcode=$40 digit=0 match =dec, name opcode=$48 digit=1 end match get_type p type=its_type if its_size=0 err 'Size must be specified' end if if its_size=2 oso end if s_bit=0 if its_size>=2 s_bit=1 end if if type='r' db opcode+p else if type='m' db $FE or s_bit get_mode p write_mode digit else err 'Invalid operand' end if end macro macro inc p inc_dec inc, p end macro macro dec p inc_dec dec, p end macro macro test_inc_dec inc eax inc dword [edx] inc byte [$12345678] inc dword [edi+ecx*4] dec ebx dec byte [eax+$80] dec word [edi] dec dword [edi+ecx*8] end macro ;;;;;;;;;;;;;;;;;; NEGATE, NOT ;;;;;;;;;;;;;;;;;;; ; neg rm8 ; F6 /3 ; neg rmx ; oso F7 /3 ; not rm8 ; F6 /2 ; not rmx ; oso F7 /2 macro neg_not name, p& local type, opcode, digit type=0 opcode=$F6 digit=3 match =not, name digit=2 end match get_type p type=its_type if its_size=0 err 'Size must be specified' end if if its_size=2 oso end if s_bit=0 if its_size>=2 s_bit=1 end if if type='r' db opcode or s_bit put_mode 11b, digit, p else if type='m' db opcode or s_bit get_mode p write_mode digit else err 'Invalid operand' end if end macro macro neg x neg_not neg, x end macro macro not x neg_not not, x end macro macro test_neg_not neg eax neg dword [edx] neg byte [$12345678] neg dword [edi+ecx*4] not ebx not byte [eax+$80] not word [edi] not dword [edi+ecx*8] end macro Code: DISASSEMBLY OF EXAMPLE.EXE TEST (PE BROWSE PRO DISASSEMBLER) EXAMPLE.EXE Section .one (0x00401000) 0x4015CC: 50 PUSH EAX 0x4015CD: 6A77 PUSH 0x77 0x4015CF: 6878563412 PUSH 0x12345678 0x4015D4: FF32 PUSH DWORD PTR [EDX] 0x4015D6: FF36 PUSH DWORD PTR [ESI] 0x4015D8: FF7500 PUSH DWORD PTR [EBP] 0x4015DB: FF3578563412 PUSH DWORD PTR [0x12345678] 0x4015E1: FF7708 PUSH DWORD PTR [EDI+0x8] 0x4015E4: FFB7BEBAFECA PUSH DWORD PTR [EDI+0xCAFEBABE] 0x4015EA: FF3411 PUSH DWORD PTR [ECX+EDX] 0x4015ED: FF344E PUSH DWORD PTR [ESI+ECX*2] 0x4015F0: FF3491 PUSH DWORD PTR [ECX+EDX*4] 0x4015F3: FF749177 PUSH DWORD PTR [ECX+EDX*4+0x77] 0x4015F7: FFB4D13412BEBA PUSH DWORD PTR [ECX+EDX*8+0xBABE1234] 0x4015FE: 59 POP ECX 0x4015FF: 8F4708 POP DWORD PTR [EDI+0x8] 0x401602: 8F87BEBAFECA POP DWORD PTR [EDI+0xCAFEBABE] 0x401608: 8BC1 MOV EAX,ECX 0x40160A: C7C278563412 MOV EDX,0x12345678 0x401610: 8AE1 MOV AH,CL 0x401612: 668BCB MOV CX,BX 0x401615: 8B0F MOV ECX,DWORD PTR [EDI] 0x401617: 8B5508 MOV EDX,DWORD PTR [EBP+0x8] 0x40161A: 8B5FE0 MOV EBX,DWORD PTR [EDI-0x20] 0x40161D: 8B2491 MOV ESP,DWORD PTR [ECX+EDX*4] 0x401620: 8BBCDABEBAFECA MOV EDI,DWORD PTR [EDX+EBX*8+0xCAFEBABE] 0x401627: 8B0E MOV ECX,DWORD PTR [ESI] 0x401629: 8B5500 MOV EDX,DWORD PTR [EBP] 0x40162C: 8B3D78563412 MOV EDI,DWORD PTR [0x12345678] 0x401632: 8B4708 MOV EAX,DWORD PTR [EDI+0x8] 0x401635: 8B8FBEBAFECA MOV ECX,DWORD PTR [EDI+0xCAFEBABE] 0x40163B: 8B0411 MOV EAX,DWORD PTR [ECX+EDX] 0x40163E: 8B0C4E MOV ECX,DWORD PTR [ESI+ECX*2] 0x401641: 8B1491 MOV EDX,DWORD PTR [ECX+EDX*4] 0x401644: 8B5C9177 MOV EBX,DWORD PTR [ECX+EDX*4+0x77] 0x401648: 8BBCD13412BEBA MOV EDI,DWORD PTR [ECX+EDX*8+0xBABE1234] 0x40164F: 668B02 MOV AX,WORD PTR [EDX] 0x401652: 668B1D78563412 MOV BX,WORD PTR [0x12345678] 0x401659: 8AAF565555FF MOV CH,BYTE PTR [EDI-0xAAAAAA] 0x40165F: 8A84D13412BEBA MOV AL,BYTE PTR [ECX+EDX*8+0xBABE1234] 0x401666: 8821 MOV BYTE PTR [ECX],AH 0x401668: 66890C11 MOV WORD PTR [ECX+EDX],CX 0x40166C: 891C91 MOV DWORD PTR [ECX+EDX*4],EBX 0x40166F: C600FF MOV BYTE PTR [EAX],0xFF 0x401672: 66C70411FFFF MOV WORD PTR [ECX+EDX],0xFFFF 0x401678: C704D13412CDAB MOV DWORD PTR [ECX+EDX*8],0xABCD1234 0x40167F: 8B0CFDBEBAFECA MOV ECX,DWORD PTR [0xCAFEBABE+EDI*8] 0x401686: 0FB72491 MOVZX ESP,WORD PTR [ECX+EDX*4] 0x40168A: 0FB7BCDABEBAFECA MOVZX EDI,WORD PTR [EDX+EBX*8+0xCAFEBABE] 0x401692: 0FB7C1 MOVZX EAX,CX 0x401695: 0FBE0F MOVSX ECX,BYTE PTR [EDI] 0x401698: 0FBE5508 MOVSX EDX,BYTE PTR [EBP+0x8] 0x40169C: 0FBEDC MOVSX EBX,AH 0x40169F: 8D0F LEA ECX,[EDI] 0x4016A1: 8D5508 LEA EDX,[EBP+0x8] 0x4016A4: 8D5FE0 LEA EBX,[EDI-0x20] 0x4016A7: 8D2491 LEA ESP,[ECX+EDX*4] 0x4016AA: 8DBCDABEBAFECA LEA EDI,[EDX+EBX*8+0xCAFEBABE] 0x4016B1: EB12 JMP 0x4016C5 ; (*+0x14) 0x4016B3: E80D000000 CALL 0x4016C5 0x4016B8: 740B JZ 0x4016C5 ; (*+0xD) 0x4016BA: 7509 JNZ 0x4016C5 ; (*+0xB) 0x4016BC: E804000000 CALL 0x4016C5 0x4016C1: 7D02 JGE 0x4016C5 ; (*+0x4) 0x4016C3: 7300 JAE 0x4016C5 ; (*+0x2) 0x4016C5: C3 RET 0x4016C6: C20800 RET 0x8 0x4016C9: E8F7FFFFFF CALL 0x4016C5 0x4016CE: 40 INC EAX 0x4016CF: FF02 INC DWORD PTR [EDX] 0x4016D1: FE0578563412 INC BYTE PTR [0x12345678] 0x4016D7: FF048F INC DWORD PTR [EDI+ECX*4] 0x4016DA: 4B DEC EBX 0x4016DB: FE8880000000 DEC BYTE PTR [EAX+0x80] 0x4016E1: 66FF0F DEC WORD PTR [EDI] 0x4016E4: FF0CCF DEC DWORD PTR [EDI+ECX*8] 0x4016E7: F7D8 NEG EAX 0x4016E9: F71A NEG DWORD PTR [EDX] 0x4016EB: F61D78563412 NEG BYTE PTR [0x12345678] 0x4016F1: F71C8F NEG DWORD PTR [EDI+ECX*4] 0x4016F4: F7D3 NOT EBX 0x4016F6: F69080000000 NOT BYTE PTR [EAX+0x80] 0x4016FC: 66F717 NOT WORD PTR [EDI] 0x4016FF: F714CF NOT DWORD PTR [EDI+ECX*8] 0x401702: D3E0 SHL EAX,CL 0x401704: D3EB SHR EBX,CL 0x401706: D3C7 ROL EDI,CL 0x401708: C1EA18 SHR EDX,0x18 0x40170B: C13F04 SAR DWORD PTR [EDI],0x4 0x40170E: C1C010 ROL EAX,0x10 0x401711: D30B ROR DWORD PTR [EBX],CL 0x401713: D3A0BEBAFECA SHL DWORD PTR [EAX+0xCAFEBABE],CL 0x401719: 03C1 ADD EAX,ECX 0x40171B: 12CA ADC CL,DL 0x40171D: 2AF7 SUB DH,BH 0x40171F: 661BCA SBB CX,DX 0x401722: 663BDA CMP BX,DX 0x401725: 23C6 AND EAX,ESI 0x401727: 0BCA OR ECX,EDX 0x401729: 33E7 XOR ESP,EDI 0x40172B: 81C178563412 ADD ECX,0x12345678 0x401731: 81EA3412CDAB SUB EDX,0xABCD1234 0x401737: 81D3BEBAFECA ADC EBX,0xCAFEBABE 0x40173D: 6681D93412 SBB CX,0x1234 0x401742: 6681FACDAB CMP DX,0xABCD 0x401747: 6681E3BEBA AND BX,0xBABE 0x40174C: 80CC77 OR AH,0x77 0x40174F: 80F177 XOR CL,0x77 0x401752: 030E ADD ECX,DWORD PTR [ESI] 0x401754: 135500 ADC EDX,DWORD PTR [EBP] 0x401757: 2B3D78563412 SUB EDI,DWORD PTR [0x12345678] 0x40175D: 1B4708 SBB EAX,DWORD PTR [EDI+0x8] 0x401760: 3B8FBEBAFECA CMP ECX,DWORD PTR [EDI+0xCAFEBABE] 0x401766: 230411 AND EAX,DWORD PTR [ECX+EDX] 0x401769: 0B0C4E OR ECX,DWORD PTR [ESI+ECX*2] 0x40176C: 331491 XOR EDX,DWORD PTR [ECX+EDX*4] 0x40176F: 035C9177 ADD EBX,DWORD PTR [ECX+EDX*4+0x77] 0x401773: 13BCD13412BEBA ADC EDI,DWORD PTR [ECX+EDX*8+0xBABE1234] 0x40177A: 662B02 SUB AX,WORD PTR [EDX] 0x40177D: 661B1D78563412 SBB BX,WORD PTR [0x12345678] 0x401784: 3AAF565555FF CMP CH,BYTE PTR [EDI-0xAAAAAA] 0x40178A: 2284D13412BEBA AND AL,BYTE PTR [ECX+EDX*8+0xBABE1234] 0x401791: 0821 OR BYTE PTR [ECX],AH 0x401793: 66310C11 XOR WORD PTR [ECX+EDX],CX 0x401797: 011C91 ADD DWORD PTR [ECX+EDX*4],EBX 0x40179A: 8010FF ADC BYTE PTR [EAX],0xFF 0x40179D: 66812C11FFFF SUB WORD PTR [ECX+EDX],0xFFFF 0x4017A3: 811CD13412CDAB SBB DWORD PTR [ECX+EDX*8],0xABCD1234 0x4017AA: 3B0CFDBEBAFECA CMP ECX,DWORD PTR [0xCAFEBABE+EDI*8] 0x4017B1: 90 NOP
|
|||||||||||
21 May 2015, 07:23 |
|
< Last Thread | Next Thread > |
Forum Rules:
|
Copyright © 1999-2024, Tomasz Grysztar. Also on GitHub, YouTube.
Website powered by rwasa.