The Art of
ASSEMBLY LANGUAGE PROGRAMMING

Chapter Eight (Part 10)

Table of Content

Chapter Nine 

CHAPTER EIGHT:
MASM: DIRECTIVES & PSEUDO-OPCODES (Part 11)
8.22 - Sample Program
8.22.1 - EX8.MAK
8.22.2 - Matrix.A
8.22.3 - EX8.ASM
8.22.4 - GETI.ASM
8.22.5 - GetArray.ASM
8.22.6 - XProduct.ASM
8.22 Sample Program

Here is a single program that demonstrates most of the concepts from this chapter. This program consists of several files, including a makefile, that you can assemble and link using the nmake.exe program. This particular sample program computes "cross products" of various functions. The multiplication table you learned in school is a good example of a cross product, so are the truth tables found in Chapter Two of your textbook. This particular program generates cross product tables for addition, subtraction, division, and, optionally, remainder (modulo). In addition to demonstrating several concepts from this chapter, this sample program also demonstrates how to manipulate dynamically allocated arrays. This particular program asks the user to input the matrix size (row and column sizes) and then computes an appropriate set of cross products for that array.

8.22.1 EX8.MAK

The cross product program contains several modules. The following make file assembles all necessary files to ensure a consistent .EXE file.

ex8.exe:ex8.obj geti.obj getarray.obj xproduct.obj matrix.a
	ml ex8.obj geti.obj getarray.obj xproduct.obj

ex8.obj: ex8.asm matrix.a
	ml /c ex8.asm

geti.obj: geti.asm matrix.a
	ml /c geti.asm

getarray.obj: getarray.asm matrix.a
	ml /c getarray.asm


xproduct.obj: xproduct.asm matrix.a
	ml /c xproduct.asm
8.22.2 Matrix.A

MATRIX.A is the header file containing definitions that the cross product program uses. It also contains all the externdef statements for all externally defined routines.

; MATRIX.A
;
; This include file provides the external definitions
; and data type definitions for the matrix sample program
; in Chapter Eight.
;
; Some useful type definitions:

Integer         typedef word
Char            typedef byte

; Some common constants:

Bell            equ     07      ;ASCII code for the bell character.

; A "Dope Vector" is a structure containing information about arrays that
; a program allocates dynamically during program execution.  This particular
; dope vector handles two dimensional arrays.  It uses the following fields:
;
;       TTL-    Points at a zero terminated string containing a description
;               of the data in the array.
;
;       Func-   Pointer to function to compute for this matrix.
;
;       Data-   Pointer to the base address of the array.
;
;       Dim1-   This is a word containing the number of rows in the array.
;
;       Dim2-   This is a word containing the number of elements per row
;               in the array.
;
;       ESize-  Contains the number of bytes per element in the array.

DopeVec         struct
TTL             dword   ?
Func            dword   ?
Data            dword   ?
Dim1            word    ?
Dim2            word    ?
ESize           word    ?
DopeVec         ends

; Some text equates the matrix code commonly uses:

Base            textequ <es:[di]>

byp             textequ <byte ptr>
wp              textequ <word ptr>
dp              textequ <dword ptr>

; Procedure declarations.

InpSeg          segment para public 'input'

                externdef geti:far
                externdef getarray:far

InpSeg          ends


cseg            segment para public 'code'

                externdef CrossProduct:near

cseg            ends


; Variable declarations

dseg            segment para public 'data'

                externdef InputLine:byte

dseg            ends


; Uncomment the following equates if you want to turn on the
; debugging statements or if you want to include the MODULO function.

;debug          equ     0
;DoMOD          equ     0
8.22.3 EX8.ASM

This is the main program. It calls appropriate routines to get the user input, compute the cross product, and print the result.

; Sample program for Chapter Eight.
; Demonstrates the use of many MASM features discussed in Chapter Six
; including label types, constants, segment ordering, procedures, equates,
; address expressions, coercion and type operators, segment prefixes,
; the assume directive, conditional assembly, macros, listing directives,
; separate assembly, and using the UCR Standard Library.
;
; Include the header files for the UCR Standard Library.  Note that the
; "stdlib.a" file defines two segments; MASM will load these segments into
; memory before "dseg" in this program.
;
; The ".nolist" directive tells MASM not to list out all the macros for
; the standard library when producing an assembly listing.  Doing so would
; increase the size of the listing by many tens of pages and would tend to
; obscure the real code in this program.
;
; The ".list" directive turns the listing back on after MASM gets past the
; standard library files.  Note that these two directives (".nolist" and
; ".list") are only active if you produce an assembly listing using MASM's
; "/Fl" command line parameter.


                .nolist
                include    stdlib.a
                includelib stdlib.lib
                .list



