8086 Instruction Set (Applicable to the Micro86 simulator) -------------------------------------------------------- AAA - ASCII Adjust for Addition Usage: AAA Flag-Bit Changes: AF CF (OF,PF,SF,ZF undefined) Operation IF ((AL AND 0FH) > 9) OR (AF = 1) THEN AL <-- (AL + 6) AND 0FH; AH <-- AH + 1; AF <-- 1; CF <-- 1; ELSE CF <-- 0; AF <-- 0; FI; Description Execute AAA only following an ADD instruction that leaves a byte result in the AL register. The lower nibbles of the operands of the ADD instruction should be in the range 0 through 9 (BCD digits). In this case, AAA adjusts AL to contain the correct decimal digit result. If the addition produced a decimal carry, the AH register is incremented, and the carry and auxiliary carry flags are set to 1. If there was no decimal carry, the carry and auxiliary flags are set to 0 and AH is unchanged. In either case, AL is left with its top nibble set to 0. To convert AL to an ASCII result, follow the AAA instruction with OR AL, 30H. Operands none -------------------------------------------------------- AAD - ASCII Adjust for Division Usage: AAD Flag-Bit Changes: SF ZF PF (AF,CF,OF undefined) Operation AL <-- AH * 10 + AL; AH <-- 0; Description AAD is used to prepare two unpacked BCD digits (the least-significant digit in AL, the most-significant digit in AH) for a division operation that will yield an unpacked result. This is accomplished by setting AL to AL + (10 * AH), and then setting AH to 0. AX is then equal to the binary equivalent of the original unpacked two-digit number. Operands none -------------------------------------------------------- AAM - ASCII Adjust for Multiplication Usage: AAM Flag-Bit Changes: PF SF ZF (AF,CF,OF undefined) Operation AH <-- AL / 10; AL <-- AL MOD 10; Description Execute AAM only after executing a MUL instruction between two unpacked BCD digits that leaves the result in the AX register. Because the result is less than 100, it is contained entirely in the AL register. AAM unpacks the AL result by dividing AL by 10, leaving the quotient (most-significant digit) in AH and the remainder (least-significant digit) in AL. Operands none -------------------------------------------------------- AAS - ASCII Adjust for Subtraction Usage: AAS Flag-Bit Changes: AF CF (OF,PF,SF,ZF undefined) Operation IF (AL AND 0FH) > 9 OR AF = 1 THEN AL <-- AL - 6; AL <-- AL AND 0FH; AH <-- AH - 1; AF <-- 1; CF <-- 1; ELSE CF <-- 0; AF <-- 0; FI; Description Execute AAS only after a SUB instruction that leaves the byte result in the AL register. The lower nibbles of the operands of the SUB instruction must have been in the range 0 through 9 (BCD digits). In this case, AAS adjusts AL so it contains the correct decimal digit result. If the subtraction produced a decimal carry, the AH register is decremented, and the carry and auxiliary carry flags are set to 1. If no decimal carry occurred, the carry and auxiliary carry flags are set to 0, and AH is unchanged. In either case, AL is left with its top nibble set to 0. To convert AL to an ASCII result, follow the AAS with OR AL, 30H. Operands none -------------------------------------------------------- ADC - Add With Carry Usage: ADC DEST,SRC Flag-Bit Changes: AF CF OF SF PF ZF Operation DEST <-- DEST + SRC + CF; Description ADC performs an integer addition of the two operands DEST and SRC and the carry flag, CF. The result of the addition is assigned to the first operand (DEST), and the flags are set accordingly. ADC is usually executed as part of a multi-byte or multi-word addition operation. When an immediate byte value is added to a word operand, the immediate value is first sign-extended to the size of the word operand. Operands REG,REG - ADC AX,BX MEM,REG - ADC [BX],AX REG,MEM - ADC AL,[BX] REG,IMMED - ADC CX,50 MEM,IMMED - ADC BPTR [BX],50 ACCUM,IMMED - ADC AX,50 -------------------------------------------------------- ADD - Arithmetic Addition Usage: ADD DEST,SRC Flag-Bit Changes: AF CF OF PF SF ZF Operation DEST <-- DEST + SRC; Description ADD performs an integer addition of the two operands (DEST and SRC). The result of the addition is assigned to the first operand (DEST), and the flags are set accordingly. When an immediate byte is added to a word operand, the immediate value is sign-extended to the size of the word operand. Operands REG,REG - ADD AX,BX MEM,REG - ADD [BX],AX REG,MEM - ADD AL,[BX] REG,IMMED - ADD CX,50 MEM,IMMED - ADD BPTR [BX],50 ACCUM,IMMED - ADD AX,50 -------------------------------------------------------- AND - Logical And Usage: AND DEST,SRC Flag-Bit Changes: CF OF PF SF ZF (AF undefined) Operation DEST <-- DEST AND SRC; CF <-- 0; OF <-- 0; Description Each bit of the result of the AND instruction is a 1 if both corresponding bits of the operands are 1; otherwise, it becomes a 0. Operands REG,REG - AND AX,BX MEM,REG - AND [BX],AX REG,MEM - AND AL,[BX] REG,IMMED - AND CX,50 MEM,IMMED - AND WPTR [BX],50 ACCUM,IMMED - AND AX,50 -------------------------------------------------------- CALL - Procedure Call Usage: CALL destination Flag-Bit Changes: None Operation IF rel16 type of call THEN (* near relative call *) Push(IP); IP <-- IP + rel16; FI; IF r/m16 type of call THEN (* near absolute call *) Push(IP); IP <-- [r/m16]; FI; Description The CALL instruction causes the procedure named in the operand to be executed. When the procedure is complete (a return instruction is executed within the procedure), execution continues at the instruction that follows the CALL instruction. The action of the different forms of the instruction are described below. Near calls are those with destinations of type r/m16, rel16; The CALL rel16 form add a signed offset to the address of the instruction following CALL to determine the destination. The rel16 form is used when the instruction's operand-size attribute is 16 bits. CALL r/m16 specify a register or memory location from which the absolute segment offset is fetched. The offset of the instruction following CALL is pushed onto the stack. It will be popped by a near RET instruction within the procedure. Operands REL16 (NEAR, IP RELATIVE) - CALL DELAY REG16 (NEAR, REGISTER INDIRECT) - CALL AX MEM16 (NEAR, MEMORY INDIRECT) - CALL [BX+SI] -------------------------------------------------------- CBW - Convert Byte to Word Usage: CBW Flag-Bit Changes: None Operation AX <-- SignExtend(AL); Description CBW converts the signed byte in AL to a signed word in AX by extending the most significant bit of AL (the sign bit) into all of the bits of AH. Operands none -------------------------------------------------------- CLC - Clear Carry Usage: CLC Flag-Bit Changes: CF Operation CF <-- 0; Description CLC sets the carry flag to zero. It does not affect other flags or registers. Operands none -------------------------------------------------------- CLD - Clear Direction Flag Usage: CLD Flag-Bit Changes: DF Operation DF <-- 0; Description CLD clears the direction flag. No other flags or registers are affected. After CLD is executed, string operations will increment the index registers (SI and/or DI) that they use. Operands none -------------------------------------------------------- CLI - Clear Interrupt Flag (disable) Usage: CLI Flag-Bit Changes: IF Operation IF <-- 0; Description CLI clears the interrupt flag. External interrupts are not recognized at the end of the CLI instruction or from that point on until the interrupt flag is set. Operands none -------------------------------------------------------- CMC - Complement Carry Flag Usage: CMC Flag-Bit Changes: CF Operation CF <-- NOT CF; Description CMC reverses the setting of the carry flag. No other flags are affected. Operands none -------------------------------------------------------- CMP - Compare Usage: CMP DEST,SRC Flag-Bit Changes: AF CF OF PF SF ZF Operation DEST - SRC; (* CMP does not store a result; its purpose is to set the flags *) Description CMP subtracts the second operand from the first but, unlike the SUB instruction, does not store the result; only the flags are changed. CMP is typically used in conjunction with conditional jumps. If an operand greater than one byte is compared to an immediate byte, the byte value is first sign-extended. Operands REG,REG - CMP AX,BX MEM,REG - CMP [BX],AX REG,MEM - CMP AL,[BX] REG,IMMED - CMP CX,50 MEM,IMMED - CMP WPTR [BX],50 ACCUM,IMMED - CMP AX,50 -------------------------------------------------------- CMPS - Compare String (Byte, Word) Usage: CMPSB CMPSW Flag-Bit Changes: AF CF OF PF SF ZF Operation IF byte type of instruction THEN [SI] - [DI]; (* byte comparison *) IF DF = 0 THEN IncDec <-- 1 ELSE IncDec <-- -1; ELSE [SI] - [DI]; (* word comparison *) IF DF = 0 THEN IncDec <-- 2 ELSE IncDec <-- -2; FI; SI = SI + IncDec; DI = DI + IncDec; Description CMPS compares the byte, or word pointed to by the source-index register with the byte, or word pointed to by the destination-index register. The comparison is done by subtracting the operand indexed by the destination-index register from the operand indexed by the source-index register. Note that the direction of subtraction for CMPS is [SI] - [DI] . The left operand (SI) is the source and the right operand (DI) is the destination. This is the reverse of the usual Intel convention in which the left operand is the destination and the right operand is the source. The result of the subtraction is not stored; only the flags reflect the change. The types of the operands determine whether bytes, or words are compared. After the comparison is made, both the source-index register and destination-index register are automatically advanced. If the direction flag is 0 (CLD was executed), the registers increment; if the direction flag is 1 (STD was executed), the registers decrement. The registers increment or decrement by 1 if a byte is compared or by 2 if a word is compared. CMPSB and CMPSW are synonyms for the byte and word CMPS instructions, respectively. CMPS can be preceded by the REPE or REPNE prefix for block comparison of CX bytes or words. Refer to the description of the REP instruction for more information on this operation. Operands none -------------------------------------------------------- CWD - Convert Word to Doubleword Usage: CWD Flag-Bit Changes: None Operation IF AX < 0 THEN DX <-- FFFF; ELSE DX <-- 0; Description CWD converts the signed word in AX to a signed doubleword in DX:AX by extending the most significant bit of AX into all the bits of DX. Operands none -------------------------------------------------------- DAA - Decimal Adjust for Addition Usage: DAA Flag-Bit Changes: AF CF PF SF ZF (OF undefined) Operation IF ((AL AND 0FH) > 9) OR (AF = 1) THEN AL <-- AL + 6; AF <-- 1; ELSE AF <-- 0; FI; IF (AL > 9FH) OR (CF = 1) THEN AL <-- AL + 60H; CF <-- 1; ELSE CF <-- 0; FI; Description Execute DAA only after executing an ADD instruction that leaves a two-BCD-digit byte result in the AL register. The ADD operands should consist of two packed BCD digits. The DAA instruction adjusts AL to contain the correct two-digit packed decimal result. Operands none -------------------------------------------------------- DAS - Decimal Adjust for Subtraction Usage: DAS Flag-Bit Changes: AF CF PF SF ZF (OF undefined) Operation IF (AL AND 0FH) > 9 OR AF = 1 THEN AL <-- AL - 6; AF <-- 1; ELSE AF <-- 0; FI; IF (AL > 9FH) OR (CF = 1) THEN AL <-- AL - 60H; CF <-- 1; ELSE CF <-- 0; FI; Description Execute DAS only after a subtraction instruction that leaves a two-BCD-digit byte result in the AL register. The operands should consist of two packed BCD digits. DAS adjusts AL to contain the correct packed two-digit decimal result. Operands none -------------------------------------------------------- DEC - Decrement Usage: DEC DEST Flag-Bit Changes: AF OF PF SF ZF Operation DEST <-- DEST - 1; Description DEC subtracts 1 from the operand. DEC does not change the carry flag. To affect the carry flag, use the SUB instruction with an immediate operand of 1. Operands REG8 - DEC AL MEM - DEC WPTR [BX] REG16 - DEC CX -------------------------------------------------------- DIV - Divide Usage: DIV SRC Flag-Bit Changes: (AF,CF,OF,PF,SF,ZF undefined) Operation temp <-- dividend / SRC; IF temp does not fit in quotient THEN Interrupt 0; ELSE quotient <-- temp; remainder <-- dividend MOD SRC; FI; --------------------------------------------------------------------------- Note: Divisions are unsigned. The divisor is given by SRC. The dividend, quotient, and remainder use implicit registers. Refer to the table under "Description." --------------------------------------------------------------------------- Description DIV performs an unsigned division. The dividend is implicit; only the divisor is given as an operand. The remainder is always less than the divisor. The type of the divisor determines which registers to use as follows: Size Dividend Divisor Quotient Remainder byte AX r/m8 AL AH word DX:AX r/m16 AX DX Operands REG8 - DIV BL REG16 - DIV CX MEM - DIV BPTR [BX] -------------------------------------------------------- HLT - Halt CPU Usage: HLT Flag-Bit Changes: None Operation Enter Halt state; Description HALT stops instruction execution and places the 8086 in a HALT state. Operands none -------------------------------------------------------- IDIV - Signed Integer Division Usage: IDIV SRC Flag-Bit Changes: (AF,CF,OF,PF,SF,ZF undefined) Operation temp <-- dividend / SRC; IF temp does not fit in quotient THEN Interrupt 0; ELSE quotient <-- temp; remainder <-- dividend MOD SRC; FI; --------------------------------------------------------------------------- Notes: Divisions are signed. The divisor is given by the SRC operand. The dividend, quotient, and remainder use implicit registers. Refer to the table under "Description." --------------------------------------------------------------------------- Description IDIV performs a signed division. The dividend, quotient, and remainder are implicitly allocated to fixed registers. Only the divisor is given as an explicit SRC operand. The type of the divisor determines which registers to use as follows: Size Divisor Quotient Remainder Dividend byte r/m8 AL AH AX word r/m16 AX DX DX:AX If the resulting quotient is too large to fit in the destination, or if the division is 0, an Interrupt 0 is generated. Nonintegral quotients are truncated toward 0. The remainder has the same sign as the dividend and the absolute value of the remainder is always less than the absolute value of the divisor. Operands REG8 - IDIV BL REG16 - IDIV CX MEM - IDIV BPTR [BX] -------------------------------------------------------- IMUL - Signed Multiply Usage: IMUL SRC Flag-Bit Changes: CF OF (AF,PF,SF,ZF undefined) Operation result <-- multiplicand * multiplier; Description Signed multiplication of accumulator by "SRC" with result placed in the accumulator. If the source operand is a byte value, it is multiplied by AL and the result stored in AX. If the source operand is a word value it is multiplied by AX and the result is stored in DX:AX. Operands REG8 - IMUL BL REG16 - IMUL DX MEM8 - IMUL BPTR [SI] MEM16 - IMUL WPTR [DI] -------------------------------------------------------- IN - Input Byte or Word From Port Usage: IN ACCUM,PORT Flag-Bit Changes: None Operation ACCUM <-- [PORT]; (* Reads from I/O address space *) Description IN transfers a data byte or data word from the port numbered by the second operand into the register (AL, AX) specified by the first operand. If the port number is in the range of 0-255 it can be specified as an immediate, otherwise the port number must be specified in DX. Operands ACCUM,IMMED8 - IN AL,20 ACCUM,DX - IN AL,DX -------------------------------------------------------- INC - Increment Usage: INC dest Flag-Bit Changes: AF OF PF SF ZF Operation DEST <-- DEST + 1; Description INC adds 1 to the operand. It does not change the carry flag. To affect the carry flag, use the ADD instruction with a second operand of 1. Operands REG8 - INC AL MEM - INC WPTR [BX] REG16 - INC CX -------------------------------------------------------- INT - Interrupt Usage: INT n Flag-Bit Changes: TF IF Operation --------------------------------------------------------------------------- NOTE: The following operational description applies not only to the above instructions but also to external interrupts and exceptions. --------------------------------------------------------------------------- Push (FLAGS); IF <-- 0; (* Clear interrupt flag *) TF <-- 0; (* Clear trap flag *) Push(CS); Push(IP); CS <-- IVT[Interrupt number * 4].selector; IP <-- IVT[Interrupt number * 4].offset; Description The INT instruction generates via software a call to an interrupt handler. The immediate operand, from 0 to 255, gives the index number into the Interrupt Vector Table (IVT) of the interrupt routine to be called. The IVT is an array of four byte-long pointers. The first 32 interrupts are reserved by Intel for system use. Some of these interrupts are use for internally generated exceptions. INT n generally behaves like a call except that the flags register is pushed onto the stack before the return address. Interrupt procedures return via the IRET instruction, which pops the flags and return address from the stack. INT n pushes the flags, CS, and the return IP onto the stack, in that order, then jumps to the pointer indexed by the interrupt number. Initiates a software interrupt by pushing the flags, clearing the Trap and Interrupt Flags, pushing CS followed by IP and loading CS:IP with the value found in the interrupt vector table. Execution then begins at the location addressed by the new CS:IP Operands 3 (CONSTANT) - INT 3 IMMED8 - INT 20 -------------------------------------------------------- INTO - Interrupt on Overflow Usage: INTO Flag-Bit Changes: IF TF The INTO conditional software instruction is identical to the INT interrupt instruction except that the interrupt number is implicitly 4, and the interrupt is made only if the 8086 overflow flag is set. If the Overflow Flag is set this instruction generates an INT 4 which causes the code addressed by 0000:0010 to be executed. Operands None -------------------------------------------------------- IRET - Interrupt Return Usage: IRET Flag-Bit Changes: AF CF DF IF PF SF TF ZF Operation IP <-- Pop(); CS <-- Pop(); FLAGS <-- Pop(); Description IRET pops the instruction pointer, CS, and the flags register from the stack and resumes the interrupted routine. Returns control to point of interruption by popping IP, CS and then the Flags from the stack and continues execution at this location. Operands none -------------------------------------------------------- Jxx - Jump Instructions Table Mnemonic Meaning Jump Condition JA Jump if Above CF=0 and ZF=0 JAE Jump if Above or Equal CF=0 JB Jump if Below CF=1 JBE Jump if Below or Equal CF=1 or ZF=1 JC Jump if Carry CF=1 JCXZ Jump if CX Zero CX=0 JE Jump if Equal ZF=1 JG Jump if Greater (signed) ZF=0 and SF=OF JGE Jump if Greater or Equal (signed) SF=OF JL Jump if Less (signed) SF != OF JLE Jump if Less or Equal (signed) ZF=1 or SF != OF JNA Jump if Not Above CF=1 or ZF=1 JNAE Jump if Not Above or Equal CF=1 JNB Jump if Not Below CF=0 JNBE Jump if Not Below or Equal CF=0 and ZF=0 JNC Jump if Not Carry CF=0 JNE Jump if Not Equal ZF=0 JNG Jump if Not Greater (signed) ZF=1 or SF != OF JNGE Jump if Not Greater or Equal (signed) SF != OF JNL Jump if Not Less (signed) SF=OF JNLE Jump if Not Less or Equal (signed) ZF=0 and SF=OF JNO Jump if Not Overflow (signed) OF=0 JNP Jump if No Parity PF=0 JNS Jump if Not Signed (signed) SF=0 JNZ Jump if Not Zero ZF=0 JO Jump if Overflow (signed) OF=1 JP Jump if Parity PF=1 JPE Jump if Parity Even PF=1 JPO Jump if Parity Odd PF=0 JS Jump if Signed (signed) SF=1 JZ Jump if Zero ZF=1 Operation IF condition THEN IP <-- IP + rel8; FI; Description Conditional jumps (except JCXZ) test the flags which have been set by a previous instruction. The conditions for each mnemonic are given in parentheses after each description above. The terms "less" and "greater" are used for comparisons of signed integers; "above" and "below" are used for unsigned integers. If the given condition is true, a jump is made to the location provided as the operand. The target for the conditional jump is in the current code segment and within -128 to +127 bytes of the next instruction's first byte. There is more than one mnemonic for most of the conditional jump opcodes. For example, if you compared two characters in AX and want to jump if they are equal, use JE; or, if you ANDed AX with a bit field mask and only want to jump if the result is 0, use JZ, a synonym for JE. JCXZ differs from other conditional jumps because it tests the contents of the CX register for 0, not the flags. JCXZ is useful at the beginning of a conditional loop that terminates with a conditional loop instruction (such as LOOPNE LABEL. The JCXZ prevents entering the loop with CX equal to zero, which would cause the loop to execute 64K times instead of zero times. Operands Label - jxx NOT_EQU -------------------------------------------------------- JMP - Unconditional Jump Usage: JMP target Flag-Bit Changes: None Operation IP <-- IP + rel16; IF instruction = near indirect JMP (* i.e. operand is reg/mem16*) THEN IP <-- [reg/mem16]; FI; Description The JMP instruction transfers control to a different point in the instruction stream without recording return information. The action of the various forms of the instruction are shown below. The JMP rel16 instruction add an offset to the address of the instruction following the JMP to determine the destination. JMP reg/mem16 specifies a register or memory location from which the absolute offset is fetched. Operands LABEL - JMP START REG16 - JMP CX MEM16 - JMP [BX] -------------------------------------------------------- LAHF - Load Register AH From Flags Usage: LAHF Flag-Bit Changes: None Operation AH <-- SF:ZF:xx:AF:xx:PF:xx:CF; Description LAHF transfers the low byte of the flags word to AH. The bits, from MSB to LSB, are sign, zero, indeterminate, auxiliary, carry, indeterminate, parity, indeterminate, and carry. Operands none -------------------------------------------------------- LEA - Load Effective Address Usage: LEA DEST,SRC Flag-Bit Changes: None Operation DEST <-- Addr(SRC); Description LEA calculates the effective address (offset part) and stores it in the specified register Effective address is calculated and stored in requested register destination. Operands REG,MEM - LEA SI,[BX] -------------------------------------------------------- LODS - Load String (Byte, Word) Usage: LODSB LODSW Flag-Bit Changes: None Operation IF byte type of instruction THEN AL <-- [SI]; (* byte load *) IF DF = 0 THEN IncDec <-- 1 ELSE IncDec <-- -1; FI; ELSE AX <-- [SI]; (* word load *) IF DF = 0 THEN IncDec <-- 2 ELSE IncDec <-- -2; FI; FI; SI <-- SI + IncDec Description LODS loads the AL or AX register with the memory byte or word at the location pointed to by the source-index register. After the transfer is made, the source-index register is automatically advanced. If the direction flag is 0 (CLD was executed), the source index increments; if the direction flag is 1 (STD was executed), it decrements. The increment or decrement is 1 if a byte is loaded, 2 if a word is loaded. The address of the source data is determined solely by the contents of ESI/SI. Load the correct index value into SI before executing the LODS instruction. LODSB, LODSW are synonyms for the byte and word LODS instructions. LODS can be preceded by the REP prefix; however, LODS is used more typically within a LOOP construct, because further processing of the data moved into AX or AL is usually necessary. Operands none -------------------------------------------------------- LOOP - Decrement CX and Loop if CX Not Zero Usage: LOOP label Flag-Bit Changes: None Operation CX <-- CX - 1; IF CX <> 0 THEN IP <-- IP + rel8; FI; Description LOOP decrements CX without changing any of the flags. If CX is not zero, a jump is made to the label. The LOOP instructions provide iteration control and combine loop index management with conditional branching. Use the LOOP instruction by loading an unsigned iteration count into the count register, then code the LOOP at the end of a series of instructions to be iterated. The destination of LOOP is a label that points to the beginning of the iteration. Operands LABEL - loop NEXT -------------------------------------------------------- LOOPE/LOOPZ - Loop While Equal / Loop While Zero Usage: LOOPE label LOOPZ label Flag-Bit Changes: None Operation CX <-- CX - 1; IF CX <> 0 and ZF = 1 THEN IP <-- IP + rel8; FI; Description Decrements CX by 1 (without modifying the flags) and transfers control to "label" if CX != 0 and the Zero Flag is set. Operands LABEL - LOOPE NEXT -------------------------------------------------------- LOOPNZ/LOOPNE - Loop While Not Zero / Loop While Not Equal Usage: LOOPNZ label LOOPNE label Flag-Bit Changes: None Operation CX <-- CX - 1; IF CX <> 0 and ZF = 0 THEN IP <-- IP + rel8; FI; Description Decrements CX by 1 (without modifying the flags) and transfers control to "label" if CX != 0 and the Zero Flag is clear. Operands LABEL - LOOPNE NEXT -------------------------------------------------------- MOV - Move Byte or Word Usage: MOV DEST,SRC Flag-Bit Changes: None Operation DEST <-- SRC; Description MOV copies the second operand to the first operand. Operands REG,REG - MOV AL,BL MEM,REG - MOV [BX],CL REG,MEM - MOV DX,[BX] MEM,IMMED - MOV BPTR [SI],30 REG,IMMED - MOV AL,30 MEM,ACCUM - MOV [1000],AX ACCUM,MEM - MOV AX,[1000] -------------------------------------------------------- MOVS - Move String (Byte or Word) Usage: MOVSB MOVSW Flag-Bit Changes: None Operation IF byte type of instruction THEN [DI] <-- [SI]; (* byte assignment *) IF DF = 0 THEN IncDec <-- 1 ELSE IncDec <-- -1; FI; ELSE [DI] <-- [SI]; (* word assignment *) IF DF = 0 THEN IncDec <-- 2 ELSE IncDec <-- -2; FI; FI; SI <-- SI + IncDec; DI <-- DI + IncDec; Description MOVS copies the byte or word at [SI] to the byte or word at [DI]. The addresses of the source and destination are determined solely by the contents of SI and DI. Load the correct index values into SI and DI before executing the MOVS instruction. MOVSB and MOVSW are synonyms for the byte and word MOVS instructions. After the data is moved, both SI and DI are advanced automatically. If the direction flag is 0 (CLD was executed), the registers are incremented; if the direction flag is 1 (STD was executed), the registers are decremented. The registers are incremented or decremented by 1 if a byte was moved or 2 if a word was moved. MOVS can be preceded by the REP prefix for block movement of CX bytes or words. Refer to the REP instruction for details of this operation. Operands none -------------------------------------------------------- MUL - Unsigned Multiply Usage: MUL SRC Flag-Bit Changes: CF OF (AF,PF,SF,ZF undefined) Operation IF byte-size operation THEN AX <-- AL * SRC ELSE (* word operation *) DX:AX <-- AX * SRC FI; Description MUL performs unsigned multiplication. Its actions depend on the size of its operand, as follows: - A byte operand is multiplied by AL; the result is left in AX. The carry and overflow flags are set to 0 if AH is 0; otherwise, they are set to 1. - A word operand is multiplied by AX; the result is left in DX:AX. DX contains the high-order 16 bits of the product. The carry and overflow flags are set to 0 if DX is 0; otherwise, they are set to 1. Operands REG8 - MUL BL REG16 - MUL CX MEM8 - MUL BPTR [BX] MEM16 - MUL WPTR [SI] -------------------------------------------------------- NEG - Two's Complement Negation Usage: NEG DEST Flag-Bit Changes: AF CF OF PF SF ZF Operation IF DEST = 0 THEN CF <-- 0 ELSE CF <-- 1; FI; DEST <-- (- DEST); Description NEG replaces the value of a register or memory operand with its two's complement. The operand is subtracted from zero, and the result is placed in the operand. The carry flag is set to 1, unless the operand is zero, in which case the carry flag is cleared to 0. Operands REG - NEG AX MEM - NEG BPTR [BX+SI] -------------------------------------------------------- NOP - No Operation (90h) Usage: NOP Flag-Bit Changes: None Description NOP performs no operation. NOP is a one-byte instruction that takes up space but affects none of the machine context except IP. NOP is an alias mnemonic for the XCHG AX, AX instruction. Operands none -------------------------------------------------------- NOT - One's Compliment Negation (Logical NOT) Usage: NOT DEST Flag-Bit Changes: None Operation DEST <-- NOT DEST; Description NOT inverts the operand; every 1 becomes a 0, and vice versa. Operands REG - NOT CX MEM - NOT WPTR [1010] -------------------------------------------------------- OR - Inclusive Logical OR Usage: OR DEST,SRC Flag-Bit Changes: CF OF PF SF ZF (AF undefined) Operation DEST <-- DEST OR SRC; CF <-- 0; OF <-- 0 Description OR computes the inclusive OR of its two operands and places the result in the first operand. Each bit of the result is 0 if both corresponding bits of the operands are 0; otherwise, each bit is 1.. Operands REG,REG - OR AX,BX MEM,REG - OR [BX],AX REG,MEM - OR AL,[BX] REG,IMMED - OR CX,50 MEM,IMMED - OR WPTR [BX],50 ACCUM,IMMED - OR AX,50 -------------------------------------------------------- OUT - Output Data to Port Usage: OUT PORT,ACCUM Flag-Bit Changes: None Operation [PORT] <-- ACCUM; (* I/O address space used *) Description OUT transfers a data byte or data word from the register (AL or AX) given as the second operand to the output port numbered by the first operand. Output to any port from 0 to 65535 is performed by placing the port number in the DX register and then using an OUT instruction with DX as the first operand. If the instruction contains an eight-bit port ID, that value is zero-extended to 16 bits. Operands IMMED8,ACCUM - OUT 30,AL DX,ACCUM - OUT DX,AL -------------------------------------------------------- POP - Pop Word off Stack Usage: POP DEST Flag-Bit Changes: None Operation SP <-- SP + 2; DEST <-- [SP]; (* copy a word *) Description POP replaces the previous contents of the memory or the register operand with the word on the top of the 8086 stack,addressed by SP. The stack pointer SP is incremented by 2 for an operand-size of 16 bits. It then points to the new top of stack. Operands REG16 - POP AX MEM16 - POP [BX] -------------------------------------------------------- POPF - Pop Flags off Stack Usage: POPF Flag-Bit Changes: all flags Operation Flags <-- Pop(); Description POPF/POPFD pops the word on the top of the stack and stores the value in the flags register. Operands none -------------------------------------------------------- PUSH - Push Word onto Stack Usage: PUSH SRC Flag-Bit Changes: None Operation SP <-- SP - 2; [SP] <-- (SRC); (* word assignment *) Description PUSH decrements the stack pointer by 2. PUSH then places the operand on the new top of stack, which is pointed to by the stack pointer. Operands REG16 - PUSH AX MEM16 - POP [SI] -------------------------------------------------------- PUSHF - Push Flags onto Stack Usage: PUSHF Flag-Bit Changes: None Operation push(FLAGS); Description PUSHF decrements the stack pointer by 2 and copies the FLAGS register to the new top of stack which is pointed to by SP. Operands none -------------------------------------------------------- RCL/RCR/ROL/ROR – Rotate Usage: RXX DEST,COUNT Flag-Bit Changes: CF OF Operation (* ROL - Rotate Left *) temp <-- COUNT; WHILE (temp <> 0) DO tmpcf <-- high-order bit of DEST; DEST <-- DEST * 2 + (tmpcf); temp <-- temp - 1; OD; IF COUNT = 1 THEN IF high-order bit of DEST <> CF THEN OF <-- 1; ELSE OF <-- 0; FI; ELSE OF <-- undefined; FI; (* ROR - Rotate Right *) temp <-- COUNT; WHILE (temp <> 0 ) DO tmpcf <-- low-order bit of (DEST); DEST <-- DEST / 2 + (tmpcf * 2^(width(DEST))); temp <-- temp - 1; DO; IF COUNT = 1 THEN IF (high-order bit of DEST) <> (bit next to high-order bit of DEST) THEN OF <-- 1; ELSE OF <-- 0; FI; ELSE OF <-- undefined; FI; Description Each rotate instruction shifts the bits of the register or memory operand given. The left rotate instructions shift all the bits upward, except for the top bit, which is returned to the bottom. The right rotate instructions do the reverse: the bits shift downward until the bottom bit arrives at the top. For the RCL and RCR instructions, the carry flag is part of the rotated quantity. RCL shifts the carry flag into the bottom bit and shifts the top bit into the carry flag; RCR shifts the carry flag into the top bit and shifts the bottom bit into the carry flag. For the ROL and ROR instructions, the original value of the carry flag is not a part of the result, but the carry flag receives a copy of the bit that was shifted from one end to the other. The rotate is repeated the number of times indicated by the second operand, which is either ‘1’ or the contents of the CL register. The overflow flag is defined only for the single-rotate forms of the instructions (second operand = 1). It is undefined in all other cases. For left shifts/rotates, the CF bit after the shift is XORed with the high-order result bit. For right shifts/rotates, the high-order two bits of the result are XORed to get OF. Operands REG,1 - RCL CL,1 MEM,1 - RCL BPTR [BX],1 REG,CL - RCL AX,CL MEM,CL - RCL BPTR [BX],CL -------------------------------------------------------- REP/REPE/REPZ/REPNE/REPNZ -- Repeat Following String Operation Usage: REP Flag-Bit Changes: None Operation WHILE CX <> 0 DO PERFORM PRIMITIVE STRING INSTRUCTION; CX <-- CX - 1; IF primitive operation is CMPB, CMPW, SCASB, or SCASW THEN IF (instruction is REP/REPE/REPZ) AND (ZF=1) THEN exit WHILE loop ELSE IF (instruction is REPNZ or REPNE) AND (ZF=0) THEN exit WHILE loop; FI; FI; FI; OD; Description REP, REPE (repeat while equal), and REPNE (repeat while not equal) are prefix that are applied to string operation. Each prefix cause the string instruction that follows to be repeated the number of times indicated in the count register or (for REPE and REPNE) until the indicated condition in the zero flag is no longer met. Synonymous forms of REPE and REPNE are REPZ and REPNZ, respectively. The REP prefixes apply only to one string instruction at a time. To repeat a block of instructions, use the LOOP instruction or another looping construct. The precise action for each iteration is as follows: 1. Check CX. If it is zero, exit the iteration, and move to the next instruction. 2. Perform the string operation once. 3. Decrement CX or ECX by one; no flags are modified. 4. Check the zero flag if the string operation is SCAS or CMPS. If the repeat condition does not hold, exit the iteration and move to the next instruction. Exit the iteration if the prefix is REPE and ZF is 0 (the last comparison was not equal), or if the prefix is REPNE and ZF is one (the last comparison was equal). 5. Return to step 1 for the next iteration. Repeated CMPS and SCAS instructions can be exited if the count is exhausted or if the zero flag fails the repeat condition. These two cases can be distinguished by using either the JCXZ instruction, or by using the conditional jumps that test the zero flag (JZ, JNZ, and JNE). Operands primitive operation -REPXX CMPSB -------------------------------------------------------- RET - Return From Procedure Usage: RET Flag-Bit Changes: None Operation IP <-- Pop(); Description RET transfers control to a return address located on the stack. The address is usually placed on the stack by a CALL instruction, and the return is made to the instruction that follows the CALL. Operands none -------------------------------------------------------- SAHF - Store AH Register into FLAGS Usage: SAHF Flag-Bit Changes: AF CF PF SF ZF Operation SF:ZF:xx:AF:xx:PF:xx:CF <-- AH; Description SAHF loads the flags listed above with values from the AH register, from bits 7, 6, 4, 2, and 0, respectively. Transfers bits 0-7 of AH into the Flags Register. This includes AF, CF, PF, SF and ZF. Operands none -------------------------------------------------------- SAL/SAR/SHL/SHR -- Shift Instructions Usage: SAL DEST,COUNT SHL DEST,COUNT Flag-Bit Changes: CF OF PF SF ZF (AF undefined) Operation (* COUNT is the second parameter *) (temp) <-- COUNT; WHILE (temp <> 0) DO IF instruction is SAL or SHL THEN CF <-- high-order bit of DEST; FI; IF instruction is SAR or SHR THEN CF <-- low-order bit of DEST; FI; IF instruction = SAL or SHL THEN DEST <-- DEST * 2; FI; IF instruction = SAR THEN DEST <-- DEST /2 (*Signed divide, rounding toward negative infinity*); FI; IF instruction = SHR THEN DEST <-- DEST / 2; (* Unsigned divide *); FI; temp <-- temp - 1; OD; (* Determine overflow for the various instructions *) IF COUNT = 1 THEN IF instruction is SAL or SHL THEN OF <-- high-order bit of DEST <> (CF); FI; IF instruction is SAR THEN OF <-- 0; FI; IF instruction is SHR THEN OF <-- high-order bit of operand; FI; ELSE OF <-- undefined; FI; Description SAL (or its synonym, SHL) shifts the bits of the operand upward. The high-order bit is shifted into the carry flag, and the low-order bit is set to 0. SAR and SHR shift the bits of the operand downward. The low-order bit is shifted into the carry flag. The effect is to divide the operand by 2. SAR performs a signed divide with rounding toward negative infinity (not the same as IDIV); the high-order bit remains the same. SHR performs an unsigned divide; the high-order bit is set to 0. The shift is repeated the number of times indicated by the second operand, which is either ‘1’ or the contents of the CL register. The overflow flag is set only if the single-shift forms of the instructions are used. For left shifts, OF is set to 0 if the high bit of the answer is the same as the result of the carry flag (i.e., the top two bits of the original operand were the same); OF is set to 1 if they are different. For SAR, OF is set to 0 for all single shifts. For SHR, OF is set to the high-order bit of the original operand. Operands REG,1 - SAL CL,1 MEM,1 - SAL BPTR [BX],1 REG,CL - SAL AL,CL MEM,CL - SAL WPTR [BX],CL -------------------------------------------------------- SBB - Subtract with Borrow/Carry Usage: SBB DEST,SRC Flag-Bit Changes: AF CF OF PF SF ZF Operation DEST <-- DEST - (SRC + CF); Description SBB adds the second operand (DEST) to the carry flag (CF) and subtracts the result from the first operand (SRC). The result of the subtraction is assigned to the first operand (DEST), and the flags are set accordingly. When an immediate byte value is subtracted from a word operand, the immediate value is first sign-extended. Operands REG,REG - SBB AX,BX MEM,REG - SBB [BX],AX REG,MEM - SBB AL,[BX] REG,IMMED - SBB CX,50 MEM,IMMED - SBB BPTR [BX],50 ACCUM,IMMED - SBB AX,50 -------------------------------------------------------- SCAS - Scan String (Byte, Word) Usage: SCASB SCASW Flag-Bit Changes: AF CF OF PF SF ZF Operation IF byte type of instruction THEN AL - [DI]; (* Compare byte in AL and dest *) IF DF = 0 THEN IndDec <-- 1 ELSE IncDec <-- -1; FI; ELSE AX - [DI]; (* compare word in AL and dest *) IF DF = 0 THEN IncDec <-- 2 ELSE IncDec <-- -2; FI; FI; DI = DI + IncDec Description SCAS subtracts the memory byte or word at the destination register from the AL or AX register. The result is discarded; only the flags are set. The address of the memory data being compared is determined solely by the contents of the destination register, not by the operand to SCAS. After the comparison is made, the destination register is automatically updated. If the direction flag is 0 (CLD was executed), the destination register is incremented; if the direction flag is 1 (STD was executed), it is decremented. The increments or decrements are by 1 if bytes are compared, by 2 if words are compared. SCASB and SCASW are synonyms for the byte and word SCAS instructions that don't require operands. SCAS can be preceded by the REPE or REPNE prefix for a block search of CX or ECX bytes or words. Refer to the REP instruction for further details.. Operands none -------------------------------------------------------- STC - Set Carry Usage: STC Flag-Bit Changes: CF Operation CF <-- 1; Description STC sets the carry flag to 1. Operands none -------------------------------------------------------- STD - Set Direction Flag Usage: STD Flag-Bit Changes: DF Operation DF <-- 1; Description STD sets the direction flag to 1, causing all subsequent string operations to decrement the index registers, SI and/or DI, on which they operate. Operands none -------------------------------------------------------- STI - Set Interrupt Flag (Enable Interrupts) Usage: STI Flag-Bit Changes: IF Operation IF <-- 1 Description STI sets the interrupt flag to 1. The 8086 then responds to external interrupts after executing the next instruction if the next instruction allows the interrupt flag to remain enabled. Operands none -------------------------------------------------------- STOS - Store String (Byte, Word) Usage: STOSB STOSW Flag-Bit Changes: None Operation IF byte type of instruction THEN [DI] <-- AL; IF DF = 0 THEN DI <-- DI + 1; ELSE DI <-- DI - 1; FI; ELSE [DI] <-- AX; IF DF = 0 THEN DI <-- DI + 2; ELSE DI <-- DI - 2; FI; FI; Description STOS transfers the contents of all AL, or AX register to the memory byte or word given by the destination register . The address of the destination is determined by the contents of the destination register, not by the explicit operand of STOS. After the transfer is made, DI is automatically updated. If the direction flag is 0 (CLD was executed), DI is incremented; if the direction flag is 1 (STD was executed), DI is decremented. DI is incremented or decremented by 1 if a byte is stored, by 2 if a word is stored. STOSB and STOSW are synonyms for the byte and word STOS Instructions. STOS can be preceded by the REP prefix for a block fill of CX bytes, words. Refer to the REP instruction for further details. Operands none -------------------------------------------------------- SUB - Subtract Usage: SUB DEST,SRC Flag-Bit Changes: AF CF OF PF SF ZF Operation DEST <-- DEST - SRC; Description SUB subtracts the second operand (SRC) from the first operand (DEST). The first operand is assigned the result of the subtraction, and the flags are set accordingly. When an immediate byte value is subtracted from a word operand, the immediate value is first sign-extended to the size of the destination operand. Operands REG,REG - SUB AX,BX MEM,REG - SUB [BX],AX REG,MEM - SUB AL,[BX] REG,IMMED - SUB CX,50 MEM,IMMED - SUB BPTR [BX],50 ACCUM,IMMED - SUB AX,50 -------------------------------------------------------- TEST - Test for Bit Pattern Usage: TEST DEST,SRC Flag-Bit Changes: CF OF PF SF ZF (AF undefined) Operation DEST AND SRC; CF <-- 0; OF <-- 0; Description TEST computes the bit-wise logical AND of its two operands. Each bit of the result is 1 if both of the corresponding bits of the operands are 1; otherwise, each bit is 0. The result of the operation is discarded and only the flags are modified. Operands REG,REG - TEST AX,BX MEM,REG - TEST [BX],AX REG,MEM - TEST AL,[BX] REG,IMMED - TEST CX,50 MEM,IMMED - TEST WPTR [BX],50 ACCUM,IMMED - TEST AX,50 -------------------------------------------------------- XCHG - Exchange Usage: XCHG DEST,SRC Flag-Bit Changes: None Operation TEMP <-- DEST DEST <-- SRC SRC <-- TEMP Description XCHG exchanges two operands. The operands can be in either order. Operands REG,REG - XCHG AX,BX MEM,REG - XCHG [BX],AX REG,MEM - XCHG DX,[SI] ACCUM,REG - XCHG AX,BX REG,ACCUM - XCHG BX,AX -------------------------------------------------------- XLAT - Translate Usage: XLAT translation-table Flag-Bit Changes: None Operation AL <-- [BX + AL] Description Replaces the byte in AL with byte from a user table addressed by BX. The original value of AL is the index into the translate table. The best way to describe this is MOV AL,[BX+AL] The table address should have been moved into BX with a previous instruction. Operands none -------------------------------------------------------- XOR - Exclusive OR Usage: XOR DEST,SRC Flag-Bit Changes: CF OF PF SF ZF (AF undefined) Operation DEST <-- DEST XOR SRC CF <-- 0 OF <-- 0 Description XOR computes the exclusive OR of the two operands. Each bit of the result is 1 if the corresponding bits of the operands are different; each bit is 0 if the corresponding bits are the same. The answer replaces the first operand. Operands REG,REG - XOR AX,BX MEM,REG - XOR [BX],AX REG,MEM - XOR AL,[BX] REG,IMMED - XOR CX,50 MEM,IMMED - XOR WPTR [BX],50 ACCUM,IMMED - XOR AX,50