You are on page 1of 30

BRANCHING

INSTRUCTIONS OF 8086
Classifications
 Type of Branch
 Branch with return (CALL, RET, IRET)
 Branch without return (JMP, JNC, JO, JPE, JAE)
 Conditional Branch (JNC, JO, JPE, JAE)
 Unconditional Branch (JMP)

 Range of Branch
 Intrasegment (NEAR/SHORT Branch)
 Only IP is updated
 Intersegment (FAR Branch)
 Both CS and IP are updated

 Addressing Mode
 Direct (FAR, Near/short)
 Intersegment Range (CSSBA16, IPEA16)
 Intrasegment Range ( IPIP+disp16 or IPIP+sign bit extended(disp8) (Relative branch)
 Indirect (No relative branch)
 Intersegment Range (CSSBA16, IPEA16)
 Intrasegment Range ( IPEA16)
Note

 Conditional Branch instructions are always of:


 Intrasegment
 Direct Short
 Unconditional Branch instructions can be:
 Direct or Indirect type, intersegment/intrasegment branch
 For Intrasegment branch the branching address can be specified for short or near
range
 Short Branch is a special case of Near Branch
Examples of different addressing modes
 Intersegment Direct
 JMP EA16, SBA16
 IP EA16
 CSSBA16
 Intersegment Indirect
 JMP M32 (JMP DWORD PTR [BX])
 IPLSB M and IPMSB M+1
 CSLSB M+2 and CSMSB M+3
 Intrasegment Direct short
 JMP disp8 (JMP short label)
 IPIPold+Sign bit extended (disp8)
 Intrasegment Direct Near
 JMP disp16 (JMP Near PTR label)
 IP IPold + disp16
 Intrasegment Indirect Near
 JMP R16 or JMP M16 (JMP BX or JMP Word Ptr [BX])
 IPR16 OR IPM16
Conditional JMP instructions
 Only Instra-segment short Flags checking types Comparison of Unsigned Nos
type (CF, SF, ZF, PF, OF) (Above/Below/Equal)
 IPIP + sign bit Instruction Branching Instruction Branching
extended (disp8) condition condition
JC CF=1 JA/JNBE CF=0 & ZF=0
JCXZ short label JNC CF=0 JAE/JNB CF=0
Jump if CX=0
JS SF=1 JB/JNAE CF=1
JNS SF=0 JBE/JNA CF=1 OR ZF=1
JZ ZF=1 Comparison of Signed Nos. (Greater than/Less
than/Equal to)
JNZ ZF=0
Instruction Branching condition
JP/JPE PF=1
JG/JNLE (SF XOR OF)=0 & ZF=0
JNP/JPO PF=0
JGE/JNL (SF XOR OF)=0
JO OF=1
JL/JNGE (SF XOR OF)=1
JNO OF=0
JLE/JNG (SF XOR OF)=1 OR ZF=1
Example
 Subtract the decimal contents of CL from AL and convert the result in sign
magnitude format
MOV AL, 09H
MOV CL, 15H
SUB AL, CL
DAS
JNC Skip_tensComp
MOV BL, 0
SUB BL, AL
MOV AL, BL
DAS
MOV AH, 01H
JMP end_code
Skip_tensComp: MOV AH, 00H
end_code: MOV AX, 4C00H
INT21H
Example: Compare given signed two numbers and flash an appropriate output string on simulator
window
data segment JNO skip_next
op1 db -3,127 lea dx, pkeyOverflow
mov ah, 9
pkeyL db " Second number is Lower than first number.$"
int 21h ; output string at ds:dx
pkeyH db " Second number is Higher than first number.$" skip_next: jnge skip_l
pkeyE db " Second number is Equal to first number.$" jg skip_h
pkeyOverflow db "Overflow Occurred during comparison.$“
ends lea dx, pkeyE
jmp disp_res
stack segment
dw 128 dup(0) skip_l:
ends lea dx, pkeyl
code segment jmp disp_res

start: skip_h: lea dx, pkeyH


; set segment registers:
mov ax, data disp_res: mov ah, 9
mov ds, ax int 21h ; output string at ds:dx

mov es, ax mov ax, 4c00h ; exit to operating system.


: Codes for this program int 21h
mov cx, word ptr op1 ends
cmp ch,cl end start ; set entry point and stop the
assembler.
CALL instruction

 Branches program control to the first instruction of a subroutine


 The address of next instruction after call instruction is saved in stack
 Updation of IP and/or CS is done
 Types:
 Near: Subprogram is located in the same code segment and only IP is updated
 FAR: Subprogram is located in a different code segment and both CS and IP are
updated
 Addressing Mode:
 Direct
 Indirect
Examples: Intra-segment Direct
data_seg segment ; add your code here
; add your data here! MOV AL, Byte Ptr OP1
 CALL MULT OP1 DW 0205H MOV BL, Byte Ptr OP1+1
OP2 DW ? CALL MULT
 IP  IP+MULT data_seg ends MOV OP2, AX
 Example Program (Simulator emu8086): MOV AX, 4C00h ; exit to
stack_seg segment operating system.
 To multiply contents of two dw 128 dup(0) INT 21h
memory locations tos label word
stack_seg ends MULT PROC NEAR
 The effective address of starting MUL BL
location of subroutine MULT is code_seg segment RET
0020H ASSUME CS: code_seg, MULT ENDP
DS:data_seg
 The value assigned to label MULT is start: code_seg ends
0008H ; set segment registers:
mov ax, data_seg end start ; set entry point
 The return address (IP) saved in
mov ds, ax and stop the assembler.
stack is 0018H
 The result obtained in AX is 000AH mov ax, stack_seg
mov ss, ax
mov sp, tos;
Examples: Intra-segment Indirect
data_seg segment ; add your code here
; add your data here! MOV AL, Byte Ptr OP1
 CALL Register16/memory16 OP1 DW 0205H MOV BL, Byte Ptr OP1+1
OP2 DW ? LEA BP, MULT
 CALL Register16 data_seg ends CALL BP
 IP  Register16 MOV OP2, AX
 CALL WORD PTR memory16 stack_seg segment mov ax, 4c00h ; exit to
dw 128 dup(0) operating system.
 IP  [memory16] and [memory 16+1] tos label word int 21h
stack_seg ends
MULT PROC NEAR
 Example Program (Simulator emu8086):
code_seg segment MUL BL
 To multiply contents of two memory ASSUME CS: code_seg, RET
locations DS:data_seg MULT ENDP
 The effective address of starting location start:
of subroutine MULT is 0022H ; set segment registers: code_seg ends
mov ax, data_seg
 The value moved into BP is 0022H
mov ds, ax end start
 The return address (IP) saved in stack is
001AH mov ax, stack_seg
 The result obtained in AX is 000AH mov ss, ax
mov sp, tos;
Examples
 Intrasegment Indirect:  Intersegment Indirect (Indirect FAR call)
 CALL Register16/memory16
 Calling the subroutine
 CALL Register16
 IP  Register16
 CALL DWORD PTR Memory32

 CALL WORD PTR memory16  Assembled as 3 bytes


 IP  [memory16] and [memory 16+1]  OPCODE (2 Byte) OPERAND (1 byte)
 CALL WORD PTR [BX]  Operation:
 Intersegment direct (Direct FAR call)  Save return address:
 Calling the subroutine  SP=SP-1, [SP]CSHB , SP=SP-1, [SP]CSlB ,
 CALL EA16, SBA16 [Without using assembler labels]  SP=SP-1, [SP]IPHB , SP=SP-1, [SP]IPlB
 CALL FAR PTR PROC_NAME [Using assembler labels]
 Update CS and IP with Branching address:
 Assembled as 5 bytes:
 CS[Memory32] and [Memory32+1]
 Opcode(1 Byte) EALB EAHB SBALB SBAHB
 IP[Memory32+2] and [Memory32+3]
 Current value of CS and IP pushed in stack (return address saved)
 IPEA16, CSSBA16
 Definition of subroutine in a different code segment
 Definition of subroutine in a different code segment
 PROC_NAME PROC FAR
 PROC_NAME PROC FAR
 //Code of procedure  //Code of procedure

 PROC_NAME ENDP  PROC_NAME ENDP


RET instructions

 Depending upon the type of procedure and the contents SP, the RET
instruction may be of four types
 Return within segment
 Return within segment adding 16 bit immediate displacement to the SP contents
(RET disp16)
 Return intersegment
 Return intersegment adding 16 bit immediate displacement to the SP contents (RET
disp16)
The INT n Instructions
 INT instructions are software calls for 8086 ISRs (In other words it creates
interrupts within a program)
 ‘n’ indicates the type of interrupts.
 There are 256 interrupts in 8086 from ‘type 0’ to ‘type FF’
 In order to call each of these 256 interrupts the value ‘n’ respectively varies from
00H-FFH (for example in INT 21H, the value of n is 21H).
 During execution of INT n the following things happen:
 Decrements the stack pointer by 2 and push the flags onto the stack
 Decrement the stack pointer by 2 and push the contents of CS onto the stack
 Decrement the stack pointer by 2 and push the contents of IP (i.e. the offset of next
instruction after INT n instruction) onto the stack
 Update IP with the 16 bit number present in memory with a physical address given by
n*4. For example, for INT 21H the new effective address to be loaded in IP will be read
from memory location: 21H*04H=00084H
 Update CS with the 16 bit number present in memory with a physical address given by
n*4+2. For example, for INT 21H the new effective address to be loaded in IP will be read
from memory location: 21H*04H+2=00086H
 Reset Both IF and TF. Other flags are not affected
The IRET Instruction
 The IRET instruction is used at the end of interrupt service procedure to
return the execution to the interrupted program.
 When IRET instruction is executed the following things take place:
 The saved value of IP (effective return address saved during execution of INT n
instruction) in stack is copied into IP register.
 The stored value of CS in stack is copied into CS register.
 The stored value of flags (saved earlier during execution of INT n instruction) in
stack memory are saved into the flag register
Interrupt vector table (IVT) Interrupt
type
Logical address
SBA=0000H
Memory

(n) EA=n * 4

 In the zeroeth segment of physical address TYPE 0 0000:0000 T0_BR_EALB

space (CS=0000H), Intel has reserved 1024 0000:0001 T0_BR_EAHB


(1 KB) locations for storing interrupt Vector 0000:0002 T0_BR_SBALB
table from effective address 0000H-03FFH. 0000:0003 T0_BR_SBAHB
 8086 has 256 interrupts, each interrupt type TYPE 1 0000:0004 T1_BR_EALB
require 2 components of logical address (EA IP
0000:0005 T1_BR_EAHB
and SBA) to specify the branching address 0000:0006 T1_BR_SBALB
for the interrupt service routine. CS
0000:0007 T1_BR_SBAHB
 16 bit EA of Branching location (2 Bytes) TYPE 2 0000:0008 T2_BR_EALB
 16 bits SBA of branching location (2 0000:0009 T2_BR_EAHB
Bytes) 0000:000A T3_BR_SBALB

 Each of these 4 byte branching information 0000:000B T4_BR_SBAHB


for each of 256 interrupt types are stored ---- ---- ----
sequentially in Interrupt vector Table. Thus TYPE 255 0000:03FC T255_BR_EALB
the maximum size of IVT is (256*4=1024 0000:03FD T255_BR_EAHB
Bytes or 1KB) 0000:03FE T255_BR_SBALB
0000:03FF T255_BR_SBAHB
Interrupt Structure of 8086
Interrupt INT instruction Interrupt name Nature of interrupting event Vector
executed address
TYPE 0 INT 00H (Intel Division by zero Caused by Internal hardware event, 00000H
predefined) Cannot be masked
TYPE 1 INT 01H (Intel Single step execution Caused by Internal software event, 00004H
predefined) Configured by TRAP flag
TYPE 2 INT 02H (Intel Non maskable Invoked by external hardware event 00008H
predefined) interrupt on NMI pin, NON-MASKABLE
INTERRUPT
TYPE 3 INT 03H (Intel Break point Interrupt Invoked by Internal software event 0000CH
predefined) by placing INT 3 instruction in
program.
TYPE 4 INT 04H (Intel OVERFLOW interrupt Invoked by Internal hardware event 00010H
predefined)
TYPE 5-TYPE31 INTEL RESERVED INTERRUPTS FOR FUTURE USE
TYPE 32-TYPE255 INT 20H – INT FFH USER DEFINED Invoked by Internal 00080H-
INTERRUPTS Caused by software/External hardware Events: 003FCH
Hardware or software • Internal software: Specifying INT
events x in user program
• External hardware: Using INTR Pin
• MASKABLE INTERRUPT (IF)
ITERATION CONTROL
INSTRUCTIONS
INSTRUCTIONS

 REP
 REPZ/REPE
 REPNZ/REPNE
 LOOP
 LOOPZ/LOOPE
 LOOPNZ/LOOPNE
LOOP disp8 A

A
L1: B Microprocessor
C Executes from B to D
D
LOOP L1
E
CX=CX-1

• Assuming A – E
instructions are all
single bytes. IS
• LOOP disp8 is a two CX==0?
byte instruction NO
• Value assigned to L1 is
-5 YES

Microprocessor will
1. If CX=N Iteration will be for N times (entry values for loop body is N to 1) Execute E
1. Cx=1, iteration for once
2. If CX=0, then iteration will be for 65536 times
3. Running condition: CX ≠ 0 E
4. Exit condition: CX = 0
LOOPZ disp8 A

Microprocessor
A
Executes from B to D
L1: B
(ZF is affected)
C
D
LOOPZ L1 NO IS
E ZF==1?
• Assuming A – E
instructions are all
CX=CX-1
single bytes.
• LOOPZ disp8 is a two
byte instruction IS
• Value assigned to L1 is CX==0? NO
-5
YES
1. Loop as long as ZF is 1 (ie the result of comparison of signed/unsigned
number satisfies equality condition) and CX ≠ 0
Microprocessor will
2. Running condition: (ZF==1 AND CX ≠ 0)
Execute E
3. Exit condition: (ZF==0 OR CX==0)
1. Special case: Loop will breakout while ZF remains at 1 but CX
becomes 0 E
4. May be used to compare for dissimilarity of two data sequence
LOOPNZ disp8 A

Microprocessor
A
Executes from B to D
L1: B
(ZF is affected)
C
D
LOOPNZ L1 NO IS
E ZF==0?
• Assuming A – E
instructions are all single
bytes. CX=CX-1
• LOOPNZ disp8 is a two
byte instruction
IS
• Value assigned to L1 is -5
CX==0? NO
YES
1. Loop as long as ZF is 0 (ie the result of comparison of signed/unsigned
number satisfies in-equality condition) and CX ≠ 0
Microprocessor will
2. Running condition: (ZF==0 AND CX ≠ 0)
Execute E
3. Exit condition: (ZF==1 OR CX==0)
1. Special case: Loop may breakout while ZF remains at 0 but CX
becomes 0 E
4. May be used to compare for similarity of two data sequence
REP (Prefix) Instruction
A
A
REP B
C
NO IS
CX==0?

Microprocessor will
• REP is a prefix instruction YES
Execute B
• The instruction prefixed will be executed repeatedly
as long as CX is not equal to zero
• If CX==0 THEN next instruction will be executed CX=CX-1
• To execute an instruction N no of times CX should be
populated with value N
• Nmin=0 and Nmax=65535 C
REPZ/REPE (Prefix) Instruction
A
A
REPZ B
C
NO IS
• REPZ is a prefix instruction CX==0?
• The instruction prefixed will be executed repeatedly
as long as (ZF==1 AND CX is not equal to zero) Microprocessor will
Execute B YES
• If (ZF==0 OR CX==0) THEN next instruction will be
(ZF is affected)
executed
• Special case: Iteration breaks out if ZF==1 but
CX==0 CX=CX-1
• Used with CMP/CMPS instruction to perform
repeated comparison for equal data elements of a
sequence and to break out in case of dissimilarity. C
(comparison of two strings and detect mismatch IS
position) ZF==1?
YES
• To execute an instruction N no of times CX should be
populated with value N
• Nmin=0 and Nmax=65535 NO
REPNZ/REPNE (Prefix) Instruction
A
A
REPNZ B
C
NO IS
• REPNZ is a prefix instruction CX==0?
• The instruction prefixed will be executed repeatedly
as long as (ZF==0 AND CX is not equal to zero) Microprocessor will
Execute B YES
• If (ZF==1 OR CX==0) THEN next instruction will be
(ZF is affected)
executed
• Special case: Iteration breaks out if ZF==0 but
CX==0 CX=CX-1
• Used with CMP/CMPS instruction to perform
repeated comparison for unequal data elements of
a sequence and to break out in case of similarity. C
(comparison of two strings and detect match IS
position) ZF==0 ?
YES
• To execute an instruction N no of times CX should be
populated with value N
• Nmin=0 and Nmax=65535 NO
STRING INSTRUCTIONS
Introduction
 String are sequences of data that mostly contains alphabetic characters
 Obtained from/Sent to IO devices for human interaction
 String instructions are special type of instructions those perform the following
on individual elements of a string:
 Copy a string from one place to other area in memory
 Compare two strings
 Scan a string for the occurrence of a given character
 Load characters of a string into accumulator for further processing
 Store the character present in accumulator into a given string
 The unique property of a string instruction (for ONE execution) is:
 It performs one of the primary operations mentioned in above points on only ONE
character of string/strings
 It then updates (increments/decrements) memory pointers to point to the next
character of the string.
 The direction of update is determined by the Decrement Flag (Direction Flag)
 If DF=1, memory pointers are decremented by one
 If DF=0 memory pointers are incremented by one
MOVS/MOVSB/MOVSW
 MOVSB/MOVSW: Copies a byte/word (that is a part of string) present in DMS
with effective address given in SI register TO a memory location in EMS with
effective address given in DI register

Physical address (source character) Physical address (destination location)

Source Destination
Byte/Word sized 8/16 BIT Byte/Word sized
character memory location

DS: SI ES: DI
SBA can also be obtained from:
CS/ES/SS
DF=0 DF=0
SI=SI+1(BYTE)/2(WORD) DI=DI+1(BYTE)/2(WORD)
DF=1 DF=1
SI=SI-1(BYTE)/2(WORD) DI=DI-1(BYTE)/2(WORD)
CMPS/CMPSB/CMPSW
 CMPSB/CMPSW: Compares a byte/word (that is a part of string) present in
DMS with effective addres given in SI register WITH a byte/word (that is a
part of string) present in EMS with effective address given in DI register and
UPDATES FLAGS as a result

Physical address (source character) Physical address (destination location)

X Y CF=0 and ZF=0,  X>Y


Byte/Word sized Byte/Word sized CF=1 and ZF=0,  X<Y
character character CF=0 and ZF=1,  X==Y
DS: SI ES: DI
SBA can also be obtained from:
CS/ES/SS
DF=0 DF=0
SI=SI+1(BYTE)/2(WORD) DI=DI+1(BYTE)/2(WORD)
DF=1 DF=1
SI=SI-1(BYTE)/2(WORD) DI=DI-1(BYTE)/2(WORD)
SCAS/SCASB/SCASW
 SCASB/SCASW: Compares a byte/word present in AL/AX WITH a byte/word
(that is a part of string) present in EMS with effective address given in DI
register and UPDATES FLAGS as a result

Physical address (source character) Physical address (destination location)

X Y CF=0 and ZF=0,  X>Y


Byte/Word sized Byte/Word sized CF=1 and ZF=0,  X<Y
character character CF=0 and ZF=1,  X==Y
AL/AX ES: DI

DF=0
DI=DI+1(BYTE)/2(WORD)
DF=1
DI=DI-1(BYTE)/2(WORD)
Flag manipulation and Processor control
instructions
 Flag manipulation instructions:
 CLC, CMC, STC, CLD, STD, CLI, STI
 Machine control instructions:

Instruction Description

WAIT Wait for Test input pin to go low

HLT Halt the processor

NOP No Operation

ESC Escape to external device like


NDP (Numeric co-processor)
LOCK Bus Lock prefix instruction

You might also like