; The following statement includes the special header file for this
; particular program.  The header file contains external definitions
; and various data type definitions.

                include matrix.a


; The following two statements allow us to use 80386 instructions
; in the program.  The ".386" directive turns on the 80386 instruction
; set, the "option" directive tells MASM to use 16-bit segments by
; default (when using 80386 instructions, 32-bit segments are the default).
; DOS real mode programs must be written using 16-bit segments.

                .386
                option  segment:use16



dseg            segment para public 'data'

Rows            integer ?       ;Number of rows in matrices
Columns         integer ?       ;Number of columns in matrices


; Input line is an input buffer this code uses to read a string of text
; from the user.  In particular, the GetWholeNumber procedure passes the
; address of InputLine to the GETS routine that reads a line of text
; from the user and places each character into this array.  GETS reads
; a maximum of 127 characters plus the enter key from the user.  It zero
; terminates that string (replacing the ASCII code for the ENTER key with
; a zero).  Therefore, this array needs to be at least 128 bytes long to
; prevent the possibility of buffer overflow.
;
; Note that the GetArray module also uses this array.

InputLine       char    128 dup (0)


; The following two pointers point at arrays of integers.
; This program dynamically allocates storage for the actual array data
; once the user tells the program how big the arrays should be.  The
; Rows and Columns variables above determine the respective sizes of
; these arrays.  After allocating the storage with a call to MALLOC,
; this program stores the pointers to these arrays into the following
; two pointer variables.

RowArray        dword   ?       ;Pointer to Row values
ColArray        dword   ?       ;Pointer to column values.



; ResultArrays is an array of dope vectors(*) to hold the results
; from the matrix operations:
;
; [0]- addition table
; [1]- subtraction table
; [2]- multiplication table
; [3]- division table
;
; [4]- modulo (remainder) table -- if the symbol "DoMOD" is defined.
;
; The equate that follows the ResultArrays declaration computes the number
; of elements in the array.  "$" is the offset into dseg immediately after
; the last byte of ResultArrays.  Subtracting this value from ResultArrays
; computes the number of bytes in ResultArrays.  Dividing this by the size
; of a single dope vector produces the number of elements in the array.
; This is an excellent example of how you can use address expressions in
; an assembly language program.
;
; The IFDEF DoMOD code demonstrates how easy it is to extend this matrix.
; Defining the symbol "DoMOD" adds another entry to this array.  The
; rest of the program adjusts for this new entry automatically.
;
; You can easily add new items to this array of dope vectors.  You will
; need to supply a title and a function to compute the matrice's entries.
; Other than that, however, this program automatically adjusts to any new
; entries you add to the dope vector array.
;
; (*) A "Dope Vector" is a data structure that describes a dynamically
; allocated array.  A typical dope vector contains the maximum value for
; each dimension, a pointer to the array data in memory, and some other
; possible information.  This program also stores a pointer to an array
; title and a pointer to an arithmetic function in the dope vector.

ResultArrays    DopeVec {AddTbl,Addition}, {SubTbl,Subtraction}
                DopeVec {MulTbl,Multiplication}, {DivTbl,Division}

                ifdef   DoMOD
                DopeVec {ModTbl,Modulo}
                endif

; Add any new functions of your own at this point, before the following equate:


RASize          =       ($-ResultArrays) / (sizeof DopeVec)


; Titles for each of the four (five) matrices.

AddTbl          char    "Addition Table",0
SubTbl          char    "Subtraction Table",0
MulTbl          char    "Multiplication Table",0
DivTbl          char    "Division Table",0

                ifdef   DoMOD
ModTbl          char    "Modulo (Remainder) Table",0
                endif

; This would be a good place to put a title for any new array you create.

dseg            ends




; Putting PrintMat inside its own segment demonstrates that you can have
; multiple code segments within a program.  There is no reason we couldn't
; have put "PrintMat" in CSEG other than to demonstrate a far call to a
; different segment.

