An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
-
Author
george-datcu -
Category
Documents
-
view
224 -
download
0
Embed Size (px)
Transcript of An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 1/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 1 -
Data transfer instructions and strings
operations for Intel x86 (IA-32) and
compatible processors
1. Paper’s purposeThis paper’s purpose is to get you familiar with the basic and complex data transfer instructions and the
specific addressing mechanisms of Intel x86 and compatible processors.
2. Instruction summary
We convene upon the following notations:
s: source;d: destination;
AL|AX: default accumulator (8 or 16 bits);mem: the content of a memory location or two successive memory locations addressed through
one of the permitted addressing modes for data memory (except immediate
addressing);mem16: the content of two successive memory locations addressed through one of the permitted
addressing modes for data memory (except immediate addressing);mem32: the content of four successive memory locations addressed through one of the permitted
addressing modes for data memory (except immediate addressing);r|r i|r j: a common 8 bit or 16 bit register (except segment registers);
r8: an 8 bit register (except segment registers);
r16: a 16 bit register (except segment registers);rs: a segment register;
data: an 8 or 16 bit operand coded in the instruction format (immediate addressing);data8: an 8 bit operand coded in the instruction format (immediate addressing);
data16: a 16 bit operand coded in the instruction format (immediate addressing);
disp8: an 8 bit displacement (coded in the instruction format);
disp16: a 16 bit displacement (coded in the instruction format);
adr : a complete, 16 bit address;
adr8: a short, 8 bit address;adr32: a logical, 32 bit address;
port: the address (index) of an input/output (8 bit) port
tip: an 8 bit operand coded in the instruction format that specifies the type of an interrupt;
nrcel: the number of cells that an operand can be shifted or rotated with;AE: effective address;
Flags notations:
x: the flag’s value changes according to the instruction result;
1: the flag is unconditionally set;
0: the flag is unconditionally reset;
?: the flag’s value changes unpredictably;
blank: the flag’s value is not modified by the instruction;

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 2/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 2 -
Number of states calculus:
cAE – effective address calculus time (measured in number of states):
direct addressing:AE = disp8|disp16 6 states
indexed addressing:
AE = (SI)|(DI) + disp8|disp16 9 statesindirect implicit addressing:
AE = (SI)|(DI) 5 states
direct base relative addressing (no displacement):AE = (BX) 5 states
direct base relative addressing (with displacement):
AE = (BX) + disp8|disp16 9 states
indexed base relative addressing:AE = (BX) + (SI)|(DI) + disp8|disp16 12 states
implicit base relative addressing:
AE = (BX) + (SI)|(DI) 8 statesdirect stack addressing (no displacement):
AE = (BP) 5 states
direct stack addressing (with displacement):AE = (BP) + disp8|disp16 9 states
indexed stack addressing:AE = (BP) + (SI)|(DI) + disp8|disp16 12 states
implicit stack addressing:AE = (BP) + (SI)|(DI) 8 states
for any segment redirect 2 more states have to be added
2.1 Data transfer instructions
Copies a byte or OF DF IF TF SF ZF AF PF CF MOV d,s word from source to
destination
General formal semantic description: (d) (s).
Operands Example Formal semantic description
r, data MOV BX,ALFA (BX) ALFA
mem, data MOV [BP+DI],55H ((SS)0H + (BP) + (DI)) 55H
AL|AX, mem MOV AX,[SI] (AL) ((DS)0H + (SI)),
(AH) ((DS)0H + (SI) + 1)
mem, AL|AX MOV [BX+SI+10H],AL ((DS)0H + (BX) + (SI) + 10H) (AL)
r1, r2 MOV AX,SP (AX) (SP)
r, mem MOV BH,[BX+1000H] (BH) ((DS)0H + (BX) + 1000H)
mem, r MOV [2000H],DL ((DS)0H + 2000H) (DL)
rs*, r16 MOV ES,CX (ES) (CX)
rs*, mem16 MOV SS,[DI] (SS) ((DS)0H +(DI)+1) ((DS)0H + (DI))
r16, rs MOV CX,CS (CX) (CS)
mem16, rs MOV [SI],DS ((DS)0H +(SI)+1) ((DS)0H+(SI))(DS)
* any segment register except CS

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 3/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 3 -
Push (source) on OF DF IF TF SF ZF AF PF CF
PUSH s stack
General formal semantic description:(SP) (SP) - 2
((SS)0H + (SP) + 1)
(s)h
((SS)0H + (SP)) (s)l
Operands Example Formal semantic description
r16 PUSH BP (SP) (SP) - 2
((SS)0H+(SP)+1) ((SS)0H+(SP)) (BP)
mem16 PUSH [DI+100H] (SP) (SP) - 2
((SS)0H+(SP)+1) ((DS)0H +(DI) +101H)
((SS)0H + (SP)) ((DS)0H +(DI) +100H)
rs PUSH SS (SP) (SP) - 2
((SS)0H+(SP)+1) ((SS)0H+(SP)) (SS)
Push the flags OF DF IF TF SF ZF AF PF CF
PUSHF register on stack
Formal semantic description:(SP) (SP) - 2
((SS)0H + (SP) + 1) (F)h
((SS)0H + (SP)) (F)l
Pop from stack OF DF IF TF SF ZF AF PF CF
POP d (to destination)
General formal semantic description:(d)l ((SS)0H + (SP))
(d)h ((SS)0H + (SP) + 1)
(SP) (SP) + 2
Operands Example Formal semantic description
r16 POP CX (CL) ((SS)0H + (SP))
(CH) ((SS)0H + (SP) + 1)
(SP) (SP) + 2
mem16 POP [F0F0H] ((DS)0H +F0F0H) ((SS)0H + (SP))
((DS)0H +F0F1H)((SS)0H + (SP) + 1)
(SP) (SP) + 2
rs
(except CS)
POP SS (SS) ((SS)0H+(SP)+1) ((SS)0H+(SP))
(SP) (SP) + 2

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 4/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 4 -
Pop from stack to OF DF IF TF SF ZF AF PF CF
POPF flags register x x x x x x x x x
Formal semantic description:(F)l ((SS)0H + (SP))
(F)h ((SS)0H + (SP) + 1)(SP) (SP) + 2
OF DF IF TF SF ZF AF PF CF
XCHG d,s Exchange values
General formal semantic description:
(d) (s)
Operands Example Formal semantic description
r16 XCHG DX
XCHG AX
(AX) (DX)
(AX) (AX) NOP
r1, r2 XCHG CH,CL (CH) (CL)
r, mem XCHG BX,[BX+DI] (BL) ((DS)0H + (BX) + (DI))
(BH) ((DS)0H + (BX) + (DI) + 1)
OF DF IF TF SF ZF AF PF CF
XLAT Translate byte
Formal semantic description:
(AL) ((DS)0H + (BX) + (AL))
OF DF IF TF SF ZF AF PF CF
LAHF Load flags into AH
Formal semantic description:
(AH) (F)l
Store AH in the OF DF IF TF SF ZF AF PF CF
SAHF flags register (F) x x x x x
Formal semantic description:
(F)l (AH)

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 5/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 5 -
Input from port OF DF IF TF SF ZF AF PF CF
IN d,s (to accumulator)
General formal semantic description:(AL) | (AX)(s).
Operands Example Formal semantic description
AL|AX, port IN AL,0FH (AL) (0FH)
AL|AX, DX IN AX,DX (AX) ((DX) + 1) ((DX))
Output to port OF DF IF TF SF ZF AF PF CF
OUT d,s (from accumulator)
General formal semantic description:
(d) (AL) | (AX).
Operands Example Formal semantic description
port, AL|AX OUT 10H,AL (10H) (AL)
DX, AL|AX OUT DX,AX ((DX) + 1) ((DX)) (AX)
Load register OF DF IF TF SF ZF AF PF CF
LDS d,s (destination) and
data segment (DS)
General formal semantic description:(r16) (mem32)l
(DS) (mem32)h
Operands Example Formal semantic description
r16, mem32 LDS SI,[10H] (SI) ((DS)0H + 11H) ((DS)0H + 10H)
(DS) ((DS)0H+13H) ((DS)0H + 12H)
Load register OF DF IF TF SF ZF AF PF CF
LES d,s (destination) and
extended data
segment (ES)
General formal semantic description:(r16) (mem32)l
(ES) (mem32)h
Operands Example Formal semantic description
r16, mem32 LES DI,[DI] (DI) ((DS)0H +(DI) +1) ((DS)0H +(DI))
(ES) ((DS)0H+(DI)+3)((DS)0H+(DI)+2)

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 6/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 6 -
Load register OF DF IF TF SF ZF AF PF CF
LEA d,s (destination) with
effective address
General formal semantic description:
(r16) AEof the memory location
Operands Example Formal semantic description
r16, mem16 LEA BX,[BX+DI+10H] (BX) (BX) + (DI) + 10H
physical addr.: AF = (DS)0H +(BX) +(DI) +10H
effective addr.: AE = (BX) +(DI) +10H
Note that only POPF and LAHF instructions modify the flag’s register!
2.2 String transfer instructions
These instructions use default sources and destinations:
source – in DS segment at the effective address stored in SI
destination – in ES segment at the effective address stored in DI
The string transfer instructions can be prefixed by the following repeatability prefixes:
Repeat OF DF IF TF SF ZF AF PF CF
REP (unconditionally)
string operation
Repeat while equal OF DF IF TF SF ZF AF PF CF
REPE | REPZ | while zero the
CMPS or SCAS
instruction
Operands No. of
states
Bytes Examples
9 1 REPE CMPSB
Repeat while not OF DF IF TF SF ZF AF PF CF
REPNE|REPNZ equal | while not
zero the CMPS or
SCAS instruction
Operands No. of
states
Bytes Examples
9 1 REPNE SCASW

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 7/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 7 -
String transfer instructions:
Copies the current OF DF IF TF SF ZF AF PF CF
MOVS component of the
source string into
the current
component of the
destination string
Operands No. of
states
Bytes Examples
18 1 MOVSB ;copies one byte
18 1 MOVSW ;copies one word
Obs.: MOVS can be prefixed by the repeatability prefix REP; this prefix adds 9 more states.
Formal semantic description:((ES)0H + (DI)) ((DS)0H + (SI))
[((ES)0H + (DI) + 1) ((DS)0H + (SI) + 1)]
if (DF) = 0 then
(DI) (DI) + N
(SI) (SI) + N
else
(DI) (DI) - N
(SI) (SI) - N , N=1 for byte copy
, N=2 for word copy.
Load string OF DF IF TF SF ZF AF PF CF
LODS Loads the current
string component
into the
accumulator
Operands No. of
states
Bytes Examples
12 1 LODSB ;loads one byte
12 1 LODSW ;loads one word
Formal semantic description:(AL) ((DS)0H + (SI))
| (AX) ((DS)0H + (SI) + 1)((DS)0H + (SI))
if (DF) = 0 then
(SI) (SI) + N
else
(SI) (SI) - N , N=1 for byte load
, N=2 for word load.

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 8/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 8 -
Store string OF DF IF TF SF ZF AF PF CF
STOS (stores the current
component of the
string in the
accumulator)
Operands No. of
states
Bytes Examples
11 1 STOSB ;stores one byte
11 1 STOSW ;stores one word
Obs.: STOS can be prefixed by the repeatability prefix REP; this prefix adds 9 more states.
Formal semantic description:
((ES)0H + (DI)) (AL)
| ((ES)0H + (DI) + 1) ((ES)0H + (DI)) (AX)
if (DF) = 0 then
(DI) (DI) + N
else
(DI) (DI) - N , N=1 for byte store
, N=2 for word store.
3. Assembly directives and reserved words in TASMBThe source code can also contain assembly directives. These directives are used by the
assembler and won’t be part of the resulted object code. Some of the most usual assembly directives
and their purpose are presented below:
ORG (Assign location counter) directive
o syntax: ORG addr o effect: Next instruction will have addr address.
DB (Define Byte) directive
o syntax: [symbol] DB [data[,data]]o effect: allocates one or more bytes and initializes them with the expression
values (if there are any). Symbol will have the value of the first allocated byte.
DW (Define Word) directive
o syntax: [symbol] DW [data[,data]]o effect: allocates one or more words (two byte words) and initializes them with
the expression values (if there are any). Symbol will have the value of the first
allocated word.
EQU (Create Symbol) directive
o syntax: symbol EQU expressiono effect: symbol will have the value obtained after evaluating the expression.
OFFSET (Offset of expression) operatoro syntax: OFFSET symbolo effect: returns the address stored by symbol.
BYTE PTR (Change type of variable) operator
o syntax: BYTE PTR symbolo effect: converts symbol to byte.
WORD PTR (Change type of variable) operator
o syntax: WORD PTR symbolo effect: converts symbol to word.

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 9/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 9 -
4. Recommended workflowIn order to better understand the functionality of each instruction presented in the previous chapters
three data transfer programs will be presented:
The first program exemplifies the MOV instruction and several memory addressing modes.
The second program exemplifies some stack mechanisms (saving register values and memory locations
in the stack and eventually restoring them) and the flags set, clear and complement instructions.
The third program exemplifies the string transfer instructions. It initializes some memory locations withdifferent strings and then copies them into another allocated memory location.You should write and assemble each program and then run it step by step using the disassembler tool
(AFD) noting, at each step, the processor status and its modifications.
Note that the numbers that appear at the start of each source code line are not part of the programs.They are only used to identify each source code line.
5. Exercises5.1 Launch TASMB and edit (E) the source file given in Appendix 1.5.2 Save (W) the source file as P2_1.asm and assemble it (don’t forget to enable the assembler options).5.3 Display the symbols list (S command) and write down the address of each symbol.
5.4 Quit TASMB.5.5 Launch AFD and load the program using the L command (L P2_1.com).
5.6 Execute the program, step by step (F2), and note the modifications of the involved registers andmemory locations (as indicated din Appendix 1).
5.7 Repeat exercises 5.1 to 5.6 for the second and the third programs (given in Appendix 2 and 3).

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 10/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 1 0 -
6. Appendixes
6.1 Appendix 1 – P2_1.asm source code
1 org 100h
2 mov bx, cs ;set the data segment equal
3 mov ds, bx ;to the code segment
4 mov ax, const ;copy immediate in accumulator5 mov dx, ax ;from the accumulator into DX
6 mov var, 89abh ;copy immediate in memory
7 mov ax, var ;from memory into the accumulator
8 mov ax, [var] ;(direct addressing)
9 mov ax, 140h ;copy immediate in accumulator
10 mov ax, [140h] ;from memory into AX
11 mov byte ptr var, ah ;from AH into memory
;(direct addressing)
12 mov bx, offset var ;load var’s address into BX
13 mov bp, bx ;copy BX into BP
14 mov si, 4 ;immediate into SI index register
15 mov al, [bx+si-2] ;from memory into AX
;(indexed base relative addressing)
16 mov di, 2 ;immediate into DI index register
17 mov [bp+di], dl ; from DL into memory
;(implicit stack addressing)
18 mov [bp][si], al ;from AL into memory
;(implicit stack addressing)
19 mov var2, 11h ;store 011h at ‘var2’ address in
;memory
;(immediate addressing)
20 mov word ptr var2, 3456h ;store 034h and 056h values at
;‘var2’ and ‘var2’+1 addresses in
;memory (immediate addressing)
21 int 20h
22 var dw 0
23 const equ 0abcdh
24 var2 db 0
Please visualize and note the modifications of the specified registers, flags and memory locations after
executing the indicated instructions (before executing any instruction please set the start address DS:13F for
the second memory zone):
instructions: modifications to be noted in:2-3 CS, BX and DS.
4 AX and DX.
6 memory at the address ‘var ’.7-10 AX and the instructions codes.11 memory at the address ‘var ’.12-13 BX and BP.
14 SI.15 AL and the memory at BX+SI-2 address.16 DI.17-20 DL, AL, DX and the memory.

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 11/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 1 1 -
6.2 Appendix 2 – P2_2.asm source code
1 org 100h
2 mov bx, cs ;set the data segment equal
3 mov ds, bx ;to the code segment
4 mov temp, 0aabbh ;store 0aabbh at the addresses
;‘temp’ and ‘temp’+1 in memory
5 mov dx, 0ccddh ;store 0ccddh in DX register
6 push dx ;save DX in stack
7 push temp ;save the two memory locations with
;the addresses ‘temp’ and ‘temp’+1
;in stack
8 xchg dx, temp ;exchange the value in DX with the
;value stored in memory
9 pop temp ;restore the value of the locations
;at addresses ‘temp’ and ‘temp’+1
10 pop dx ;restore DX
11 mov ah, 11010101b ;load 0d5h in the accumulator
12 sahf ;store AH in the flags register
13 clc ;clear carry flag14 stc ;set carry flag
15 cmc ;complement carry flag
16 lahf ;load AH with the flags register
17 int 20h
18 temp dw ?
Please visualize and note the modifications of the specified registers, flags and memory locations after executing the indicated instructions (before executing any instruction please set the start address DS:124 for the second memory zone):
instructions: modifications to be noted in:4-5 DX and the memory address temp.6-7 SP and the stack.
8 DX and the memory address temp.
9-10 SP, DX, the stack and the memory address temp.
11-12 AL and the flags.13-15 The carry flag: CF.
16 The flags and AL.

