The Art of
ASSEMBLY LANGUAGE PROGRAMMING

Chapter Six (Part 5)

Table of Content

Chapter Seven 

CHAPTER SIX:
THE 80x86 INSTRUCTION SET (Part 6)
6.11 - Sample Programs
6.11.1 - Simple Arithmetic I
6.11.2 - Simple Arithmetic II
6.11.3 - Logical Operations
6.11.4 - Shift and Rotate Operations
6.11.5 - Bit Operations and SETcc Instructions
6.11.6 - String Operations
6.11.7 - Conditional Jumps
6.11.8 - CALL and INT Instructions
6.11.9 - Conditional Jumps I
6.11.10 - Conditional Jump Instructions II
6.11 Sample Programs

The following sample programs demonstrate the use of the various instructions appearing in this chapter.

6.11.1 Simple Arithmetic I

; Simple Arithmetic
; This program demonstrates some simple arithmetic instructions.

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'

; Some type definitions for the variables we will declare:

uint            typedef word            ;Unsigned integers.
integer         typedef sword           ;Signed integers.


; Some variables we can use:

j               integer ?
k               integer ?
l               integer ?

u1              uint    ?
u2              uint    ?
u3              uint    ?
dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Initialize our variables:

                mov     j, 3
                mov     k, -2

                mov     u1, 254
                mov     u2, 22

; Compute L := j+k and u3 := u1+u2

                mov     ax, J
                add     ax, K
                mov     L, ax

                mov     ax, u1          ;Note that we use the "ADD"
                add     ax, u2          ; instruction for both signed
                mov     u3, ax          ; and unsigned arithmetic.

; Compute L := j-k and u3 := u1-u2

                mov     ax, J
                sub     ax, K
                mov     L, ax

                mov     ax, u1          ;Note that we use the "SUB"
                sub     ax, u2          ; instruction for both signed
                mov     u3, ax          ; and unsigned arithmetic.

; Compute L := -L

                neg     L

; Compute L := -J

                mov     ax, J           ;Of course, you would only use the
                neg     ax              ; NEG instruction on signed values.
                mov     L, ax

; Compute K := K + 1 using the INC instruction.

                inc     K

; Compute u2 := u2 + 1 using the INC instruction.
; Note that you can use INC for signed and unsigned values.

                inc     u2

; Compute J := J - 1 using the DEC instruction.

                dec     J

; Compute u2 := u2 - 1 using the DEC instruction.
; Note that you can use DEC for signed and unsigned values.

                dec     u2

Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.2 Simple Arithmetic II

; Simple Arithmetic
; This program demonstrates some simple arithmetic instructions.

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'

; Some type definitions for the variables we will declare:

uint            typedef word            ;Unsigned integers.
integer         typedef sword           ;Signed integers.


; Some variables we can use:

j               integer ?
k               integer ?
l               integer ?

u1              uint    ?
u2              uint    ?
u3              uint    ?

dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Initialize our variables:

                mov     j, 3
                mov     k, -2

                mov     u1, 254
                mov     u2, 22


; Extended multiplication using 8086 instructions.
;
; Note that there are separate multiply instructions for signed and
; unsigned operands.
;
; L := J * K (ignoring overflow)

                mov     ax, J
                imul    K               ;Computes DX:AX := AX * K
                mov     L, ax           ;Ignore overflow into DX.

; u3 := u1 * u2

                mov     ax, u1
                mul     u2              ;Computes DX:AX := AX * U2
                mov     u3, ax          ;Ignore overflow in DX.


; Extended division using 8086 instructions.
;
; Like multiplication, there are separate instructions for signed
; and unsigned operands.
;
; It is absolutely imperative that these instruction sequences sign
; extend or zero extend their operands to 32 bits before dividing.
; Failure to do so will may produce a divide error and crash the
; program.
;
; L := J div K

                mov     ax, J
                cwd                     ;*MUST* sign extend AX to DX:AX!
                idiv    K               ;AX := DX:AX/K, DX := DX:AX mod K
                mov     L, ax

; u3 := u1/u2

                mov     ax, u1
                mov     dx, 0           ;Must zero extend AX to DX:AX!
                div     u2              ;AX := DX:AX/u2, DX := DX:AX mod u2
                mov     u3, ax