PrintSeg        segment para public 'PrintSeg'

; PrintMat-     Prints a matrix for the cross product operation.
;
;       On Entry:
;
;               DS must point at DSEG.
;               DS:SI points at the entry in ResultArrays for the
;               array to print.
;
; The output takes the following form:
;
;       Matrix Title
;
;              <- column matrix values ->
;
;       ^      *------------------------*
;       |      |                        |
;       R      |                        |
;       o      | Cross Product Matrix   |
;       w      |       Values           |
;              |                        |
;       V      |                        |
;       a      |                        |
;       l      |                        |
;       u      |                        |
;       e      |                        |
;       s      |                        |
;       |      |                        |
;       v      *------------------------*


PrintMat        proc    far
                assume  ds:dseg


; Note the use of conditional assembly to insert extra debugging statements
; if a special symbol "debug" is defined during assembly.  If such a symbol
; is not defined during assembly, the assembler ignores the following
; statements:

                ifdef   debug
                print
                char    "In PrintMat",cr,lf,0
                endif

; First, print the title of this table.  The TTL field in the dope vector
; contains a pointer to a zero terminated title string.  Load this pointer
; into es:di and call PUTS to print that string.

                putcr
                les     di, [si].DopeVec.TTL
                puts

; Now print the column values.  Note the use of PUTISIZE so that each
; value takes exactly six print positions. The following loop repeats
; once for each element in the Column array (the number of elements in
; the column array is given by the Dim2 field in the dope vector).

                print                           ;Skip spaces to move past the
                char    cr,lf,lf,"       ",0    ; row values.

                mov     dx, [si].DopeVec.Dim2   ;# times to repeat the loop.
                les     di, ColArray            ;Base address of array.
ColValLp:       mov     ax, es:[di]             ;Fetch current array element.
                mov     cx, 6                   ;Print the value using a
                putisize                        ; minimum of six positions.
                add     di, 2                   ;Move on to next element.
                dec     dx                      ;Repeat this loop DIM2 times.
                jne     ColValLp
                putcr                           ;End of column array output
                putcr                           ;Insert a blank line.

; Now output each row of the matrix.  Note that we need to output the
; RowArray value before each row of the matrix.
;
; RowLp is the outer loop that repeats for each row.

                mov     Rows, 0                 ;Repeat for 0..Dim1-1 rows.
RowLp:          les     di, RowArray            ;Output the current RowArray
                mov     bx, Rows                ; value on the left hand side
                add     bx, bx                  ; of the matrix.
                mov     ax, es:[di][bx]         ;ES:DI is base, BX is index.
                mov     cx, 5                   ;Output using five positions.
                putisize
                print
                char    ": ",0

; ColLp is the inner loop that repeats for each item on each row.

                mov     Columns, 0              ;Repeat for 0..Dim2-1 cols.
ColLp:          mov     bx, Rows                ;Compute index into the array
                imul    bx, [si].DopeVec.Dim2   ; index := (Rows*Dim2 +
                add     bx, Columns             ;              columns) * 2
                add     bx, bx

; Note that we only have a pointer to the base address of the array, so we
; have to fetch that pointer and index off it to access the desired array
; element.  This code loads the pointer to the base address of the array into
; the es:di register pair.

                les     di, [si].DopeVec.Data   ;Base address of array.
                mov     ax, es:[di][bx]         ;Get array element

; The functions that compute the values for the array store an 8000h into
; the array element if some sort of error occurs.  Of course, it is possible
; to produce 8000h as an actual result, but giving up a single value to
; trap errors is worthwhile.  The following code checks to see if an error
; occurred during the cross product.  If so, this code prints "  ****",
; otherwise, it prints the actual value.

                cmp     ax, 8000h               ;Check for error value
                jne     GoodOutput
                print
                char    "  ****",0              ;Print this for errors.
                jmp     DoNext

GoodOutput:     mov     cx, 6                   ;Use six print positions.
                putisize                        ;Print a good value.

DoNext:         mov     ax, Columns             ;Move on to next array
                inc     ax                      ; element.
                mov     Columns, ax
                cmp     ax, [si].DopeVec.Dim2   ;See if we're done with
                jb      ColLp                   ; this column.

                putcr                           ;End each column with CR/LF

                mov     ax, Rows                ;Move on to the next row.
                inc     ax
                mov     Rows, ax
                cmp     ax, [si].DopeVec.Dim1   ;Have we finished all the
                jb      RowLp                   ; rows?  Repeat if not done.
                ret
