MNEMONICS 8086/8088/80186/80188/8087/V30/V20 assembly form : opcode [type ptr] [register],[address/reg] examples MOV AX,1234 INC BYTE PTR [BP] MOV AH,AL machine code : xxxxxxxx[xxxxxxxx]|[mdxxxr/m]|[xxxxxxxx[xxxxxxxx]]|[xxxxxxxx[xxxxxxxx]] opcode 1 / 2 bytes|mdr/m byte| disp 1 / 2 bytes |imm. data 1 / 2 bytes ADDRESS MODES (mdxxxr/m byte) effective address (EA) mdxxxr/m DS:[BX+SI] 00xxx000 DS:[BX+DI] 00xxx001 SS:[BP+SI] 00xxx010 SS:[BP+DI] 00xxx011 DS:[SI] 00xxx100 DS:[DI] 00xxx101 DS:disp16 00xxx110 DS:[BX] 00xxx111 DS:[BX+SI+disp8] 01xxx000 DS:[BX+DI+disp8] 01xxx001 SS:[BP+SI+disp8] 01xxx010 SS:[BP+DI+disp8] 01xxx011 DS:[SI+disp8] 01xxx100 DS:[DI+disp8] 01xxx101 SS:[BP+disp8] 01xxx110 DS:[BX+disp8] 01xxx111 DS:[BX+SI+disp16] 10xxx000 DS:[BX+DI+disp16] 10xxx001 SS:[BP+SI+disp16] 10xxx010 SS:[BP+DI+disp16] 10xxx011 DS:[SI+disp16] 10xxx100 DS:[DI+disp16] 10xxx101 SS:[BP+disp16] 10xxx110 DS:[BX+disp16] 10xxx111 register 11xxxreg REGISTERS (reg or sr bits) register 8bit 16bit reg segment register 16bit sr AL AX 000 ES 00 CL CX 001 CS 01 DL DX 010 SS 10 BL BX 011 DS 11 AH SP 100 CH BP 101 DH SI 110 BH DI 111 ADDRESSING MODES mode in the instruction in a register in memory example register register address----operand ,BX immediate operand ,FFH direct memory address---------------------operand ,[FFH] reg. indirect register address----mem. address---operand ,[BX] based register address----mem. address-+-operand ,[BX+FFH] displacement---------------------^ indexed register address----displacement-+-operand ,[SI+FFH] mem. address---------------------^ based indexed register address----mem. address-v register address----displacement-+-operand ,[BX+SI+FFH] displacement---------------------^ string operand mem. address---operand mem. address---destination I/O port dir. port address ,20H I/O port indir. port address ,DX DATA TRANSFER MOV move data register/mem. to/from register 100010dw mdregr/m immediate to reg./mem. 1100011w md000r/m data8/16bit immediate to register 1011wreg data8/16bit mem. to accu (AX/AL) 1010000w address16bit accu to mem. (AX/AL) 1010001w address16bit reg./mem. to segm. reg. 10001110 md0srr/m segm. reg. to reg./mem. 10001100 md0srr/m XCHG exchange register/memory with register 1000011w mdregr/m register with accu (AX) 10010reg PUSH push register/memory 11111111 md110r/m register 01010reg segment register 000sr110 immediate 011010s0 data8/16bit * PUSHA push all AX,CX,DX,BX,SP,BP,SI,DI 01100000 * POP pop register/memory 10001111 md000r/m register 01011reg segment register 000sr111 POPA pop all, except SP, (skipping) DI,SI,BP,xx,BX,DX,CX,AX 01100001 * IN input from I/O port fixed port 1110010w port8bit variable port in DX 1110110w OUT output to I/O port fixed port 1110011w port8bit variable port in DX 1110111w XLAT translate byte to AL 11010111 (AL = [BX + AL]) LEA load EA to register 10001101 mdregr/m LDS load pointer to DS 11000101 mdregr/m LES load pointer to ES 11000100 mdregr/m LAHF load AH with flags 10011111 (O,D,I,S,Z,A,P,C) SAHF store AH into flags 10011110 (O,D,I,S,Z,A,P,C) PUSHF push flags 10011100 POPF pop flags 10011101 ARITHMETIC ADD add reg./mem. with reg. to either 000000dw mdregr/m imm. to reg./mem. 100000sw md000r/m data8/16bit imm. to accu. (AX/AL) 0000010w data8/16bit ADC add with carry reg./mem. with reg. to either 000100dw mdregr/m imm. to reg./mem. 100000sw md010r/m data8/16bit imm. to accu. (AX/AL) 0001010w data8/16bit INC increment register/memory 1111111w md000r/m register 01000reg AAA ASCII adjust for add 00110111 DAA decimal adjust for add 00100111 SUB subtract reg./mem. and reg. to either 001010dw mdregr/m imm. from reg./mem. 100000sw md101r/m data8/16bit imm. from accu. (AX/AL) 0010110w data8/16bit SBB subtract with borrow reg./mem. and reg. to either 000110dw mdregr/m imm. from reg./mem. 100000sw md011r/m data8/16bit imm. from accu. (AX/AL) 0001110w data8/16bit DEC decrement register/memory 1111111w md001r/m register 01001reg AAS ASCII adjust for subtract 00111111 DAS decimal adjust for subtract 00101111 MUL multiply (unsigned) 1111011w md100r/m IMUL integer multiply (signed) register/memory 1111011w md101r/m immediate 011010s1 mdregr/m data8/16bit * AAM ASCII adjust for multiply 11010100 00001010 DIV divide (unsigned) 1111011w md110r/m IDIV integer divide (signed) 1111011w md111r/m AAD ASCII adjust for divide 11010101 00001010 CBW convert byte to word AL in AX 10011000 CWD convert word to double word 10011001 (AX in DX : AX) NEG change sign 1111011w md011r/m CMP compare reg./mem. and register 001110dw mdregr/m imm. with reg./mem. 100000sw md111r/m data8/16bit imm. with accu. (AX/AL) 0011110w data8/16bit LOGIC AND and reg./mem. with reg. to either 001000dw mdregr/m imm. to reg./mem. 100000sw md100r/m data8/16bit imm. to accu. (AX/AL) 0010010w data8/16bit OR or reg./mem. with reg. to either 000010dw mdregr/m imm. to reg./mem. 100000sw md001r/m data8/16bit imm. to accu. (AX/AL) 0000110w data8/16bit XOR exclusive or reg./mem. with reg. to either 001100dw mdregr/m imm. to reg./mem. 100000sw md110r/m data8/16bit imm. to accu. (AX/AL) 0011010w data8/16bit NOT invert 1111011w md010r/m SHL shift logical left (SAL) register/memory by 1 1101000w md100r/m register/memory by CX 1101001w md100r/m register/memory by count 1100000w md100r/m count8bit * SHR shift logical right register/memory by 1 1101000w md101r/m register/memory by CX 1101001w md101r/m register/memory by count 1100000w md101r/m count8bit * ROL rotate left register/memory by 1 1101000w md000r/m register/memory by CX 1101001w md000r/m register/memory by count 1100000w md000r/m count8bit * ROR rotate right register/memory by 1 1101000w md001r/m register/memory by CX 1101001w md001r/m register/memory by count 1100000w md001r/m count8bit * SAL shift arithmetic left (SHL) register/memory by 1 1101000w md100r/m register/memory by CX 1101001w md100r/m register/memory by count 1100000w md100r/m count8bit * SAR shift arithmeric right register/memory by 1 1101000w md111r/m register/memory by CX 1101001w md111r/m register/memory by count 1100000w md111r/m count8bit * RCL rotate through carry left register/memory by 1 1101000w md010r/m register/memory by CX 1101001w md010r/m register/memory by count 1100000w md010r/m count8bit * RCR rotate through carry right register/memory by 1 1101000w md011r/m register/memory by CX 1101001w md011r/m register/memory by count 1100000w md011r/m count8bit * TEST and function to flags (no result) reg./mem. and register 1000010w mdregr/m imm. data and reg./mem. 1111011w md000r/m data8/16bit imm. data and accu. (AX/AL) 1010100w data8/16bit STRING MANIPULATION DS:SI = source, ES:DI = destination, CX = rep. count direction flag = direction set = decrement SI/DI clear = increment SI/DI REP repeat next string oper. 1111001z REPZ repeat for zero (REPE) 11110011 REPNZ repeat for not zero (REPNE) 11110010 REPE repeat for equal (REPZ) 11110011 REPNE repeat for not equal (REPNZ) 11110010 MOVSB move byte(s) 10100100 MOVSW move word(s) 10100101 CMPSB compare byte(s) 10100110 CMPSW compare word(s) 10100111 SCASB scan byte(s) 10101110 SCASW scan word(s) 10101111 LODSB load byte(s) to AL 10101100 LODSW load word(s) to AX 10101101 STOSB store byte(s) from AL 10101010 STOSW store word(s) from AX 10101011 INSB input byte(s) from DX port 01101100 * INSW input word(s) from DX port 01101101 * OUTSB output byte(s) to DX port 01101110 * OUTSW output word(s) to DX port 01101111 * CONTROL TRANSFER CALL call to subroutine direct within segment 11101000 disp16bit indirect within segment 11111111 md010r/m direct intersegment 10011010 offset:seg32bit indirect intersegment 11111111 md011r/m JMP unconditional jump direct within segment 11101001 disp16bit direct within segment-short 11101011 disp8bit indirect within segment 11111111 md100r/m direct intersegment 11101010 offset:seg32bit indirect intersegment 11111111 md101r/m RET return from call in segment 11000011 adding immediate to SP (level) 11000010 data16bit RETF return intersegment 11001011 adding immediate to SP (level) 11001010 data16bit JNBE jump on not below or equal (JA) 01110111 disp8bit JAE jump on above or equ. (JNB/JNC) 01110011 disp8bit JA jump on above (JNBE) 01110111 disp8bit JCXZ jump on CX zero 11100011 disp8bit JNB jump on not below (JAE/JNC) 01110011 disp8bit JBE jump on below or equal (JNA) 01110110 disp8bit JB jump on below (JNAE/JC) 01110010 disp8bit JNC jump on no carry (JNB/JAE) 01110011 disp8bit JC jump on carry (JB/JNAE) 01110010 disp8bit JNAE jump on not ab. or equ. (JB/JC) 01110010 disp8bit JNA jump on not above (JBE) 01110110 disp8bit JZ jump on zero (JE) 01110100 disp8bit JE jump on equal (JZ) 01110100 disp8bit JGE jump on greater or equal (JNL) 01111101 disp8bit JG jump on greater (JNLE) 01111111 disp8bit JNLE jump on not less or equal (JG) 01111111 disp8bit JNL jump on not less (JGE) 01111101 disp8bit JLE jump on less or equal (JNG) 01111110 disp8bit JL jump on less (JNGE) 01111100 disp8bit JNGE jump on not great. or equ. (JL) 01111100 disp8bit JNG jump on not greater (JLE) 01111110 disp8bit JNZ jump on not zero (JNE) 01110101 disp8bit JNE jump on not equal (JNZ) 01110101 disp8bit JPE jump on parity even (JP) 01111010 disp8bit JPO jump on parity odd (JNP) 01111011 disp8bit JNP jump on not parity (JPO) 01111011 disp8bit JNS jump on not sign 01111001 disp8bit JNO jump on not overflow 01110001 disp8bit JO jomp on overflow 01110000 disp8bit JS jump on sign 01111000 disp8bit JP jump on parity (JPE) 01111010 disp8bit LOOP loop CX times 11100010 disp8bit LOOPNZ loop while not zero (LOOPNE) 11100000 disp8bit LOOPZ loop while zero (LOOPE) 11100001 disp8bit LOOPNE loop while not equal (LOOPNZ) 11100000 disp8bit LOOPE loop while equal (LOOPZ) 11100001 disp8bit ENTER enter procedure 11001000 data16bit level8bit * LEAVE leave procedure 11001001 * INT interrupt type specified 11001101 type8bit type 3 11001100 INTO interrupt on overflow 11001110 IRET interrupt return 11001111 PROCESSOR CONTROL CLC clear carry 11111000 STC set carry 11111001 CMC complement carry 11110101 CLD clear direction 11111100 STD set direction 11111101 CLI clear interrupt 11111010 STI set interrupt 11111011 ESC escape (to external device) 11011xxx mdxxxr/m HLT halt 11110100 LOCK bus lock prefix (no external bus request allow. on next instr.) 11110000 NOP no operation 10010000 WAIT wait till test pin is low 10011011 SEGMENT CONTROL 001sr110 ES: segment override prefix ES 00100110 CS: segment override prefix CS 00101110 SS: segment override prefix SS 00110110 DS: segment override prefix DS 00111110 SPECIAL BITS d direction from/to 0 from register 1 to register w word/byte 0 8bit data/reg. instruction 1 16bit data/reg. instruction s sign extended 8bit or 16bit, w = 1 0 16bit data 1 8bit sign extended to 16bit z uses for string primitives for comparison with ZF flag (zero) x is don't care, uses with external device (8087) SEGMENT REGISTERS sr segment register 00 ES 01 CS 10 SS 11 DS POSTBYTE (mdregr/m) md mode 00 if r/m = 110 then EA = disp16bit, else disp = 0 (no disp) 01 disp is 8bit, sign extended to 16bit 10 disp is 16bit 11 r/m is a reg field disp follows 2nd byte of instruction (before data if required) r/m register/memory 000 EA = (BX)+(SI)+disp / AX / AL 001 EA = (BX)+(DI)+disp / CX / CL 010 EA = (BP)+(SI)+disp / DX / DL 011 EA = (BP)+(DI)+disp / BX / BL 100 EA = (SI)+disp / SP / AH 101 EA = (DI)+disp / BP / CH 110 EA = (BP)+disp / SI / DH when md = 00, EA = disp16bit 111 EA = (BX)+disp / DI / BH disp follows 2nd byte of instruction (before data if required) reg register 8/16bits 000 AL / AX 001 CL / CX 010 DL / DX 011 BL / BX 100 AH / SP 101 CH / BP 110 DH / SI 111 BH / DI * is extended opcodes, not available in 8086/8088 only on V20/V30/80188/80186 and upper procedure protocol : ENTER data,level : data is number of bytes to reserve on the stack level is nesting depth 1 = top, 0 = no nesting push BP on the stack, move SP in BP, look at level, if level is not zero then push level-1 words on the stack from old BP value address down, then push BP if level > 0. Finally subtract data from SP: SP stack BP stack low mem. SP after->| | | | |------| | | : undef } data value | | |------| | | (SP/2)->|BP aft|>-when level > 0 | | |------| |------| :BP xxx:<-------------------<:BP xxx } level value -1 |------| |------| (SP/1)-BP after->|BP bef| BP before->|BP xxx| |------| |------| high mem. SP before->| | | | |------| | | SP/BP before is value before ENTER opcode SP/BP after is value after ENTER opcode SP/1 is SP after when level and data is 0 SP/2 is SP after when data is 0 and level > 0 BP xxx is stack pointers from prev. procedure(s) LEAVE : move BP to SP, pop BP ; MOV SP,BP POP BP FLOATING POINT (8087) DATA TRANSFER FLD load and push int./real mem. to ST(0) 11011mf1 md000r/m temp real mem to ST(0) (80bit) 11011011 md101r/m ST(i) to ST(0) 11011001 11000sti FILD load integer memory to ST(0) and push short integer (32bit) 11011101 md000r/m long integer (64bit) 11011111 md101r/m FBLD load BCD memory to ST(0) (80b.) 11011111 md100r/m FST store ST(0) to int./real mem. 11011mf1 md010r/m ST(0) to ST(i) 11011101 11010sti FIST store in short integer (32bit) 11011011 md010r/m FSTP store and pop ST(0) to int./real mem. 11011mf1 md011r/m ST(0) to temp real mem (80bit) 11011011 md111r/m ST(0) to ST(i) 11011101 11011sti FISTP store and pop ST(0) to int. mem. short integer (32bit) 11011011 md011r/m long integer (64bit) 11011111 md111r/m FBSTP store and pop to BCD mem (80b.) 11011111 md110r/m FXCH exchange ST(i) and ST(0) 11011001 11001sti COMPARISON FCOM compare int./real mem. to ST(0) 11011mf0 md010r/m ST(i) to ST(0) 11011000 11010sti FICOM compare short int. to ST(0) 11011010 md010r/m FCOMP compare and pop int./real mem. to ST(0) 11011mf0 md011r/m ST(i) to ST(0) 11011000 11011sti FICOMP compare and pop short integer 11011010 md011r/m FCOMPP comp.ST(1) to ST(0) pop twice 11011110 11011001 FTST test ST(0) 11011001 11100100 FXAM examine ST(0) 11011001 11100101 CONSTANTS FLDZ load 0.0 into ST(0) 11011001 11101110 FLD1 load 1.0 into ST(0) 11011001 11101000 FLDPI load pi into ST(0) 11011001 11101011 FLDL2T load log2 10 into ST(0) 11011001 11101001 FLDL2E load log2 e into ST(0) 11011001 11101010 FLDLG2 load log10 2 into ST(0) 11011001 11101100 FLDLN2 load loge 2 into ST(0) 11011001 11101101 ARITHMETIC FADD addition int./real mem. with ST(0) 11011mf0 md000r/m ST(i) and ST(0) 11011d00 11000sti FIADD add short integer to ST(0) 11011010 md000r/m FADDP add and pop ST(0) ST(i) 11011d10 11000sti FSUB subtract ST(0) - [ST(i)/mem.] int./real mem. with ST(0) 11011mf0 md101r/m ST(i) and ST(0) 11011d00 11101sti FISUB subtract ST(0) - short integer 11011010 md101r/m FSUBP subtract ST(0) - ST(i) and pop 11011d10 11101sti FSUBR subtract [ST(i)/mem.] - ST(0) int./real mem. with ST(0) 11011mf0 md100r/m ST(i) and ST(0) 11011100 11100sti FISUBR subtract short integer - ST(0) 11011010 md100r/m FSUBRP subtract ST(i) - ST(0) and pop 11011110 11100sti FMUL multiplication int./real mem. with ST(0) 11011mf0 md001r/m ST(i) and ST(0) 11011d00 11001sti FIMUL mult. ST(0) * short integer 11011010 md001r/m FMULP mult. and pop ST(0) * ST(i) 11011d10 11001sti FDIV divide ST(0) / [ST(i)/mem.] int./real mem. with ST(0) 11011mf0 md111r/m ST(i) and ST(0) 11011d00 11111sti FIDIV div. ST(0) / short integer 11011010 md111r/m FDIVP divide ST(0) / ST(i) and pop 11011d10 11111sti FDIVR divide [ST(i)/mem.] / ST(0) int./real mem. with ST(0) 11011mf0 md110r/m ST(i) and ST(0) 11011100 11110sti FIDIVR div. short integer / ST(0) 11011010 md110r/m FDIVRP divide ST(i) / ST(0) and pop 11011110 11110sti FSQRT ST(0)=square root of ST(0) 11011001 11111010 FSCALE scale ST(0) by ST(1) 11011001 11111101 FPREM part. remainder of ST(0)/ST(1) 11011001 11111000 FRNDINT round ST(0) to integer 11011001 11111100 FXTRACT extract components of ST(0) 11011001 11110100 FABS absolute value of ST(0) 11011001 11100001 FCHS change sign of ST(0) 11011001 11100000 TRANSCENDENTAL FPTAN ST(0)=partial tangent of ST(0) 11011001 11110010 FPATAN partial tangent of ST(0)/ST(1) 11011001 11110011 F2XM1 ST(0)=2^ST(0)-1 11011001 11110000 FYL2X ST(0)=ST(1)*log2(|ST(0)|) 11011001 11110001 FYL2XP1 ST(0)=ST(1)*log2(|ST(0)+1|) 11011001 11111001 PROCESSOR CONTROL FINIT initialize 8087 11011011 11100011 FENI enable interrupts from 8087 11011011 11100000 FDISI disable interrupts from 8087 11011011 11100001 FLDCW load control word 11011001 md101r/m FSTCW store control word 11011001 md111r/m FSTSW store status word 11011101 md111r/m FCLEX clear exeptions (int) 11011011 11100010 FSTENV store environment 11011001 md110r/m FLDENV load environment 11011001 md100r/m FSAVE save state 11011101 md110r/m FRSTOR restore state 11011101 md100r/m FINCSTP increment stackpointer 11011001 11110111 FDECSTP decrement stackpointer 11011001 11110110 FFREE free ST(i) 11011101 11000sti FNOP no operation 11011001 11010000 FWAIT CPU wait for 8087 (WAIT) 10011011 SPECIAL BITS d destination 0 destination is ST(0) 1 destination is ST(i) mf memory format 00 32bit real (short real) 01 32bit integer (short integer) (FI) 10 64bit real (long real) 11 16bit integer (word integer) sti sti'th register below stack top POSTBYTE (mdxxxr/m) md mode 00 if r/m = 110 then EA = disp16bit, else disp = 0 (no disp) 01 disp is 8bit, sign extended to 16bit 10 disp is 16bit 11 r/m is a reg field disp follows 2nd byte of instruction (before data if required) r/m register/memory 000 EA = (BX)+(SI)+disp / ST(i) 001 EA = (BX)+(DI)+disp / ST(i) 010 EA = (BP)+(SI)+disp / ST(i) 011 EA = (BP)+(DI)+disp / ST(i) 100 EA = (SI)+disp / ST(i) 101 EA = (DI)+disp / ST(i) 110 EA = (BP)+disp / ST(i) when md = 00 EA = disp16bit 111 EA = (BX)+disp / ST(i) disp follows 2nd byte of instruction (before data if required) ST(0) is current stack top ST(i) is i'th register below stack top ASSEMBLY PSEUDO OPCODES DB inline bytes 8bit DW inline words 16bit ; comment line ASSEMBLER DATA TYPE PREFIX (after opcode mnem.) BYTE PTR byte (8bit) WORD PTR word / word integer (16bit) DWORD PTR double word / short integer / short real (32bit) QWORD PTR quad word / long integer / long real (64bit) TBYTE PTR ten byte / packed BCD / temporary real (80bit) DATA TYPES bits |7 0| |15 8|7 0| |31 24|23 16|15 8|7 0| |63 56|55 48|47 40|39 32|31 24|23 16|15 8|7 0| |79 72|71 64|63 56|55 48|47 40|39 32|31 24|23 16|15 8|7 0| |7 0|7 0|7 0|7 0|7 0|7 0|7 0|7 0|7 0|7 0| byte | | | | | | | | | | | - MAG. - | | | | | | | | | signed byte | | | | | | | | | | -S-MAG - | | | | | | | | | word | | | | | | | | | | | - MAGNITUDE - | | | | | | | | signed word / word integer | | | | | | | | -S-MAGNITUDE - | | | | | | | | pointer | | | | | | | | | | - SELECTOR - OFFSET - | | | | | | short integer / double word | | | | | | | | -S- MAGNITUDE - | | | | | | short real 23|24 | | | | | | | | | -S- EXP - MAGNITUDE - | | | | | | long integer / quad word | | | | | | | | -S- MAGNITUDE - | | long real | 52|53| | | | | | | | | -S-EXPONENT- MAGNITUDE - | | temporary real | | | | | | | | -S- EXPONENT -I- MAGNITUDE - packed BCD 18 digits | | | | | | | | -S--D17-D16/15- 2 DIGITS PER BYTE -D1/D0 - string | | | | | | | | | | | -ASCII - ANY NUMBER OF BYTES ......... S is sign bit; I is int. bit of significant, implicit in short and long real packed BCD: (-1)^S (D17...D0) real: (-1)^S (2^(EXP-bias)) (F0F1...) exponent bias (normalized values): short real: 127 (7FH) long real: 1023 (3FFH) temporary real: 16383 (3FFFH) REGISTERS 8086/8088/80186/80188/8087/V30/V20 bits 15 8 7 0 | | | | accumulator - AH -AX- AL - base - BH -BX- BL - count - CH -CX- CL - data - DH -DX- DL - | | | | stack pointer - SP - }--- base pointer - BP - }---| source index - SI - | destination index - DI - | | | | | | instruction pointer - IP - }-- | status flags - F - | | | | | | | | code segment - CS - }-- | data segment - DS - | stack segment - SS - }---- extra segment - ES - real address is : segment |15|14|13|12|11|10|09|08|07|06|05|04|03|02|01|00| offset |15|14|13|12|11|10|09|08|07|06|05|04|03|02|01|00| _____________________________________________________________ sum + 20 bit addr |19|18|17|16|15|14|13|12|11|10|09|08|07|06|05|04|03|02|01|00| FLAGS |15|14|13|12|11|10|09|08|07|06|05|04|03|02|01|00| -xx-xx-xx-xx-OF-DF-IF-TF-SF-ZF-xx-AF-xx-PF-xx-CF- OF overflow flag - set if result is too large DF direction flag for string instructions incr. when clear IF interrupt enable flag, when set int. transfer control to vector TF trace flag, when set a single step int. occurs after next instr. SF sign flag - set equal to high orderbit of result ZF zero flag - set if result is zero AF aux. carry - set on carry or borrow to the low fourbits of AL PF parity flag - set if low 8bits of result is even num. of bits CF carry flag - set on highbit carry or borrow FLOATING POINT REGISTERS 8087 bits | 79 | 78 64 | 63 0| |1 0| storage -sign- exponent - significand- -tag field- 8 float registers ST(0) - ST(7) with stack access all values are internally stored as temp. real (80bits) + tag (2bits) converting is done when values are loaded/stored CONTROL |15|14|13|12|11|10|09|08|07|06|05|04|03|02|01|00| control register -xx-xx-xx-IC- RC - PC -M -xx-PM-UM-OM-ZM-DM-IM- status register -B -C3- TOP -C2-C1-C0-IR-xx-PE-UE-OE-ZE-DE-IE- tag word -TAG7 -TAG6 -TAG5 -TAG4 -TAG3 -TAG2 -TAG1 -TAG0 - control register IC infinity control 0 - projective 1 - affine RC rounding control 00 - round to nearest or even 01 - round down (toward -inf.) 10 - round up (toward +inf.) 11 - chop (truncate toward zero) PC precision control 00 - 24 bits 10 - 53 bits 11 - 64 bits M interrupt mask 1 - int. are masked xM exeption masks 1 - exeption is masked PM precision OM underflow ZM zero divide DM denormalized operand IM invalid operation status register B neu busy TOP top of stack pointer ST(0) is ST(TOP) C0-C3 condition code IR interrupt request xE exeption flags 1 - exeption has occurred PE precision UE underflow OE overflow ZE zero divide DE denormalized operand IE invalid operation tag word values TAGx 00 - valid 01 - zero 10 - special 11 - empty condition codes C3 C2 C1 C0 compare, test 0 0 x 0 ST > source or 0 (FTST) 0 0 x 1 ST < source or 0 (FTST) 1 0 x 0 ST = source or 0 (FTST) 1 1 x 1 ST is not comparable remainder Q1 0 Q0 Q2 complete reduc. with 3 low bits of quotient x 1 x x incomplete reduction examine 0 0 0 0 valid, positive, unnormalized 0 0 0 1 invalid, positive, exponent = 0 0 0 1 0 valid, negative, unnormalized 0 0 1 1 invalid, negative, exponent = 0 0 1 0 0 valid, positive, normalized 0 1 0 1 infinity, positive 0 1 1 0 valid, negative, normalized 0 1 1 1 infinity, negative 1 0 0 0 zero, positive 1 0 0 1 empty 1 0 1 0 zero, negative 1 0 1 1 empty 1 1 0 0 invalid, positive, exponent = 0 1 1 0 1 empty 1 1 1 0 invalid, negative, exponent = 0 1 1 1 1 empty INSTRUCTION POINTER 20bits last used or current IP (debug) DATA POINTER 20bits last used or current DP (debug) environment image in memory (FSTENV,FLDENV) (debug) offset 15 12|11 0 +0 - CONTROL WORD - +2 - STATUS WORD - +4 - TAG WORD - +6 - INSTRUCTION POINTER (15-0) - +8 -INSTRUCT POINT. (19-16) -0 - OPCODE (10-0) - +10 - DATA POINTER (15-0) - +12 - DATA POINTER (19-16) - 0 -