Instruction set of 8086 Microprocessor
Software
The sequence of commands used to tell a microcomputer what to do is called a program, Each command in a program is called an instruction 8088 understands and performs operations for 117 basic instructions
ADD AX, BX
(Opcode) (Destination operand) (Source operand )
Instructions
LABEL: INSTRUCTION
Address identifier
; COMMENT
Does not generate any machine code
Ex.
START: MOV AX, BX
; copy BX into AX
There is a one-to-one relationship between assembly and machine language instructions
A compiled machine code implementation of a program written in a high-level language results in inefficient code
More machine language instructions than an assembled version of an equivalent handwritten assembly language program
3
Flag register
Data Transfer Instructions - MOV
Mnemonic MOV Meaning Move Format Mov D,S Operation (S) (D) Flags affected None
Destination
Memory Accumulator Register Register Memory Register Memory Seg reg Seg reg
Source
Accumulator Memory Register Memory Register Immediate Immediate Reg 16 Mem 16
NO MOV
Memory Immediate Segment Register Memory Segment Register Segment Register
Reg 16
Memory
Seg reg
Seg reg
EX:
MOV AL, BL
5
Data Transfer Instructions - XCHG
Mnemonic XCHG Meaning Exchange Format XCHG D,S Operation (S) (D) Flags affected None
Destination
Source
Accumulator Reg 16 Memory Register Register Register Register Memory
Example: XCHG [1234h], BX
NO XCHG
MEMs SEG REGs
Mnemo nic LEA
Data Transfer Instructions LEA, LDS, LES
Meaning Format Operation Load Effective Address Load Register And DS LEA Reg16,EA EA (Reg16)
Flags affected None
LDS
LDS Reg16,MEM32
(MEM32) (Reg16) (Mem32+2) (DS)
None
LES
Load Register and ES
LES Reg16,MEM32
(MEM32) (Reg16)
(Mem32+2) (DS)
None
LEA SI DATA (or) MOV SI Offset DATA
7
The XLAT Instruction
Mnemonic XLAT Meaning Translate Format XLAT Operation ((AL)+(BX)+(DS)0) (AL) Flags None
Example: Assume (DS) = 0300H, (BX)=0100H, and (AL)=0DH XLAT replaces contents of AL by contents of memory location with PA=(DS)0 +(BX) +(AL) = 03000H + 0100H + 0DH = 0310DH Thus (0310DH) (AL)
8
Arithmetic Instructions: ADD, ADC, INC, AAA, DAA
Mnemonic
ADD
Meaning
Addition
Format
ADD D,S
Operation
(S)+(D) (D) carry (CF) (S)+(D)+(CF) carry (D)+1 (D) (CF) (D)
Flags affected
ALL
ADC
Add with carry Increment by one
ASCII adjust for addition
ADC D,S
ALL
INC
INC D
ALL but CY
AAA
AAA
If the sum is >9, AH is incremented by 1
AF,CF
DAA
Decimal adjust for addition
DAA
Adjust AL for decimal Packed BCD
ALL
Examples:
Ex.1 ADD AX,2 ADC AX,2
Ex.2 INC BX INC WORD PTR [BX]
Ex.3 ASCII CODE 0-9 = 30-39h
MOV AX,38H ADD AL,39H AAA ADD AX,3030H Ex.4 AL contains 25 (packed BCD) BL contains 56 (packed BCD)
ADD AL, BL DAA
; (ASCII code for number 8) ; (ASCII code for number 9) AL=71h ; used for addition AH=01, AL=07 ; answer to ASCII 0107 AX=3137
25 + 56 -------7B 81
10
Arithmetic Instructions SUB, SBB, DEC, AAS, DAS, NEG
Mnemonic Meaning Format Operation Flags affected
SUB
SBB
Subtract
Subtract with borrow Decrement by one Negate Decimal adjust for subtraction ASCII adjust for subtraction
SUB D,S
SBB D,S
(D) - (S) Borrow
(D) - (S) - (CF)
(D) (CF)
(D)
All
All
DEC NEG DAS
DEC D NEG D DAS
(D) - 1
(D)
All but CF All
Convert the result in AL to packed decimal format (AL) difference (AH) dec by 1 if borrow
All
AAS
AAS
CY,AC
11
Examples: DAS
MOV BL, 28H MOV AL, 83H SUB AL,BL DAS
; AL=5BH ; adjust as AL=55H
MOV AX, 38H SUB AL,39H; AX=00FF AAS ; AX=FF09 tens complement of -1 OR AL,30H ; AL=39
(Borrow one from AH )
12
Multiplication and Division
13
Multiplication and Division
14
Multiplication and Division
Multiplication (MUL or IMUL) Byte*Byte Word*Word Dword*Dword Multiplicand AL AX EAX Operand (Multiplier) Register or memory Register or memory Register or memory Result AX DX :AX EAX :EDX
Division (DIV or IDIV) Word/Byte
Dividend
Operand (Divisor) Register or Memory
Quotient: Remainder
AX
AL : AH
Dword/Word
DX:AX
Register or Memory
AX : DX
Qword/Dword
EDX: EAX
Register or Memory
EAX : EDX
15
Multiplication and Division Examples
Ex1: Assume that each instruction starts from these values: AL = 85H, BL = 35H, AH = 0H 1. MUL BL AL . BL = 85H * 35H = 1B89H AX = 1B89H 2. IMUL BL AL . BL = 2S AL * BL = 2S (85H) * 35H = 7BH * 35H = 1977H 2s comp E689H AX. 3. DIV BL
0085 H = 02 (85-02*35=1B) = 35 H
AH
AL
1B
02
4. IDIV BL
0085 H = = 35 H
AH
AL
1B 02
16
Ex2:
AL = F3H, BL = 91H, AH = 00H
1. MUL BL AL * BL = F3H * 91H = 89A3H AX = 89A3H 2. IMUL BL AL * BL = 2S AL * 2S BL = 2S (F3H) * 2S(91H) = 0DH * 6FH = 05A3H AX.
00 F 3H 00 F 3H AX 3.IDIV BL = = = 2 (00F3 2*6F=15H) 6 FH 2' S (91H ) BL
AH AL
15 R
02 Q
POS NEG 2s(02) = FEH NEG
AH
15
AL
FE
00 F 3H AX 4. DIV BL = = 01(F3-1*91=62) 91H BL
AH 62 R
AL 01 Q
17
Ex3: AX= F000H, BX= 9015H, DX= 0000H
1. MUL BX = F000H * 9015H =
DX 8713
AX B000
DX AX
2. IMUL BX = 2S(F000H) * 2S(9015H) = 1000 * 6FEB =
06FE
B000
F 000 H 3. DIV BL = = B6DH More than FFH Divide Error. 15 H
2' S ( F 000 H ) 1000 H 4. IDIV BL = = C3H > 7F Divide Error. 15 H 15 H
18
Ex4:
AX= 1250H, BL= 90H
AX 1250 H 1250 H POS POS 1250 H 1. IDIV BL = = = = = BL NEG 2' sNEG 2' s(90 H ) 70 H 90 H
= 29H (Q) (1250 29 * 70) = 60H (REM) 29H ( POS) 2S (29H) = D7H
R 60H
Q D7H
1250 H AX 2. DIV BL = = 20H1250-20*90 =50H 90 H BL
R 50H AH
Q 20H AL
19
Logical Instructions
Mnemonic AND OR Meaning Logical AND Logical Inclusive OR Logical Exclusive OR Format AND D,S OR D,S Operation (S) (D) (D) (S)+(D) (D) (S) + Flags Affected OF, SF, ZF, PF, CF AF undefined OF, SF, ZF, PF, CF AF undefined OF, SF, ZF, PF, CF AF undefined None
XOR
XOR D,S
(D)(D) _ (D) (D)
NOT
LOGICAL NOT
NOT D
Destination Register Register Memory Register Memory Accumulator
Source Register Memory Register Immediate Immediate Immediate Destination
Register Memory
20
LOGICAL Instructions AND
Uses any addressing mode except memory-to-memory and segment registers Especially used in clearing certain bits (masking) xxxx xxxx AND 0000 1111 = 0000 xxxx (clear the first four bits) Examples: AND BL, 0FH AND AL, [345H]
OR
Used in setting certain bits
xxxx xxxx OR 0000 1111 = xxxx 1111 (Set the upper four bits)
21
XOR
Used in Inverting bits xxxx xxxx XOR 0000 1111 = xxxxxxxx
-Example: Clear bits 0 and 1, set bits 6 and 7, invert bit 5 of register CL: AND CL, OFCH ; OR CL, 0C0H ; XOR CL, 020H ; 1111 1100B 1100 0000B 0010 0000B
22
Shift and Rotate Instructions
SHR/SAL: shift logical left/shift arithmetic left SHR: shift logical right SAR: shift arithmetic right ROL: rotate left ROR: rotate right RCL: rotate left through carry RCR: rotate right through carry
23
Logical vs Arithmetic Shifts
A logical shift fills the newly created bit position with zero:
0
CF
An arithmetic shift fills the newly created bit position with a copy of the numbers sign bit:
CF
24
Shift Instructions
Mnemo -nic
SAL/SH L
Meaning
Format
Operation
Shift the (D) left by the number of bit positions equal to count and fill the vacated bits positions on the right with zeros
Flags Affected
CF,PF,SF,ZF AF undefined OF undefined if count 1
Shift SAL/SHL D, Count arithmetic Left/shift Logical left
SHR
Shift logical right
SHR D, Count
Shift the (D) right by the number of bit positions equal to count and fill the vacated bits positions on the left with zeros
Shift the (D) right by the number of bit positions equal to count and fill the vacated bits positions on the left with the original most significant bit
CF,PF,SF,ZF AF undefined OF undefined if count 1
SAR
Shift arithmetic right
SAR D, Count
CF,PF,SF,ZF AF undefined OF undefined if count 1
25
Allowed operands
Destination Register Register Memory Memory Count 1 CL 1 CL
26
27
SHL Instruction
The SHL (shift left) instruction performs a logical left shift on the destination operand, filling the lowest bit with 0.
0
CF
Operand types: SHL reg,imm8 SHL mem,imm8 SHL reg,CL SHL mem,CL
28
Fast Multiplication
Shifting left 1 bit multiplies a number by 2
mov dl,5
shl dl,1
Before: After:
00000101 00001010
=5 = 10
Shifting left n bits multiplies the operand by
2n For example, 5 * 22 = 20 mov dl,5 shl dl,2
; DL = 20
29
Ex. ; Multiply AX by 10
SHL AX, 1 MOV BX, AX MOV CL,2 SHL AX,CL ADD AX, BX
30
SHR Instruction
The SHR (shift right) instruction performs a logical right shift on the destination operand. The highest bit position is filled with a zero.
0
CF
Shifting right n bits divides the operand by 2n
MOV DL,80 SHR DL,1 SHR DL,2 ; DL = 40 ; DL = 10
31
SAR Instruction
SAR (shift arithmetic right) performs a right arithmetic shift on the destination operand.
CF
An arithmetic shift preserves the number's sign.
MOV DL,-80 SAR DL,1 SAR DL,2 ; DL = -40 ; DL = -10
32
Rotate Instructions
Mnem -onic ROL Meaning Rotate Left Format ROL D,Count Operation Flags Affected Rotate the (D) left by the CF number of bit positions equal OF undefined to Count. Each bit shifted out if count 1 from the left most bit goes back into the rightmost bit position. CF OF undefined if count 1
ROR
Rotate Right
ROR D,Count Rotate the (D) right by the number of bit positions equal to Count. Each bit shifted out from the rightmost bit goes back into the leftmost bit position. RCL D,Count Same as ROL except carry is attached to (D) for rotation.
RCL
Rotate Left through Carry Rotate right through Carry
CF OF undefined if count 1 CF OF undefined if count 1 33
RCR
RCR D,Count Same as ROR except carry is attached to (D) for rotation.
ROL Instruction
ROL (rotate) shifts each bit to the left The highest bit is copied into both the Carry flag and into the lowest bit No bits are lost
CF
MOV Al,11110000b ROL Al,1
MOV Dl,3Fh ROL Dl,4
; AL = 11100001b
; DL = F3h
34
ROR Instruction
ROR (rotate right) shifts each bit to the right The lowest bit is copied into both the Carry flag and into the highest bit No bits are lost
CF
MOV AL,11110000b ROR AL,1
MOV DL,3Fh ROR DL,4
; AL = 01111000b
; DL = F3h
35
RCL Instruction
RCL (rotate carry left) shifts each bit to the left Copies the Carry flag to the least significant bit Copies the most significant bit to the Carry flag
CF
CLC MOV BL,88H RCL BL,1 RCL BL,1
; ; ; ;
CF = 0 CF,BL = 0 10001000b CF,BL = 1 00010000b CF,BL = 0 00100001b
36
RCR Instruction
RCR (rotate carry right) shifts each bit to the right Copies the Carry flag to the most significant bit Copies the least significant bit to the Carry flag
CF
STC MOV AH,10H RCR AH,1
; CF = 1 ; CF,AH = 00010000 1 ; CF,AH = 10001000 0
37
Rotate Instructions
Destination Register Register Memory Memory Count 1 CL 1 CL
38
Flag control instructions
MNEMONIC MEANING OPERATION Flags Affected
CLC STC CMC CLD
Clear Carry Flag (CF) 0 Set Carry Flag Complement Carry Flag Clear Direction Flag Set Direction Flag Clear Interrupt Flag Set Interrupt Flag (CF) 1 (CF) (CF)l (DF) 0 SI & DI will be auto incremented while string instructions are executed. (DF) 1 SI & DI will be auto decremented while string instructions are executed. (IF) 0 (IF) 1
CF CF CF
DF
STD
DF IF IF
39
CLI STI
Compare Instruction, CMP
Mnemo Meaning nic CMP Compare Format CMP D,S Operation Flags Affected
(D) (S) is used in CF, AF, OF,
setting or resetting the PF, SF, ZF flags
Allowed Operands (D) = (S) (D) > (S) ; ZF=1 ; ZF=0, CF=0
Destination Register Register Memory Register Memory Accumulator Source Register Memory Register Immediate Immediate Immediate
40
(D) < (S)
; ZF=0, CF=1
String?
An array of bytes or words located in memory Supported String Operations Copy (move, load) Search (scan) Store Compare
41
String Instruction Basics
Source DS:SI, Destination ES:DI You must ensure DS and ES are correct You must ensure SI and DI are offsets into DS and ES respectively Direction Flag (0 = Up, 1 = Down)
CLD - Increment addresses (left to right) STD - Decrement addresses (right to left)
42
String Instructions
Instruction prefixes
Prefix
Used with
Meaning
REP
MOVS STOS
Repeat while not end of string CX 0 Repeat while not end of string and strings are equal. CX 0 and ZF = 1
REPE/REPZ
CMPS SCAS
REPNE/REP NZ
CMPS SCAS
Repeat while not end of string and strings are not equal. CX 0 and ZF = 0 43
Instructions
MnemoNic MOVS meaning format Operation Flags effect -ed
Move string DS:SI ES:DI Compare string DS:SI ES:DI
MOVSB/ ((ES)0+(DI)) ((DS)0+(SI)) none MOVSW (SI) (SI) 1 or 2 (DI) (DI) 1 or 2 CMPSB/ Set flags as per CMPSW ((DS)0+(SI)) - ((ES)0+(DI)) (SI) (SI) 1 or 2 (DI) (DI) 1 or 2 All status flags
CMPS
44
MnemoNic SCAS
meaning Scan string AX ES:DI
format SCASB/ SCASW
Operation Set flags as per (AL or AX) - ((ES)0+(DI)) (DI) (DI) 1 or 2 (AL or AX) ((DS)0+(SI)) (SI) (SI) 1 or 2
LODS
Load string LODSB/ DS:SI AX LODSW
STOS
Store string STOSB/ ES:DI AX STOSW
((ES)0+(DI)) (AL or A) 1 or 2 (DI) (DI) 1 or 2
45
Branch group of instructions
Branch instructions provide lot of convenience to the programmer to perform operations selectively, repetitively etc. Branch group of instructions
Conditional jumps
Unconditional jump
Iteration instructions
CALL instructions
Return instructions
46
SUBROUTINE & SUBROUTINE HANDILING INSTRUCTIONS
Main program
Subroutine A First Instruction Call subroutine A Next instruction
Return Call subroutine A
Next instruction
47
A subroutine is a special segment of program that can be called for execution from any point in a program. An assembly language subroutine is also referred to as a procedure. To branch a subroutine the value in the IP or CS and IP must be modified. After execution, we want to return the control to the instruction that immediately follows the one called the subroutine i.e., the original value of IP or CS and IP must be preserved. Execution of the instruction causes the contents of IP to be saved on the stack. (this time (SP) (SP) -2 ) A new 16-bit (near-proc, mem16, reg16 i.e., Intra Segment) value which is specified by the instructions operand is loaded into IP. Examples: CALL 1234H
CALL BX CALL [BX]
48
Near call (Intra Segment)
PUSH IP New values are loaded into IP given by the operand. After execution POP IP Far-proc Memptr32
49
Far call (Inter Segment)
At starting CS and IP placed in a stack. New values are loaded in to CS and IP given by the operand. After execution original CS, IP values placed as it is. Far-proc Memptr32
These two words (32 bits) are loaded directly into IP and CS with execution at CALL instruction.
First 16 IP
Next 16 CS
50
Mnem- Meaning onic
CALL
Format
Operation
Flags Affected
Subroutine CALL operand Execution continues from none call the address of the subroutine specified by the operand. Information required to return back to the main program such as IP and CS are saved on the stack.
Operand Near-proc
Far proc
Memptr 16 Regptr 16 Memptr 32
51
RETURN
Every subroutine must end by executing an instruction that returns control to the main program. This is the return (RET) instruction. (this time (SP) (SP)+2 )
Mnem Meaning -onic RET Return
Format
Operation
Flags Affected to the main None by restoring IP for far-proc). If is present, it is the contents of
RET or Return RET operand program (and CS operands added to SP.
Operand None Disp16
52
LOOP Instruction contd.
General format : LOOP r8 ; r8 is 8-bit signed value.
It is a 2 byte instruction.
Used for backward jump only. Maximum distance for backward jump is only 128 bytes. LOOP AGAIN is almost same as: DEC CX JNZ AGAIN
LOOP instruction does not affect any flags.
53
Mnemonic meaning LOOP Loop
format Loop short-label
Operation (CX) (CX) 1 Jump to location given by short-label if CX 0 (CX) (CX) 1 Jump to location given by short-label if CX 0 and ZF=1 (CX) (CX) 1 Jump to location given by short-label if CX 0 and ZF=0
LOOPE/ LOOPZ
Loop while equal/ loop while zero
LOOPE/LOOPZ short-label
LOOPNE/ Loop while LOOPNZ not equal/ loop while not zero
LOOPNE/LOOPNZ short-label
54
Control flow and JUMP instructions
Unconditional Jump
Part 1
JMP AA
Part 2
Unconditional JMP Skipped part
Part 3 AA XXXX
Next instruction
JMP unconditional jump JMP Operand
55
Unconditional Jump Unconditional Jump Instruction Near Jump or Far Jump or
Intra segment Jump Inter segment Jump (Jump within the segment) (Jump to a different segment)
Is limited to the address with in the current segment. It is achieved by modifying value in IP Operands
Short label Near label Far label Memptr16 Regptr16 memptr32
Permits jumps from one code segment to another. It is achieved by modifying CS and IP
Inter Segment Jump
Inter Segment Jump
56
Conditional Jump
Part 1
Jcc AA Part 2 NO
Conditional Jump
condition
YES
XXXX
Skipped part
Part 3
AA XXXX Next instruction
57
Conditional Jump instructions
Conditional Jump instructions in 8086 are just 2 bytes long. 1-byte opcode followed by 1-byte signed displacement (range of 128 to +127).
Conditional Jump Instructions
Jumps based on a single flag
Jumps based on more than one flag
58
TYPES Mnemonic JA JAE JB JBE meaning Above Above or Equal Below Below or Equal condition CF=0 and ZF=0 CF=0 CF=1 CF=1 or ZF=1
JC
JCXZ JE JG JGE
Carry
CX register is Zero Equal Greater Greater or Equal
CF=1
(CF or ZF)=0 ZF=1 ZF=0 and SF=OF SF=OF
JL
Less
(SF XOR OF) = 1
59
Mnemonic
meaning
condition
JLE
JNA JNAE JNB JNBE
Less or Equal
Not Above Not Above nor Equal Not Below Not Below nor Equal
((SF XOR OF) or ZF) = 1
CF =1 or Zf=1 CF = 1 CF = 0 CF = 0 and ZF = 0
JNC
JNE JNG JNGE JNL
Not Carry
Not Equal Not Greater
CF = 0
ZF = 0 ((SF XOR OF) or ZF)=1
Not Greater nor Equal (SF XOR OF) = 1 Not Less SF = OF
60
Mnemonic
JNLE JNO JNP
meaning
Not Less nor Equal Not Overflow Not Parity OF = 0 PF = 0
condition
ZF = 0 and SF = OF
JNZ
JNS JO JP
Not Zero
Not Sign Overflow Parity
ZF = 0
SF = 0 OF = 1 PF = 1
JPE
JPO JS JZ
Parity Even
Parity Odd Sign Zero
PF = 1
PF = 0 SF = 1 ZF = 1
61
Jumps Based on a single flag
JZ JNZ JS JNS JC JNC JP r8 ;Jump if zero flag set to 1 (Jump if result is zero) r8 ;Jump if Not Zero (Z flag = 0 i.e. result is nonzero) r8 ;Jump if Sign flag set to 1 (result is negative) r8 ;Jump if Not Sign (result is positive) r8 ;Jump if Carry flag set to 1 r8 ;Jump if No Carry
There is no jump based on AC flag
r8 ;Jump if Parity flag set to 1 (Parity is even)
JNP JO JNO
r8 ;Jump if No Parity (Parity is odd) r8 ;Jump if Overflow flag set to 1 (result is wrong) r8 ;Jump if No Overflow (result is correct)
62
JZ r8 ; JE (Jump if Equal) also means same.
JNZ r8 ; JNE (Jump if Not Equal) also means same.
JC r8 ;JB (Jump if below) and JNAE (Jump if Not Above or Equal) also mean same.
JNC r8 ;JAE (Jump if Above or Equal) and JNB (Jump if Not Above) also mean same. JZ, JNZ, JC and JNC used after arithmetic operation JE, JNE, JB, JNAE, JAE and JNB are used after a compare operation.
JP r8 ; JPE (Jump if Parity Even) also means same. JNP r8 ; JPO (Jump if Parity Odd) also means same.
63
Examples for JE or JZ instruction
Ex. for forward jump (Only examples for JE given) CMP SI, DI
JE SAME
Should be <=127 bytes ADD CX, DX ;Executed if Z = 0
:
:
(if SI not equal to DI)
SAME: SUB BX, AX
;Executed if Z = 1
(if SI = DI)
64
Examples for JE or JZ instruction
Ex. for backward jump BACK: SUB BX, AX ; executed if Z = 1
Should be <= 128 bytes
:
: CMP SI, DI JE BACK ADD CX, DX
(if SI = DI)
;executed if Z = 0 (if SI not equal to DI)
65
Jumping beyond -128 to +127?
Requirement CMP SI, DI JE SAME What if >127 bytes ADD CX, DX :
Then do this! CMP SI, DI JNE NEXT JMP SAME NEXT: ADD CX, DX
:
SAME: SUB BX, AX
:
:
SAME: SUB BX, AX
Range for JMP (unconditional jump) can be +215 = + 32K JMP instruction discussed in detail later
66
Terms used in comparison
Above and Below used for comparing Unsigned nos. Greater than and less than used with signed numbers. All Intel microprocessors use this convention. 95H is above 65H 95H is less than 65H Unsigned comparison - True Signed comparison True 95H is negative, 65H is positive Unsigned comparison - True
65H is below 95H
65H is greater than 95H
Signed comparison -
True
67
Jump on multiple flags
Conditional Jumps based on more than one flag are used after a CMP (compare) instruction.
JBE or JNA
Jump if Below or Equal Jump if Not Above
Jump if Cy = 1 OR Z= 1
No Jump if Cy = 0 AND Z = 0
Ex. CMP BX, CX
Below OR Equal
Surely Above
JBE BX_BE
BX_BE (BX is Below or Equal) is a symbolic location
68
Jump on multiple flags contd.
JNBE or JA
Jump if Not (Below or Equal) Jump if Above
Jump if Cy = 0 AND Z= 0 Surely Above
No Jump if Cy = 1 OR Z = 1 Below OR Equal
Ex. CMP BX, CX JA BXabove
BXabove (BX is above) is a symbolic location
69
Jump on multiple flags contd.
JLE or JNG Jump if Less than OR Equal Jump if Not Greater than Jump if S = 1 AND V = 0 (surely negative) OR (S = 0 AND V = 1) (wrong answer positive!) OR Z = 1 (equal) i.e. S XOR V = 1 OR Z = 1 No Jump if S = 0 AND V = 0 (surely positive) OR (S = 1 AND V = 1) (wrong answer negative!) AND Z = 0 (not equal) i.e. S XOR V = 0 AND Z = 0
70
Jump on multiple flags contd.
JNLE or JG Jump if Not (Less than OR Equal) Jump if Greater than Jump if S = 0 AND V = 0 (surely positive) OR (S = 1 AND V = 1) (wrong answer negative!) AND Z = 0 (not equal) i.e. S XOR V = 0 AND Z = 0 No Jump if S = 1 AND V = 0 (surely negative) OR (S = 0 AND V = 1) (wrong answer positive!) OR Z = 1 (equal) i.e. S XOR V = 1 OR Z = 1
71
Jump on multiple flags contd.
JL or JNGE Jump if Less than Jump if Not (Greater than OR Equal) Jump if S = 1 AND V = 0 (surely negative) OR (S = 0 AND V = 1) (wrong answer positive!) i.e. S XOR V = 1
When S = 1, result cannot be 0
No Jump if S = 0 AND V = 0 (surely positive) OR (S = 1 AND V = 1) (wrong answer negative!) i.e. S XOR V = 0
When S = 0, result can be 0
72
Jump on multiple flags contd.
JNL or JGE Jump if Not Less than Jump if Greater than OR Equal Jump if S = 0 AND V = 0 (surely positive) OR (S = 1 AND V = 1) (wrong answer negative!) i.e. S XOR V = 0
When S = 0, result can be 0
No Jump if S = 1 AND V = 0 (surely negative) OR (S = 0 AND V = 1) (wrong answer positive!) i.e. S XOR V = 1
When S = 1, result cannot be 0
73
Intra segment indirect Jump
Near Indirect Jump is uncommon. Instruction length: 2 or more bytes Range: complete segment
Ex.1: JMP DX If DX = 1234H, branches to CS:1234H 1234H is not signed relative displacement Ex. 2: JMP wordptr 2000H[BX] BX 1234H DS:3234H 5678H DS:3236H AB22H Branches to CS:5678H
74
Far Jump
Far Jump
Direct Jump (common) 5 bytes EA,2 byte offset, 2 byte segment Range: anywhere
Indirect Jump (uncommon)
2 or more bytes Starting with FFH Range: anywhere
3 Near Jump and 2 Far Jump instructions have the same mnemonic JMP but different opcodes
75
Inter segment Direct Jump
Also called Far Direct Jump It is the common inter segment jump scheme It is a 5 byte instruction 1 byte opcode (EAH) 2 byte offset value 2 byte segment value
Ex. JMP Far ptr LOC
76
Inter segment Indirect Jump
Instruction length depends on the way jump location is specified It can be a minimum of 2 bytes
Ex. JMP DWORD PTR 2000H[BX]
77
Inter segment Indirect Jump
Also called Far Indirect Jump It is not commonly used Instruction length is a minimum of 2 bytes. It depends on the way jump location is specified Ex. JMP DWORD PTR 2000H[BX] BX 1234H Branches to ABCDH:5678H DS:3234H DS:3236H 5678H ABCDH It is a 4-byte instruction
78
Machine control instructions
HLT instruction HALT processing
NOP instruction this instruction simply takes up three clock cycles and does no processing. to provide delays in between instructions.
ESC instruction
coprocessor instruction 6-bit opcode
79
Machine control instructions contd
LOCK instruction
this is a prefix to an instruction. Locks the bus Ex: LOCK XCHG [SI], AL
WAIT instruction
this instruction takes 8086 to an idle condition.
80
Interrupt instructions
INT instruction: INT type It does the following 1. PUSHF 2. PUSH CS 3. PUSH IP 4. get new CS and IP new CS = type X 4 + 2 new IP = type X 4 Type can vary from 0 to 255.
81
Interrupt instructions
INTO
82