PrintMat        endp
PrintSeg        ends


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

;GetWholeNum-   This routine reads a whole number (an integer greater than
;               zero) from the user.  If the user enters an illegal whole
;               number, this procedure makes the user re-enter the data.

GetWholeNum     proc    near
                lesi    InputLine       ;Point es:di at InputLine array.
                gets

                call    Geti            ;Get an integer from the line.
                jc      BadInt          ;Carry set if error reading integer.
                cmp     ax, 0           ;Must have at least one row or column!
                jle     BadInt
                ret

BadInt:         print
                char    Bell
                char    "Illegal integer value, please re-enter",cr,lf,0
                jmp     GetWholeNum
GetWholeNum     endp


; Various routines to call for the cross products we compute.
; On entry, AX contains the first operand, dx contains the second.
; These routines return their result in AX.
; They return AX=8000h if an error occurs.
;
; Note that the CrossProduct function calls these routines indirectly.

addition        proc    far
                add     ax, dx
                jno     AddDone         ;Check for signed arithmetic overflow.
                mov     ax, 8000h       ;Return 8000h if overflow occurs.
AddDone:        ret
addition        endp


subtraction     proc    far
                sub     ax, dx
                jno     SubDone
                mov     ax, 8000h       ;Return 8000h if overflow occurs.
SubDone:        ret
subtraction     endp

multiplication  proc    far
                imul    ax, dx
                jno     MulDone
                mov     ax, 8000h       ;Error if overflow occurs.
MulDone:        ret
multiplication  endp

division        proc    far
                push    cx              ;Preserve registers we destory.

                mov     cx, dx
                cwd
                test    cx, cx          ;See if attempting division by zero.
                je      BadDivide
                idiv    cx

                mov     dx, cx          ;Restore the munged register.
                pop     cx
                ret

BadDivide:      mov     ax, 8000h
                mov     dx, cx
                pop     cx
                ret
division        endp


; The following function computes the remainder if the symbol "DoMOD"
; is defined somewhere prior to this point.

                ifdef   DoMOD
modulo          proc    far
                push    cx

                mov     cx, dx
                cwd
                test    cx, cx          ;See if attempting division by zero.
                je      BadDivide
                idiv    cx
                mov     ax, dx          ;Need to put remainder in AX.
                mov     dx, cx          ;Restore the munged registers.
                pop     cx
                ret

BadMod:         mov     ax, 8000h
                mov     dx, cx
                pop     cx
                ret
modulo          endp
                endif

; If you decide to extend the ResultArrays dope vector array, this is a good
; place to define the function for those new arrays.


; The main program that reads the data from the user, calls the appropriate
; routines, and then prints the results.

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

; Prompt the user to enter the number of rows and columns:

GetRows:        print
                byte    "Enter the number of rows for the matrix:",0

                call    GetWholeNum
                mov     Rows, ax

; Okay, read each of the row values from the user:

                print
                char    "Enter values for the row (vertical) array",cr,lf,0

; Malloc allocates the number of bytes specified in the CX register.
; AX contains the number of array elements we want;  multiply this value
; by two since we want an array of words.  On return from malloc, es:di
; points at the array allocated on the "heap".  Save away this pointer in
; the "RowArray" variable.
;
; Note the use of the "wp" symbol. This is an equate to "word ptr" appearing
; in the "matrix.a" include file.  Also note the use of the address expression
; "RowArray+2" to access the segment portion of the double word pointer.

                mov     cx, ax
                shl     cx, 1
                malloc
                mov     wp RowArray, di
                mov     wp RowArray+2, es

; Okay, call "GetArray" to read "ax" input values from the user.
; GetArray expects the number of values to read in AX and a pointer
; to the base address of the array in es:di.

                print
                char    "Enter row data:",0

                mov     ax, Rows        ;# of values to read.
                call    GetArray        ;ES:DI still points at array.


; Okay, time to repeat this for the column (horizontal) array.

GetCols:        print
                byte    "Enter the number of columns for the matrix:",0

                call    GetWholeNum     ;Get # of columns from the user.
                mov     Columns, ax     ;Save away number of columns.