; Special forms of the IMUL instruction available on 80286, 80386, and
; later processors.  Technically, these instructions operate on signed
; operands only, however, they do work fine for unsigned operands as well.
; Note that these instructions produce a 16-bit result and set the overflow
; flag if overflow occurs.
;
; L := J * 10 (80286 and later only)

                imul    ax, J, 10       ;AX := J*10
                mov     L, ax

; L := J * K (80386 and later only)

                mov     ax, J
                imul    ax, K
                mov     L, ax



Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.3 Logical Operations

; Logical Operations
; This program demonstrates the AND, OR, XOR, and NOT instructions

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'


; Some variables we can use:

j               word    0FF00h
k               word    0FFF0h
l               word    ?

c1              byte    'A'
c2              byte    'a'

LowerMask       byte    20h

dseg            ends


cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Compute L := J and K (bitwise AND operation):

                mov     ax, J
                and     ax, K
                mov     L, ax

; Compute L := J or K (bitwise OR operation):

                mov     ax, J
                or      ax, K
                mov     L, ax

; Compute L := J xor K (bitwise XOR operation):

                mov     ax, J
                xor     ax, K
                mov     L, ax

; Compute L := not L (bitwise NOT operation):

                not     L

; Compute L := not J (bitwise NOT operation):

                mov     ax, J
                not     ax
                mov     L, ax

; Clear bits 0..3 in J:

                and     J, 0FFF0h

; Set bits 0..3 in K:

                or      K, 0Fh

; Invert bits 4..11 in L:

                xor     L, 0FF0h

; Convert the character in C1 to lower case:

                mov     al, c1
                or      al, LowerMask
                mov     c1, al

; Convert the character in C2 to upper case:

                mov     al, c2
                and     al, 5Fh         ;Clears bit 5.
                mov     c2, al



Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.4 Shift and Rotate Operations

; Shift and Rotate Instructions

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'

; The following structure holds the bit values for an 80x86 mod-reg-r/m byte.

mode            struct
modbits         byte    ?
reg             byte    ?
rm              byte    ?
mode            ends

Adrs1           mode    {11b, 100b, 111b}
modregrm                byte    ?

var1            word    1
var2            word    8000h
var3            word    0FFFFh
var4            word    ?

dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Shifts and rotates directly on memory locations:
;
; var1 := var1 shl 1

                shl     var1, 1

; var1 := var1 shr 1

                shr     var1, 1

; On 80286 and later processors, you can shift by more than one bit at
; at time:

                shl     var1, 4
                shr     var1, 4

; The arithmetic shift right instruction retains the H.O. bit after each
; shift.  The following SAR instruction sets var2 to 0FFFFh

                sar     var2, 15

; On all processors, you can specify a shift count in the CL register.
; The following instruction restores var2 to 8000h:

                mov     cl, 15
                shl     var2, cl

; You can use the shift and rotate instructions, along with the logical
; instructions, to pack and unpack data.  For example, the following
; instruction sequence extracts bits 10..13 of var3 and leaves
; this value in var4:

                mov     ax, var3
                shr     ax, 10          ;Move bits 10..13 to 0..3.
                and     ax, 0Fh         ;Keep only bits 0..3.
                mov     var4, ax

; You can use the rotate instructions to compute this value somewhat faster
; on older processors like the 80286.

                mov     ax, var3
                rol     ax, 6           ;Six rotates rather than 10 shifts.
                and     ax, 0Fh
                mov     var4, ax

; You can use the shift and OR instructions to easily merge separate fields
; into a single value.  For example, the following code merges the mod, reg,
; and r/m fields (maintained in separate bytes) into a single mod-reg-r/m
; byte:


                mov     al, Adrs1.modbits
                shl     al, 3
                or      al, Adrs1.reg
                shl     al, 3
                or      al, Adrs1.rm
                mov     modregrm, al

; If you've only got and 8086 or 8088 chip, you'd have to use code like the
; following:

                mov     al, Adrs1.modbits       ;Get mod field
                shl     al, 1
                shl     al, 1
                or      al, Adrs1.reg           ;Get reg field
                mov     cl, 3
                shl     al, cl                  ;Make room for r/m field.
                or      al, Adrs1.rm            ;Merge in r/m field.
                mov     modregrm, al            ;Save result away.

Quit:           mov     ah, 4ch                 ;DOS opcode to quit program.
                int     21h                     ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.5 Bit Operations and SETcc Instructions

; Bit Operations and SETcc Instructions

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'