7/30/2019 An2 Derivat.ro Arhitectura-microprocesoarelor AMP Lab2 Eng 7326
http://slidepdf.com/reader/full/an2-derivatro-arhitectura-microprocesoarelor-amp-lab2-eng-7326 12/12
“Politehnica” University of Bucharest Microprocessors’ Architecture – Lab guide
Electronics, Telecommunications and Information Technology Faculty Paper 2
© Corneliu Burileanu
- 1 2 -
6.3 Appendix 3 – P2_2.asm source code
1 org 100h
2 mov bx, cs ;set the data segment equal
3 mov ds, bx ;to the code segment
4 mov bx, 6000h ;set the ES segment at 6000h
5 mov es, bx
6 mov si, offset source ;load the start addresses of source
7 mov di, offset dest ;and dest strings into SI and DI
8 lodsb ;load the value at address DS:SI
; in AL
9 stosb ;store AL in memory at address
;ES:DI
10 movsb ;transfer one byte from source to
11 movsb ;dest – two times
12 mov di, 5+offset dest ;load the address of the fifth
;element of the dest string in DI
13 mov si, offset source+5 ;load the address of the fifth
;element of the sourc string in SI
14 std ;set the direction flag DF15 movsw ;transfer one byte from source to
16 movsw ;dest – two times
17 cld ;clear direction flag DF
18 lea si, source1 ;load the effective addresses of
19 lea di, dest ;source1 and dest strings
20 mov cx, dest-source1 ;load the length of source1 in CX
21 repnz movsb ;copy source1 to dest
22 int 20h
23 source db 'example '
;data definition area.
24 source1 db 'test string'
25 dest db 10 dup(?)
Please visualize and note the modifications of the specified registers, flags and memory locations after executing the indicated instructions. Before executing any instruction please set the start addresses for the twomemory zones. In order to visualize the source string you should set the first memory zone with the segment
register DS and the effective address noted in TASMB. In order to visualize the dest string you should set the
second memory zone with the segment register ES and the effective address noted in TASMB.
instructions: modifications to be noted in:4-5 BX and ES.
6-7 SI and DI.8-9 AL, DF, SI, DI and the memory at source and dest addresses.10-11 DF, SI, DI, the memory.
12-13 SI, DI.14 DF.
15-16 DF, SI, DI, the memory.17 DF.
18-20 SI, DI, CX.
21 DI, SI, the memory.