; Okay, read each of the column values from the user:

                print
                char    "Enter values for the column (horz.) array",cr,lf,0

; Malloc allocates the number of bytes specified in the CX register.
; AX contains the number of array elements we want;  multiply this value
; by two since we want an array of words.  On return from malloc, es:di
; points at the array allocated on the "heap".  Save away this pointer in
; the "RowArray" variable.

                mov     cx, ax                  ;Convert # Columns to # bytes
                shl     cx, 1                   ; by multiply by two.
                malloc                          ;Get the memory.
                mov     wp ColArray, di         ;Save pointer to the
                mov     wp ColArray+2, es       ;columns vector (array).

; Okay, call "GetArray" to read "ax" input values from the user.
; GetArray expects the number of values to read in AX and a pointer
; to the base address of the array in es:di.

                print
                char    "Enter Column data:",0

                mov     ax, Columns             ;# of values to read.
                call    GetArray                ;ES:DI points at column array.

; Okay, initialize the matrices that will hold the cross products.
; Generate RASize copies of the following code.
; The "repeat" macro repeats the statements between the "repeat" and the "endm"
; directives RASize times.  Note the use of the Item symbol to automatically
; generate different indexes for each repetition of the following code.
; The "Item = Item+1" statement ensures that Item will take on the values
; 0, 1, 2, ..., RASize on each repetition of this loop.
;
; Remember, the "repeat..endm" macro copies the statements multiple times
; within the source file, it does not execute a "repeat..until" loop at
; run time.  That is, the following macro is equivalent to making "RASize"
; copies of the code, substituting different values for Item for each
; copy.
;
; The nice thing about this code is that it automatically generates the
; proper amount of initialization code, regardless of the number of items
; placed in the ResultArrays array.


Item            =       0

                repeat  RASize

                mov     cx, Columns     ;Compute the size, in bytes,
                imul    cx, Rows        ; of the matrix and allocate
                add     cx, cx          ; sufficient storage for the
                malloc                  ; array.

                mov     wp ResultArrays[Item * (sizeof DopeVec)].Data, di
                mov     wp ResultArrays[Item * (sizeof DopeVec)].Data+2, es

                mov     ax, Rows
                mov     ResultArrays[Item * (sizeof DopeVec)].Dim1, ax

                mov     ax, Columns
                mov     ResultArrays[Item * (sizeof DopeVec)].Dim2, ax

                mov     ResultArrays[Item * (sizeof DopeVec)].ESize, 2

Item            =       Item+1
                endm


; Okay, we've got the input values from the user,
; now let's compute the addition, subtraction, multiplication,
; and division tables.  Once again, a macro reduces the amount of
; typing we need to do at this point as well as automatically handling
; however many items are present in the ResultArrays array.

element         =       0

                repeat  RASize
                lfs     bp, RowArray            ;Pointer to row data.
                lgs     bx, ColArray            ;Pointer to column data.

                lea     cx, ResultArrays[element * (sizeof DopeVec)]
                call    CrossProduct

element         =       element+1
                endm


; Okay, print the arrays down here.  Once again, note the use of the
; repeat..endm macro to save typing and automatically handle additions
; to the ResultArrays array.


Item            =       0

                repeat  RASize
                mov     si, offset ResultArrays[item * (sizeof DopeVec)]
                call    PrintMat
Item            =       Item+1
                endm


; Technically, we don't have to free up the storage malloc'd for each
; of the arrays since the program is about to quit.  However, it's a
; good idea to get used to freeing up all your storage when you're done
; with it.  For example, were you to add code later at the end of this
; program, you would have that extra memory available to that new code.

                les     di, ColArray
                free
                les     di, RowArray
                free

Item            =       0
                repeat  RASize
                les     di, ResultArrays[Item * (sizeof DopeVec)].Data
                free
Item            =       Item+1
                endm


Quit:           ExitPgm                 ;DOS macro to quit program.
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
8.22.4 GETI.ASM

GETI.ASM contains a routine (geti) that reads an integer value from the user.

; GETI.ASM
;
; This module contains the integer input routine for the matrix
; example in Chapter Eight.

                .nolist
                include stdlib.a
                .list

                include matrix.a

InpSeg          segment para public 'input'