; Some type definitions for the variables we will declare:

uint            typedef word            ;Unsigned integers.
integer         typedef sword           ;Signed integers.


; Some variables we can use:

j               integer ?
k               integer ?
u1              uint    2
u2              uint    2
Result          byte    ?

dseg            ends



cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Initialize some variables

                mov     j, -2
                mov     k, 2

; The SETcc instructions store a one or zero into their operand if the
; specified condition is true or false, respectively.  The TEST instruction
; logically ANDs its operands and sets the flags accordingly (in particular,
; TEST sets/clears the zero flag if there is/isn't a zero result).  We can
; use these two facts to copy a single bit (zero extended) to a byte operand.

                test    j, 11000b       ;Test bits 4 and 5.
                setne   Result          ;Result=1 if bits 4 or 5 of J are 1.

                test    k, 10b          ;Test bit #1.
                sete    Result          ;Result=1 if bit #1 = 0.

; The SETcc instructions are particularly useful after a CMP instruction.
; You can set a boolean value according to the result of the comparison.
;
; Result := j <= k

                mov     ax, j
                cmp     ax, k
                setle   Result          ;Note that "le" is for signed values.

; Result := u1 <= u2

                mov     ax, u1
                cmp     ax, u2
                setbe   Result          ;Note that "be" is for unsigned values.

; One thing nice about the boolean results that the SETcc instructions
; produce is that we can AND, OR, and XOR them and get the same results
; one would expect in a HLL like C, Pascal, or BASIC.
;
; Result := (j < k) and (u1 > u2)

                mov     ax, j
                cmp     ax, k
                setl    bl              ;Use "l" for signed comparisons.

                mov     ax, u1
                cmp     ax, u2
                seta    al              ;Use "a" for unsigned comparisons.

                and     al, bl          ;Logically AND the two boolean results
                mov     Result, al      ; and store the result away.

; Sometimes you can use the shift and rotate instructions to test to see
; if a specific bit is set.  For example, SHR copies bit #0 into the carry
; flag and SHL copies the H.O. bit into the carry flag.  We can easily test
; these bits as follows:
;
; Result := bit #15 of J.

                mov     ax, j
                shl     ax, 1
                setc    Result

; Result := bit #0 of u1:

                mov     ax, u1
                shr     ax, 1
                setc    Result

; If you don't have an 80386 or later processor and cannot use the SETcc
; instructions, you can often simulate them.  Consider the above two
; sequences rewritten for the 8086:


; Result := bit #15 of J.

                mov     ax, j
                rol     ax, 1           ;Copy bit #15 to bit #0.
                and     al, 1           ;Strip other bits.
                mov     Result, al

; Result := bit #0 of u1:

                mov     ax, u1
                and     al, 1           ;Strip unnecessary bits.
                mov     Result, al

Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.6 String Operations

; String Instructions

                .386                    ;So we can use extended registers
                option  segment:use16   ; and addressing modes.

dseg            segment para public 'data'

String1         byte    "String",0
String2         byte    7 dup (?)

Array1          word    1, 2, 3, 4, 5, 6, 7, 8
Array2          word    8 dup (?)

dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax


; The string instructions let you easily copy data from one array to
; another.  If the direction flag is clear, the movsb instruction
; does the equivalent of the following:
;
;       mov es:[di], ds:[si]
;       inc     si
;       inc     di
;
; The following code copies the seven bytes from String1 to String2:

                cld                     ;Required if you want to INC SI/DI

                lea     si, String1
                lea     di, String2

                movsb                   ;String2[0] := String1[0]
                movsb                   ;String2[1] := String1[1]
                movsb                   ;String2[2] := String1[2]
                movsb                   ;String2[3] := String1[3]
                movsb                   ;String2[4] := String1[4]
                movsb                   ;String2[5] := String1[5]
                movsb                   ;String2[6] := String1[6]

; The following code sequence demonstrates how you can use the LODSW and
; STOWS instructions to manipulate array elements during the transfer.
; The following code computes
;
;       Array2[0] := Array1[0]
;       Array2[1] := Array1[0] * Array1[1]
;       Array2[2] := Array1[0] * Array1[1] * Array1[2]
;       etc.
;
; Of course, it would be far more efficient to put the following code
; into a loop, but that will come later.

                lea     si, Array1
                lea     di, Array2

                lodsw
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw

                lodsw
                imul    ax, dx
                mov     dx, ax
                stosw



Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.7 Conditional Jumps

; Unconditional Jumps

                .386
                option  segment:use16

dseg            segment para public 'data'


; Pointers to statements in the code segment

IndPtr1         word    IndTarget2
IndPtr2         dword   IndTarget3



dseg            ends


cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; JMP instructions transfer control to the
; location specified in the operand field.
; This is typically a label that appears
; in the program.
;
; There are many variants of the JMP
; instruction.  The first is a two-byte
; opcode that transfers control to +/-128
; bytes around the current instruction:

                jmp     CloseLoc
                nop
CloseLoc:


; The next form is a three-byte instruction
; that allows you to jump anywhere within
; the current code segment.  Normally, the
; assembler would pick the shortest version
; of a given JMP instruction, the "near ptr"
; operand on the following instruction
; forces a near (three byte) JMP:


                jmp     near ptr NearLoc
                nop
NearLoc:


; The third form to consider is a five-byte
; instruction that provides a full segmented
; address operand.  This form of the JMP
; instruction lets you transfer control any-
; where in the program, even to another
; segment.  The "far ptr" operand forces
; this form of the JMP instruction:

                jmp     far ptr FarLoc
                nop
FarLoc:


; You can also load the target address of a
; near JMP into a register and jump indirectly
; to the target location.  Note that you can
; use any 80x86 general purpose register to
; hold this address; you are not limited to
; the BX, SI, DI, or BP registers.

                lea     dx, IndTarget
                jmp     dx
                nop
IndTarget:


; You can even jump indirect through a memory
; variable.  That is, you can jump though a
; pointer variable directly without having to
; first load the pointer variable into a reg-
; ister (Chapter Eight describes why the following
; labels need two colons).

                jmp     IndPtr1
                nop
IndTarget2::


; You can even execute a far jump indirect
; through memory.  Just specify a dword
; variable in the operand field of a JMP
; instruction:

                jmp     IndPtr2
                nop
IndTarget3::



Quit:           mov     ah, 4ch
                int     21h
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.8 CALL and INT Instructions

; CALL and INT Instructions

                .386
                option  segment:use16

dseg            segment para public 'data'

; Some pointers to our subroutines:

SPtr1           word    Subroutine1
SPtr2           dword   Subroutine2

dseg            ends


cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Subroutine1     proc    near
                ret
Subroutine1     endp

Subroutine2     proc    far
                ret
Subroutine2     endp


Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; Near call:

                call    Subroutine1

; Far call:

                call    Subroutine2

; Near register-indirect call:

                lea     cx, Subroutine1
                call    cx

; Near memory-indirect call:

                call    SPtr1

; Far memory-indirect call:

                call    SPtr2


; INT transfers control to a routine whose
; address appears in the interrupt vector
; table (see the chapter on interrupts for 
; details on the interrupt vector table). 
; The following call tells the PC's BIOS 
; to print theASCII character in AL to the 
; display.

                mov     ah, 0eh
                mov     al, 'A'
                int     10h

; INTO generates an INT 4 if the 80x86
; overflow flag is set.  It becomes a
; NOP if the overflow flag is clear.
; You can use this instruction after
; an arithmetic operation to quickly
; test for a fatal overflow.  Note:
; the following sequence does *not*
; generate an overflow.  Do not modify
; it so that it does unless you add an
; INT 4 interrupt service routine to
; the interrupt vector table

                mov     ax, 2
                add     ax, 4
                into


Quit:           mov     ah, 4ch
                int     21h
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.9 Conditional Jumps I

; Conditional JMP Instructions, Part I

                .386
                option  segment:use16
dseg            segment para public 'data'
J               sword   ?
K               sword   ?
L               sword   ?
dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; 8086 conditional jumps are limited to
; +/- 128 bytes because they are only
; two bytes long (one byte opcode, one
; byte displacement).

                .8086
                ja      lbl
                nop
lbl:

; MASM 6.x will automatically extend out of
; range jumps.  The following are both
; equivalent:

                ja      lbl2
                byte    150 dup (0)
lbl2:
                jna     Temp
                jmp     lbl3
Temp:
                byte    150 dup (0)
lbl3:


; The 80386 and later processors support a
; special form of the conditional jump
; instructions that allow a two-byte displace-
; ment, so MASM 6.x will assemble the code
; to use this form if you've specified an
; 80386 processor.

                .386
                ja      lbl4
                byte    150 dup (0)
lbl4:

; The conditional jump instructions work
; well with the CMP instruction to let you
; execute certain instruction sequences
; only if a condition is true or false.
;
; if (J <= K) then
;       L := L + 1
; else  L := L - 1

                mov     ax, J
                cmp     ax, K
                jnle    DoElse
                inc     L
                jmp     ifDone

DoElse:         dec     L
ifDone:

; You can also use a conditional jump to
; create a loop in an assembly language
; program:
;
; while (j >= k) do begin
;
;       j := j - 1;
;       k := k + 1;
;       L := j * k;
; end;

WhlLoop:        mov     ax, j
                cmp     ax, k
                jnge    QuitLoop

                dec     j
                inc     k
                mov     ax, j
                imul    ax, k
                mov     L, ax
                jmp     WhlLoop

QuitLoop:

Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

6.11.10 Conditional Jump Instructions II

; Conditional JMP Instructions, Part II

                .386
                option  segment:use16
dseg            segment para public 'data'

Array1          word    1, 2, 3, 4, 5, 6, 7, 8
Array2          word    8 dup (?)

String1         byte    "This string contains lower case characters",0
String2         byte    128 dup (0)

j               sword   5
k               sword   6

Result          byte    ?

dseg            ends

cseg            segment para public 'code'
                assume  cs:cseg, ds:dseg

Main            proc
                mov     ax, dseg
                mov     ds, ax
                mov     es, ax

; You can use the LOOP instruction to repeat a sequence of statements
; some specified number of times in an assembly language program.
; Consider the code taken from EX6_5.ASM that used the string
; instructions to produce a running product:
;
; The following code uses a loop instruction to compute:
;
;       Array2[0] := Array1[0]
;       Array2[1] := Array1[0] * Array1[1]
;       Array2[2] := Array1[0] * Array1[1] * Array1[2]
;       etc.

                cld
                lea     si, Array1
                lea     di, Array2
                mov     dx, 1           ;Initialize for 1st time.
                mov     cx, 8           ;Eight elements in the arrays.

LoopHere:       lodsw
                imul    ax, dx
                mov     dx, ax
                stosw
                loop    LoopHere


; The LOOPNE instruction is quite useful for controlling loops that
; stop on some condition or when the loop exceeds some number of
; iterations.  For example, suppose string1 contains a sequence of
; characters that end with a byte containing zero.  If you wanted to
; convert those characters to upper case and copy them to string2,
; you could use the following code.  Note how this code ensures that
; it does not copy more than 127 characters from string1 to string2
; since string2 only has enough storage for 127 characters (plus a
; zero terminating byte).

                lea     si, String1
                lea     di, String2
                mov     cx, 127         ;Max 127 chars to string2.

CopyStrLoop:    lodsb                   ;Get char from string1.
                cmp     al, 'a'         ;See if lower case
                jb      NotLower        ;Characters are unsigned.
                cmp     al, 'z'
                ja      NotLower
                and     al, 5Fh         ;Convert lower->upper case.
NotLower:
                stosb
                cmp     al, 0           ;See if zero terminator.
                loopne  CopyStrLoop     ;Quit if al or cx = 0.



; If you do not have an 80386 (or later) CPU and you would like the
; functionality of the SETcc instructions, you can easily achieve
; the same results using code like the following:
;
; Result := J <= K;

                mov     Result, 0       ;Assume false.
                mov     ax, J
                cmp     ax, K
                jnle    Skip1
                mov     Result, 1       ;Set to 1 if J <= K.
Skip1:


; Result := J = K;

                mov     Result, 0       ;Assume false.
                mov     ax, J
                cmp     ax, K
                jne     Skip2
                mov     Result, 1
Skip2:





Quit:           mov     ah, 4ch         ;DOS opcode to quit program.
                int     21h             ;Call DOS.
Main            endp

cseg            ends

sseg            segment para stack 'stack'
stk             byte    1024 dup ("stack   ")
sseg            ends

zzzzzzseg       segment para public 'zzzzzz'
LastBytes       byte    16 dup (?)
zzzzzzseg       ends
                end     Main

Chapter Six (Part 5)

Table of Content

Chapter Seven 

Chapter Six: The 80x86 Instruction Set (Part 6)
26 SEP 1996