Microprocessor System Design Omid Fatemi Instructions (1) (omid@fatemi.net) University of Tehran 1 Review • Flag instruction • ADD and ADC • A loop program • Data entering • MASM • Directives University of Tehran 2 Outline • Data transfer operations • Arithmetic operations • Logic operation • Control operations • String operations University of Tehran 3 MASM Program Example (another way to define segments) ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ; ; ; This is an example program. It prints the ; ; character string "Hello World" to the DOS standard output ; ; using the DOS service interrupt, function 9. ; ; ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; hellostk SEGMENT BYTE STACK 'STACK' ;Define the stack segment DB 100h DUP(?) ;Set maximum stack size to 256 bytes (100h) hellostk ENDS hellodat dos_print strng hellodat SEGMENT BYTE 'DATA' ;Define the data segment EQU 9 ;define a constant via EQU DB 'Hello World',13,10,'$' ;Define the character string ENDS hellocod START: SEGMENT BYTE 'CODE' ;Define mov ax, SEG hellodat mov ds, ax mov ah, dos_print mov dx,OFFSET strng int 21h mov ax, 4c00h int 21h ENDS END START hellocod the Code segment ;ax <-- data segment start address ;ds <-- initialize data segment register ;ah <-- 9 DOS 21h string function ;dx <-- beginning of string ;DOS service interrupt ;ax <-- 4c DOS 21h program halt function ;DOS service interrupt ; ‘END label’ defines program entry University of Tehran 4 Yet another way to define Segs ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ; Use .stack,.data,.code directives to define segment types ; ; ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; .stack 100h ; reserve 256 bytes of stack space .data dos_print EQU 9 strng DB 'Hello World',13,10,'$' ;define a constant ;Define the character string .code START: mov mov mov mov int mov int ax, SEG strng ds, ax ah, dos_print dx,OFFSET strng 21h ax, 4c00h 21h END START ;ax <-- data segment start address ;ds <-- initialize data segment register ;ah <-- 9 DOS 21h string function ;dx <-- beginning of string ;DOS service interrupt ;ax <-- 4c DOS 21h program halt function ;DOS service interrupt University of Tehran 5 Masm Assembler Directives end label end of program, label is entry point proc far|near begin a procedure; far, near keywords specify if procedure in different code segment (far), or same code segment (near) endp end of procedure page set a page format for the listing file title title of the listing file .code mark start of code segment .data mark start of data segment .stack set size of stack segment University of Tehran 6 Data Allocation Directives db define byte dw define word (2 bytes) dd define double word (4 bytes) dq define quadword (8 bytes) dt define tenbytes equ equate, assign numeric expression to a name Examples: db 100 dup (?) define 100 bytes, with no initial values for bytes db “Hello” define 5 bytes, ASCII equivalent of “Hello”. maxint equ 32767 count 10 * 20 equ ; calculate a value (200) University of Tehran 7 Data Transfer Instructions • Very Common Instruction: • Allowed Operands mov desti, source Destination Source Memory Accumulator Accumulator Memory Register Register Register Memory Memory Register Register Immediate Memory Immediate Seg. Reg. Register Seg. Reg. Memory Register Seg. Reg. Memory Seg. Reg. University of Tehran 8 Arithmetic University of Tehran 9 Arithmetic/Logic Instructions • Basic Mathematical Operations – Signed/Unsigned Integer Only – Default is 2’s Complement – Computes Result AND Modifies Status Flags • Logic Instructions – Bit Level – Word Level – Computes Results AND Modifies Status Flags University of Tehran 10 Arithmetic Instruction Summary add adc inc aaa daa sub sbb dec neg cmp das aas mul imul aam div idiv aad ax, ax, ax bx bx ax, ax, ax ax ax, bx bx cx cx cl cx bx ;axax+bx and set flags ;axax+bx+CF(lsb) and set flags ;axax+1 and set flags ;ASCII Adjust after Addition ;Decimal (BCD) Adjust after Addition ;axax-bx and set flags ;ax(ax-CF)-bx and set flags ;axax-1 ;ax(-1)*(ax) -- 2’s Complement ;Flags are set according to ax-bx ;Decimal (BCD) Adjust after Subtraction ;ASCII Adjust after Subtraction ;dx:ax ax * cx (unsigned) ;dx:ax ax * cx (2’s complement) ;ASCII Adjust after Multiplication ;alax/cl Quot. AND ahax/cl Rem. ;ax(dx:ax)/cx Quot. AND dx Rem. ;ASCII Adjust after Division University of Tehran 11 Addition Instruction Types add adc inc aaa daa ax, ax, ax Addition add al, add bx, add [bx], add cl, add al, add bx, add bx, bx bx ;axax+bx and set flags ;axax+bx+CF(lsb) and set flags ;axax+1 and set flags ;ASCII Adjust after Addition ;Decimal (BCD) Adjust after bl 35afh al [bp] [ebx] TEMP[di] [eax+2*ecx] ;alal+bl and set flags ;bxbx+35afh ;ds:(bx)ds:(bx)+al ;clcl+ss:(bp) ;alal+ds:(ebx) ;bxbx+ds:(TEMP+di) ;bxbx+ds:(eax+(2*ecx)) Scaled Index Addressing: 386+ ecx may contain 1, 2 , 4 only University of Tehran 12 Increment Examples inc bl ;blbl+1 and set flags inc BYTE PTR [bx] ;Byte at ds:(bx)ds:(bx)+1 New MASM Directive: BYTE POINTER 00ffh inc [bx] 00ffh inc 0000h [DATA1] ;Word at ds:(bx)ds:(bx)+1 0100h ;ds:(DATA1)ds:(DATA1)+1 University of Tehran 13 Add with Carry BX 1 1 AX DX 0 1 CX CF=1 BX CF add adc ax, bx, cx dx AX ;axax+cx and flags set ;bxbx+dx+CF(lsb) and flags set 33-bit Sum Present in CF:bx:ax University of Tehran 14 Decimal Adjust after Addition • For BCD Arithmetic • “Corrects” Result 0110 +0111 1101 6 7 13should be 0001 0011 (1101 is illegal BCD) •2 Digits/Word Intel Refers to as “Packed Decimal” •daa Uses Implicit Operand, al Register •Follows add, adc to “Adjust” University of Tehran 15 Decimal Adjust after Addition Example mov mov mov add daa mov mov adc daa mov dx, bx, al, al, 1234h 3099h bl dl cl, al, al, al bh dh ch, al ;dx1234 BCD ;bx3099 BCD ;al99 BCD ;alcdh illegal BCD, need 34+99=133 ;al33h (33 BCD) and CF=1 ;cl33 BCD ;al30 BCD ;al30h+12h+1=43h ;al43h (43 BCD) not illegal BCD this time ;cx=4333h BCD for 1234+3099 University of Tehran 16 ASCII Adjust after Addition • For Addition Using ASCII Encoded Numbers 30h through 39h Represent ‘0’ through ‘9’ • ax is Default Source and Destination for aaa 31 +39 6a ‘1’ ‘9’ ‘10’should be 3130h (6ah is incorrect ASCII result ‘j’) mov add aaa add ax, al, ax, 31h 39h ;ax0031h=‘1’ ;ax31h+39h=006ah=‘<nul>j’ ;ax0100h (this is BCD of result) 3030h ;Convert from BCD to ASCII ;ax0100h+3030h=3130h=‘10’ University of Tehran 17 Subtraction Instruction Types sub sbb dec neg cmp das aas ax, ax, ax ax ax, bx bx bx ;axax-bx and set flags ;ax(ax-CF)-bx and set flags ;axax-1 ;ax(-1)*(ax) - 2’s Complement ;Flag is set according to ax-bx ;Decimal (BCD) Adjust after Subtraction ;ASCII Adjust after Subtraction University of Tehran 18 Allowable Operands for add, sub Gen Reg Gen Reg + - Mem Loc Immediate Destination Source Gen Reg Mem Loc + Immediate University of Tehran 19 Subtract with Borrow, sbb CF CF sub sbb ax, bx, BX AX SI DI BX AX di si ;axax-di and CF gets borrow bit ;bx(bx-CF(lsb))-si and flags set 32-bit Difference Present in bx:ax CF Indicates If Difference is Negative University of Tehran 20 Multiplication • 8086/8088 One of First to Include mul/div Instruction • Allowable Operands: Bytes, Words, DoubleWords •Allowable Results: Words, DoubleWords, QuadWords •OF, CF Give Useful Information •AF, PF, ZF, SF Change but Contents Unpredictable •Multiplicand Always in al, ax, eax •mul - Unsigned Mnemonic •imul - Signed Mnemonic University of Tehran 21 Multiply Instructions • Product can be Twice the Size 23=6 (same size) 2 8 = 16 (double size, EXT) •OF=CF=0 means product is same size as result (faster) •OF=CF=1 means EXT product size (slower) •AF, PF, ZF, SF Contents Unpredictable mul mul mul imul imul bl bx ebx bl bx ;axal*bl, Unsigned ;dx:axbx*ax, Unsigned ;edx:eaxebx*eax, Unsigned ;axal*bl, Signed ;dx:axbx*ax, Signed imul ebx ;edx:eaxebx*eax, Signed University of Tehran 22 Special Immediate Multiply Instruction • 286+ • Uses imul Mnemonic but with 3 Operands first: 16-bit dest. register second: reg/mem location third: 8/16-bit immediate value •Always Performs Signed Multiplication •Product is Limited to 16-bits imul cx, dx, 12h ;cxdx*12h imul bx, [NUMBER], 12h ;bxds:(NUMBER)*12h University of Tehran 23 Division • 8, 16, 32 bit Operands (32 bit is 386+) • No Immediate Addressing Mode • No Flag Bits Change Predictably • Can Cause Two Types of Error: 1) Divide by 0 (Mathematically Undefined) 2) Divide Overflow (Wordlength Problem) • Operands: Divisor is Programmer Specified • Dividend is Implied • Quotient, Remainder Implied Size Dividend Quotient Remainder ax al ah 8 bits ax dx 16 bits dx:ax edx 32 bits edx:eax eax University of Tehran 24 Division Instruction Examples • idiv Signed and div Unsigned dividend / divisor = quotient, rmdr div cx ;dx:ax is divided by value in cx ;unsigned quotient is placed in ax ;positive remainder is placed in dx idiv ebx ;edx:eax is divided by value in ebx ;signed quotient is placed in eax ;remainder (ALWAYS same sign as ;dividend) is placed in edx University of Tehran 25 Logical Instructions University of Tehran 26 Logic Instruction Types not and or xor test shl sal shr sar ax ax, ax, ax, ax, ax, ax, ax, ax, BITWISE LOGICAL ;1’s Complement-Logical Invert bx ;Bitwise logical and operation bx ;Bitwise logical inclusive-or operation bx ;Bitwise logical exclusive-or operation fffh ;Bitwise and but result discarded 4 3 4 3 SHIFT ;Logical shift left ;Arithmetic shift left ;Logical shift right ;Arithmetic shift right rol ror rcl bx, 3 cx, 4 ax, 1 ROTATE ;Rotate left ;Rotate right ;Rotate left through carry rcr dx, 6 ;Rotate right through carry University of Tehran 27 Bit Level Logic and, or, xor, not, test, bt, btc, btc, btr, bts • Affect Status Flags as Follows: 1) Always Clears CF and OF 2) SF, ZF, AF, PF Change to Reflect Result • Common Usage: and ax, ax ;clear CF and OF xor ax, ax ;clear ax=CF=OF=PF=AF=SF=0 and ZF=1 ;does more than mov ax, 0h ;faster than push 00h then popf University of Tehran 28 Masking Operations (AND) XXXX XXXX (unknown word) 0000 1111 (mask word) 0000 XXXX (result) What if we wanted 1111 XXXX instead? EXAMPLE: Convert ASCII to BCD to Binary ;First convert to BCD - change 3235h into 0025h mov bx, 3235h ;bx ‘25’ and bx, 0f0fh ;bx0205h mov dx, bx ;dx0205h shl bh, 4 ;bh20h or bl, bh ; bl = bh or bl = 20 or 05 = 25h xor bh, bh ;zero out bh, so bx = 0025 (BCD value) ;Now convert to binary - change 3235h into 0019h mov al, dh ;al02h mov cl, 10 ;cl0ah mul cl ;ax = 2 * 0Ah = 14h (decimal value is 20) add al, dl ;al14h+05h=19h (decimal value is 25) University of Tehran 29 Bit Test Instruction, test • Same as and But Result is Discarded • Only Affects Flags (like cmp) • Use test for Single Bit and cmp for Byte, Word • ZF=1 if Tested Bit=0 and ZF=0 if Tested Bit=1 test al, 1 ;XXXX XXXX (AND) 0000 0001 test al, 128 ;XXXX XXXX (AND) 1000 0000 University of Tehran 30 Shifts shl shr sal sar - - - - Logical Shift Left CF REG 0 Logical Shift Right 0 REG CF Arithmetic Shift Left (same as logical) CF REG 0 Arithmetic Shift Right (sign bit is preserved) REG CF MSB University of Tehran 31 Simple Arithmetic Using Shifts ;Compute (-3)*VALUE Using Only Shifts and Adds mov mov shl add shl sub ax, bx, ax, ax, bx, ax, VALUE ax 2 bx 3 bx ;ax ;bx ;ax ;ax ;bx ;ax Word from memory with label VALUE Word from memory with label VALUE 4*VALUE 5*VALUE 8*VALUE (-3)*VALUE University of Tehran 32 Rotates rol - Rotate Left CF rcl ror rcr REG - Rotate Through Carry Left CF REG CF REG - Rotate Right - Rotate Through Carry Right CF REG University of Tehran 33 Example Using Rotates ;Multiply a 48-bit value in dx:bx:ax by 2 shl rcl rcl ax, bx, dx, 1 1 1 ;ax 2*ax ;bx 2*bx + CF(lsb) ;dx 2*dx + CF(lsb) ;End result is dx:bx:ax 2*(dx:bx:ax) • Operand for rotates and shifts can be either: 1) Immediate value 2) Quantity in cl University of Tehran 34 Program Control Instructions University of Tehran 35 Program Control Instructions •Generally modify CS:IP •Causes modification in execution sequence (of instructions) • When such a program flow change occurs: a) Instructions in the BIU inst. queue become invalid b) BIU directly fetches CS:IP instruction from memory c) While EU executes new instruction, BIU flushes/refills inst. queue • Classification a) Jumps - Unconditional control transfers (synchronous) b) Branches - Conditional control transfer c) Interrupts - Unconditional control transfers (asynchronous) d) Iteration - More complex type of branch University of Tehran 36 Control Instruction Summary jmp call ret hlt LABEL LABEL UNCONDITIONAL ;next instruction executed has LABEL ;next instruction executed has LABEL ;next instruction executed is after the call ;nothing executed until RESET signal loop LABEL loope/loopz LABEL loopne/loopnz ITERATION ;cx cx - 1, jump to LABEL if cx > 0 ;same as loop but ZF=1 also required ;same as loop but ZF=0 also required int into iret INTERRUPTS ;Invoke the int. handler specified by immed8 ;same as int but OF=1 also ;Return from interrupt handler <immed8> <immed8> CONDITIONAL to follow University of Tehran 37 Simplest Control Instruction, jmp jmp LABEL ;LABEL is offset address of instruction ;in the code segment 3 Forms of jmp SHORT - 2 bytes, allows jump to ±127 locations from current address EB NEAR - 3 bytes, allows jump to ±32K locations from current address E9 FAR disp disphi displo - 5 bytes anywhere in memory EA IP lo IP hi CS lo CS hi University of Tehran 38 Example with Short Jump ;Causes bx to count by 1 from 0 to 65535 to 0 to 65535 to … xor start: mov add jmp next: xor xor mov jmp bx, ax, ax, next bx 1 bx bx, ax, bx, start bx ax ax ;Clear ;ax ;ax ;add a ; ;Clear ;Clear ;bx ;add a ; bx and initialize status flags 1 ax+bx displacement to IP (+2 from xor to mov) bx and initialize flags ax and initialize flags ax displacement to IP (a negative value - 2’s comp.) University of Tehran 39 Indirect Jump • Address of target is in register • Does NOT add disp to IP - Transfer REG contents to IP ;assume that si contains either 0, 1 or 2 add si, si ;si 2*si add si, OFFSET TABLE ;si si + <address of TABLE> mov ax, cs:[si] ;ax gets an address from the jump table jmp ax ;ip ax ;the following jump TABLE is defined in the code segment!!!! TABLE: DW ZERO DW ONE DW TWO ZERO: ;code for ZERO option . . ONE: ;code for ONE option . . TWO: ;code for TWO option . . University of Tehran 40 Indirect Addressed Jump • Address of target is in register • Does NOT add disp to IP - Transfer MEM contents to IP ;assume that si contains either 0, 1 or 2 add si, si ;si 2*si add si, OFFSET TABLE ;si si + <address of TABLE> jmp cs:[si] ;ip gets an address from the jump table ;the following jump TABLE is defined in the code segment!!!! TABLE: DW ZERO DW ONE DW TWO ZERO: ;code for ZERO option . . ONE: ;code for ONE option . . TWO: ;code for TWO option . . University of Tehran 41 Conditional Control Instruction Summary Simple Flag Branches Jump based on single flag CONDITIONAL jc jnc je/jz jne/jnz jo jno js jns jp/jpe jnp/jpo LABEL LABEL LABEL LABEL LABEL LABEL LABEL LABEL LABEL LABEL ;jump ;jump ;jump ;jump ;jump ;jump ;jump ;jump ;jump ;jump on on if if if if on if if if carry (CF=1) no carry (CF=0) ZF=1 - jump if equal/zero ZF=0 - jump not equal/jump if zero OF=1 - jump on overflow OF=0 - jump if no overflow sign flag set (SF=1) no sign flag (SF=0) PF=1 - jump on parity/parity even PF=0 - jump on no parity/parity odd University of Tehran 42 Conditional Control Instruction Summary Branches for unsigned comparisons Jump is based on flags used for unsigned number comparison (based on C, Z flag) ja/jnbe jae/jnb jb/jnae jbe/jna LABEL LABEL LABEL LABEL ;jump ;jump ;jump ;jump Typical use: cmp al,bl jb there if if if if CONDITIONAL CF=ZF=0 - jump above-jump not below/equal CF=0 - jump above/equal-jump not below CF=1 - jump below-jump not above/equal CF=1 or ZF=1 - jump equal - jump zero ; jump if al is ‘below’ bl ; unsigned comparison University of Tehran 43 Conditional Control Instruction Summary Branches for signed comparisons Jump is based on flags used for signed number comparison (based on Z, S, V flags) CONDITIONAL jg/jnle LABEL jge/jnl LABEL jl/jnge LABEL jle/jng LABEL ;jump ; ;jump ;jump ; ;jump ; Typical use: cmp al,bl jl there if ZF=0 and (SF=OF) - jump greater/not less nor equal if SF=OF - jump greater-equal/not less than if SF OF - jump less than/not greater nor equal if ZF=1 or SF OF - jump less or equal/not greater than ; jump if al is less than bl ; signed comparison University of Tehran 44 SET condition Instruction • Sets a byte operand to 1 if a given condition is true, or it set the byte to 0 if the condition is false • Useful for saving flag contents • Syntax is SETcondition reg8 or mem8 • condition includes the suffixes of all conditional jump instructions EXAMPLE setb T1 ;T1 1 if CF=1 else T1 0 seto T1 ;T1 1 if OF=1 else T1 0 setz al ;AL 1 if ZF=1 else AL 0 setnc myFlag ;myFlag 1 if CF=0 else myFlag 0 setge byte ptr [si] ;set [si] to 1 if SF = OF University of Tehran 45 Iteration Instruction, loop • Combination of decrement cx and conditional Jump • Decrements cx and if cx0 jumps to LABEL • 386+ loopw (cx operation) and loopd (ecx operation) Example: ADDS PROC mov mov mov cld AGAIN: mov lodsw add mov ADDS stosw loop ret ENDP NEAR cx, si, di, bx, ax, di, AGAIN 100 ;cx 64h - number of words to add OFFSET BLOCK1 ;si offset of BLOCK1 (in ds) OFFSET BLOCK2 ;di offset of BLOCK2 (in es) ;Auto-increment si and di, DF=0 di ;bx di, save offset of BLOCK2 ;ax ds:[si], sisi+2, didi+2 [bx] ;ax ax + ds:[bx] bx ;di bx, restore di with ; offset in BLOCK2 ;es:[di] ax, sisi+2, didi+2 ;cx cx - 1, if cx0 jump to AGAIN ;ip ss:[sp] University of Tehran 46 Procedures • Group of instructions that perform single task – (can be used as) a SUBROUTINE call ret - invokes subroutine - pushes ip - returns from subroutine - pops ip • Uses MASM directives: PROC and ENDP • Must specify NEAR FAR - intrasegment - intersegment • Difference is op-code of ret NEAR FAR - c3h - pops IP - cbh - pops CS, pops IP University of Tehran 47 call Instruction • Differs from jmp since return address on stack NEAR call: FAR call: 3 bytes - 1 opcode and 2 for IP 5 bytes - 1 opcode, 2 for IP and 2 for CS • call with operand - can use 16-bit offset in any register except segment registers call bx ;pushes ip then jumps to cs:[bx] University of Tehran 48 call Instruction - Example mov call COMP COMP PROC push mov in inc out pop ret ENDP si, OFFSET COMP si . . . NEAR dx dx, 03f8h al, dx dx dx, al dx University of Tehran 49 call Instruction - Example Explained mov call COMP COMP PROC push mov in si, OFFSET si . . . NEAR dx dx, 03f8h al, dx inc out dx dx, pop ret ENDP dx al COMP ;get offset of COMP subroutine ;push ip, ipsi ;Save current contents of dx ;dx 03f8h (an immediate data Xfer) ;al receives 1 byte of data from I/O ; device with output port address 03f8h ;dx03f9h ;send 1 byte of data to I/O device ; input port with address 03f9h ;restore dx to value at call time ;ipss:[sp], spsp+2 University of Tehran 50 call Instruction with Indirect Address • Useful for choosing different subroutines at runtime • Can use a table (like the jump table example) ;Assume bx contains 1, 2 or 3 for subroutine desired TABLE DW ONE DW TWO DW THREE dec bx add bx, bx mov di, OFFSET TABLE call cs:[bx+di] jmp CONT ONE PROC NEAR … ONE ENDP TWO PROC NEAR … TWO ENDP THREE PROC NEAR … THREE ENDP CONT: nop University of Tehran 51 call Instruction with Indirect Address ;Table of addresses of subroutines TABLE DW ONE DW TWO DW THREE ;bx contains 1, 2 or 3 - desired subroutine dec bx ;bx 0, 1 or 2 add bx, bx ;bx 0, 2 or 4 mov di, OFFSET TABLE ;di TABLE offset call cs:[bx+di] ;push ip, ipoffset of subroutine jmp CONT ;ip offset of nop instruction ONE PROC NEAR … ONE ENDP TWO PROC NEAR … TWO ENDP THREE PROC NEAR … THREE ENDP CONT: nop University of Tehran 52 ret Instruction NEAR FAR • • pops 16-bit value places in IP pops 32-bit value places in CS:IP Type is determined by PROC directive Other form of ret has immediate operand (8 bit) The immediate operand is added to the SP after popping the return address Example ret 6 University of Tehran 53 University of Tehran 54 String Transfer Instructions • String Forms: movsb movsw ;move string byte by byte ;move string word by word EXAMPLE: movsb ;Copies 8 bits at DS:SI to ES:DI • New String Form (386+): movsd ;move string in double words University of Tehran 55 String Transfer Instructions New mov forms (386+): movsx ;move string with sign extended - Reads source as byte or word and sign extends to word or double word before storing in destination EXAMPLE: movsx cx, al movzx ;cl get al ;if MSB of al=0 then ;ch gets 00h ;else ch gets ffh ;move string with zero extended - Reads source as byte or word and zero extends to word or doub. word before storing in destination EXAMPLE: movzx cx, al ;ch gets 00h and cl gets al of Tehran 56 University Repeated String Move Example ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ; ; ; This is an example program which shows how ; ; the string move instruction works. ; ; ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; strngstk strngstk SEGMENT BYTE STACK 'STACK' DB 100h DUP(?) ENDS strngdat strng1 strng2 crlf strngdat SEGMENT BYTE 'DATA' ;Define the data segment DB 'This is string 1',13,10,'$' ;Define the first string DB 'THIS IS STRING 2',13,10,'$' ;Define the second string DB 13,10,'$' ;Space to new line string ENDS strngcod START: SEGMENT mov ax, mov ds, mov es, ; ; ; BYTE 'CODE' ;Define SEG strngdat ax ax ;Define the stack segment ;Set stack size to 100 bytes the ;ax ;ds ;es Code segment <-- data segment start address <-- initialize data segment register <-- initialize extra segment register Print the strings to the display before moving them mov lea int lea int lea int ah, dx, 21h dx, 21h dx, 21h 9 strng1 strng2 crlf ;ah <-- 9 DOS 21h string function ;dx <-- offset of first string ;DOS service interrupt ;dx <-- offset of second string ;DOS service interrupt ;dx <-- offset of crlf string ;DOS service interrupt University of Tehran 57 Repeated String Move Example (Cont.) ; ; ; Now do a repeated string move byte by byte cld lea si, strng2 lea di, strng1 mov cx, 19 rep movsb ; ; ; ;Autoincrement set DF=0 ;Source is second string ;Destination is first string ;Strings have 19 (decimal) chars. ;Repeated stirng move from 2 to 1 Print the strings to the display after moving them mov lea int lea int lea int ; ; ; ah, dx, 21h dx, 21h dx, 21h 9 strng1 strng2 crlf ;ah <-- 9 DOS 21h string function ;dx <-- offset of first string ;DOS service interrupt ;dx <-- offset of second string ;DOS service interrupt ;dx <-- offset of crlf string ;DOS service interrupt Invoke DOS interrupt that returns processor to OS mov ax, 4c00h ;ax <-- 4c DOS 21h program halt int 21h strngcod START ;DOS service interrupt function END ENDS University of Tehran 58 Assembling/Linking University of Tehran 59 Running the String Move Program University of Tehran 60 Other String Instructions lodsb ;loads al with contents of ds:si ;Inc/Dec si by 1 depending on DF lodsw ;loads ax with ds:si ;Inc/Dec si by 2 depending on DF lodsd ;loads eax with ds:si ;Inc/Dec si by 4 depending on DF ;386+ stosb ;loads es:di with contents of al ;Inc/Dec di by 1 depending on DF stosw ;loads es:di with contents of ax ;Inc/Dec di by 2 depending on DF stosd ;loads es:di with contents of eax ;Inc/Dec di by 4 depending on DF ;386+ University of Tehran 61 Logic Instruction Types (386+) shld shrd SHIFT ax, 12 ;Double precision logical shift left ax, 14 ;Double precision logical shift right bt bts btr btc BIT TEST ax, 12 ;CF12th bit from right in ax bx, 8 ;CF8th bit of bx and bx[8]1 cx, 1 ;CF1st bit in cx and cx[1]0 dx, 2 ;CF2nd bit of dx and dx[2]dx[2]’ bsf bsr BIT SCAN ax, bx ;ZF=1 if all bits in bx=0 ;else ZF=0 and ax gets index of first ;set bit (1) starting from right (LSB) of bx ax, bx ;ZF=1 if all bits in bx=0 ;else ZF=0 and ax gets index of first ;set bit (1) starting from left (MSB) of bx University of Tehran 62 Double Precision Shifts • 386+ •shld - Logical Shift Left •shrd - Logical Shift Right • Uses 3 Operands Instead of 2 • Example shrd ax, bx, 12 ;logical right shift of ax by 12 ;rightmost 12 bits of bx into ;leftmost 12 bits of ax • Contents of bx remain unchanged !!!!!!! University of Tehran 63 String Scan Instruction, scas •scasb, scasw, scasd (386+) • Compares al, ax, eax with memory data • Does an integer subtraction - result not saved • Generally used with a REPEAT prefix •DF controls auto-increment/decrement •Example: mov di, cld mov cx, xor al, repne scasb OFFSET BLOCK 100 al ;di address of memory location BLOCK ;DF 0, auto-increment mode ;cx 64h, initialize counter to 100 ;clear al ;test for 00h in location es:di ;if es:di not equal to 00h then ; cx cx - 1, di di + 1, repeat ;else if cx = 00h ; do not repeat test ;else if es:di equals 00h ; ZF = 1, do not repeat test University of Tehran 64 Skip ASCII Space Character lea di, cld mov cx, mov al, repe scasb STRING ;di offset of memory location labeled STRING ;DF=0 auto-increment mode 256 ;cx ffh, initialize counter to 256 20h ;al ‘ ’, an ASCII <space> Character ;while es:di=20h, continue scanning ;when cx=0 or es:di not equal 20h stop ;after stopping cx contains offset from ;STRING where first non-20h resides (if not 0) University of Tehran 65 Compare String Instruction, cmps •cmpsb, cmpsw, cmpsd (386+) • Compares 2 sections of memory • Does an integer subtraction - result not saved • Generally used with a REPEAT prefix •si, di auto-increment/decrement depending on DF •Example: Test two strings for equivalence ;Assume that ds and es are already set-up (NOTE:ds can equal es) lea si, LINE ;si gets offset of location labeled LINE lea di, TABLE ;di gets offset of location labeled TABLE cld ;DF=0, auto-increment mode moc cx, 10 ;initialize counter register to 10 repe cmpsb ;while ds:si=es:di decrement cx and incr. si, di ;if cx=0 stop testing ;after complete, if cx not equal 0, then ;strings do not match University of Tehran 66 Skip ASCII Space Character lea di, cld mov cx, mov al, repe scasb STRING ;di offset of memory location labeled STRING ;DF=0 auto-increment mode 256 ;cx ffh, initialize counter to 256 20h ;al ‘ ’, an ASCII <space> Character ;while es:di=20h, continue scanning ;when cx=0 or es:di not equal 20h stop ;after stopping cx contains offset from ;STRING where first non-20h resides (if not 0) University of Tehran 67 Summary University of Tehran 68