; Geti- On entry, es:di points at a string of characters.
;       This routine skips any leading spaces and comma characters and then
;       tests the first (non-space/comma) character to see if it is a digit.
;       If not, this routine returns the carry flag set denoting an error.
;       If the first character is a digit, then this routine calls the
;       standard library routine "atoi2" to convert the value to an integer.
;       It then ensures that the number ends with a space, comma, or zero
;       byte.
;
;       Returns carry clear and value in AX if no error.
;       Returns carry set if an error occurs.
;
;       This routine leaves ES:DI pointing at the character it fails on when
;       converting the string to an integer.  If the conversion occurs without
;       an error, the ES:DI points at a space, comma, or zero terminating byte.


geti            proc    far

                ifdef   debug
                print
                char    "Inside GETI",cr,lf,0
                endif

; First, skip over any leading spaces or commas.
; Note the use of the "byp" symbol to save having to type "byte ptr".
; BYP is a text equate appearing in the macros.a file.
; A "byte ptr" coercion operator is required here because MASM cannot
; determine the size of the memory operand (byte, word, dword, etc)
; from the operands.  I.e., "es:[di]" and ' ' could be any of these
; three sizes.
;
; Also note a cute little trick here; by decrementing di before entering
; the loop and then immediately incrementing di, we can increment di before
; testing the character in the body of the loop.  This makes the loop
; slightly more efficient and a lot more elegant.

                dec     di
SkipSpcs:       inc     di
                cmp     byp es:[di], ' '
                je      SkipSpcs
                cmp     byp es:[di], ','
                je      SkipSpcs

; See if the first non-space/comma character is a decimal digit:

                mov     al, es:[di]
                cmp     al, '-'          ;Minus sign is also legal in integers.
                jne     TryDigit
                mov     al, es:[di+1]    ;Get next char, if "-"

TryDigit:       isdigit
                jne     BadGeti         ;Jump if not a digit.

; Okay, convert the characters that follow to an integer:

ConvertNum:     atoi2                   ;Leaves integer in AX
                jc      BadGeti         ;Bomb if illegal conversion.

; Make sure this number ends with a reasonable character (space, comma,
; or a zero byte):

                cmp     byp es:[di], ' '
                je      GoodGeti
                cmp     byp es:[di], ','
                je      GoodGeti
                cmp     byp es:[di], 0
                je      GoodGeti

                ifdef   debug
                print
                char    "GETI: Failed because number did not end with "
                char    "a space, comma, or zero byte",cr,lf,0
                endif

BadGeti:        stc                     ;Return an error condition.
                ret

GoodGeti:       clc                     ;Return no error and an integer in AX
                ret
geti            endp

InpSeg          ends
                end
8.22.5 GetArray.ASM

GetArray.ASM contains the GetArray input routine. This reads the data for the array from the user to produce the cross products. Note that GetArray reads the data for a single dimension array (or one row in a multidimensional array). The cross product program reads two such vectors: one for the column values and one for the row values in the cross product. Note: This routine uses subroutines from the UCR Standard Library that appear in the next chapter.

; GETARRAY.ASM
;
; This module contains the GetArray input routine.  This routine reads a
; set of values for a row of some array.

                .386
                option  segment:use16

                .nolist
                include stdlib.a
                .list

                include matrix.a

; Some local variables for this module:

localdseg       segment para public 'LclData'

NumElements     word    ?
ArrayPtr        dword   ?

Localdseg       ends


InpSeg          segment para public 'input'
                assume  ds:Localdseg

; GetArray-     Read a set of numbers and store them into an array.
;
;       On Entry:
;
;               es:di points at the base address of the array.
;               ax contains the number of elements in the array.
;
;               This routine reads the specified number of array elements
;               from the user and stores them into the array.  If there
;               is an input error of some sort, then this routine makes
;               the user reenter the data.

GetArray        proc    far
                pusha                   ;Preserve all the registers
                push    ds              ; that this code modifies
                push    es
                push    fs

                ifdef   debug
                print
                char    "Inside GetArray, # of input values =",0
                puti
                putcr
                endif

                mov     cx, Localdseg           ;Point ds at our local
                mov     ds, cx                  ; data segment.

                mov     wp ArrayPtr, di         ;Save in case we have an
                mov     wp ArrayPtr+2, es       ; error during input.
                mov     NumElements, ax

; The following loop reads a line of text from the user containing some
; number of integer values.  This loop repeats if the user enters an illegal
; value on the input line.
;
; Note: LESI is a macro from the stdlib.a include file.  It loads ES:DI
; with the address of its operand (as opposed to les di, InputLine that would
; load ES:DI with the dword value at address InputLine).

RetryLp:        lesi    InputLine       ;Read input line from user.
                gets
                mov     cx, NumElements ;# of values to read.
                lfs     si, ArrayPtr    ;Store input values here.

; This inner loop reads "ax" integers from the input line.  If there is
; an error, it transfers control to RetryLp above.

ReadEachItem:   call    geti            ;Read next available value.
                jc      BadGA
                mov     fs:[si], ax     ;Save away in array.
                add     si, 2           ;Move on to next element.
                loop    ReadEachItem    ;Repeat for each element.

                pop     fs              ;Restore the saved registers
                pop     es              ; from the stack before
                pop     ds              ; returning.
                popa
                ret

; If an error occurs, make the user re-enter the data for the entire
; row:

BadGA:          print
                char    "Illegal integer value(s).",cr,lf
                char    "Re-enter data:",0
                jmp     RetryLp
getArray        endp

InpSeg          ends
                end
8.22.6 XProduct.ASM

This file contains the code that computes the actual cross-product.

; XProduct.ASM-
;
;       This file contains the cross-product module.

                .386
                option   segment:use16

                .nolist
                include     stdlib.a
                includelib  stdlib.lib
                .list

                include  matrix.a

; Local variables for this module.

dseg            segment para public 'data'
DV              dword   ?
RowNdx          integer ?
ColNdx          integer ?
RowCntr         integer ?
ColCntr         integer ?
dseg            ends


cseg            segment para public 'code'
                assume  ds:dseg

; CrossProduct- Computes the cartesian product of two vectors.
;
;       On entry:
;
;       FS:BP-  Points at the row matrix.
;       GS:BX-  Points at the column matrix.
;       DS:CX-  Points at the dope vector for the destination.
;
;       This code assume ds points at dseg.
;       This routine only preserves the segment registers.

RowMat          textequ <fs:[bp]>
ColMat          textequ <gs:[bx]>
DVP             textequ <ds:[bx].DopeVec>

CrossProduct    proc    near

                ifdef   debug
                print
                char    "Entering CrossProduct routine",cr,lf,0
                endif

                xchg    bx, cx          ;Get dope vector pointer
                mov     ax, DVP.Dim1    ;Put Dim1 and Dim2 values
                mov     RowCntr, ax     ; where they are easy to access.
                mov     ax, DVP.Dim2
                mov     ColCntr, ax
                xchg    bx, cx


; Okay, do the cross product operation.  This is defined as follows:
;
;       for RowNdx := 0 to NumRows-1 do
;           for ColNdx := 0 to NumCols-1 do
;               Result[RowNdx, ColNdx] = Row[RowNdx] op Col[ColNdx];

                mov     RowNdx, -1      ;Really starts at zero.
OutsideLp:      add     RowNdx, 1
                mov     ax, RowNdx
                cmp     ax, RowCntr
                jge     Done

                mov     ColNdx, -1      ;Really starts at zero.
InsideLp:       add     ColNdx, 1
                mov     ax, ColNdx
                cmp     ax, ColCntr
                jge     OutSideLp

                mov     di, RowNdx
                add     di, di
                mov     ax, RowMat[di]

                mov     di, ColNdx
                add     di, di
                mov     dx, ColMat[di]

                push    bx              ;Save pointer to column matrix.
                mov     bx, cx          ;Put ptr to dope vector where we can
                                        ; use it.

                call    DVP.Func        ;Compute result for this guy.

                mov     di, RowNdx      ;Index into array is
                imul    di, DVP.Dim2    ; (RowNdx*Dim2 + ColNdx) * ElementSize
                add     di, ColNdx
                imul    di, DVP.ESize

                les     bx, DVP.Data    ;Get base address of array.
                mov     es:[bx][di], ax ;Save away result.

                pop     bx              ;Restore ptr to column array.
                jmp     InsideLp

Done:           ret
CrossProduct    endp
cseg            ends
                end

Chapter Eight (Part 10)

Table of Content

Chapter Nine 

Chapter Eight: MASM: Directives & Pseudo-Opcodes (Part 11)
26 SEP 1996