News:

Masm32 SDK description, downloads and other helpful links
Message to All Guests
NB: Posting URL's See here: Posted URL Change

Main Menu

Why Code is displaying garbage value?

Started by waqar ahmad, February 19, 2013, 06:17:48 AM

Previous topic - Next topic

waqar ahmad

INCLUDE irvine16.inc

.data
   ; your variables
   
   matrix   dword  0, 1, 2, 3, 4   ; 4 rows, 5 cols
      dword 10,11,12,13,14
      dword 20,21,22,23,24
      dword 30,31,32,33,34

    ROWSIZE EQU   SIZEOF matrix   ; 20 bytes per row

.code
main PROC
mov ax, @data
mov ds, ax
    ; your program

   mov ebx, 2*ROWSIZE       ; row index = 2
   mov esi, 3          ; col index = 3
   mov eax, matrix[ebx+esi*4]        ; AX = matrix[2]

    mov edx,matrix
    call WriteString
    call Crlf

   
   exit
main ENDP
END main

dedndave

WriteString is not the function you want to use

use WriteInt to display a Signed Integer from EAX as decimal
use WriteDec to display an Unsigned Integer from EAX as decimal

RuiLoureiro

Hi waqar ahmad

                may be this code can help you
                Is there any problem ?


;=========================================================
include \masm32\include\masm32rt.inc

GetElement  proto   :DWORD,:DWORD,:DWORD,:DWORD,:DWORD

;========================================================
; note: see _arrayA definition
;
; Len      = length of each element array = 1 DWORD = 4 bytes
;
; maxCol   = maximum number of columns = 3
; maxLin   =    "      "    of lines   = 5
;
; iLin     = current line   = number from 1 to maxLin
; jCol     =    "    column =   "      "  1 to maxCol
;
; LenLin   = length of each line = maxCol * Len = 3 * 4 = 12 bytes
;
; esi      = Base address of array = offset _arrayA
;
; Starting address of line iLin = esi + (iLin-1) * LenLin
;                               = esi + (iLin-1) * maxCol * Len
;
; Address of element (iLin,jCol)= Starting address of line iLin + (jCol-1)*Len
;                               = esi + (iLin-1) * maxCol * Len + (jCol-1)*Len
;
; Replacing Len by 4 (each element is 4 bytes), we have:
;
; Address of element (iLin,jCol) = esi + (iLin-1)* maxCol * 4 + (jCol-1)*4
;
; Assigning Registers:
;                       eax - iLin
;                       ecx - maxCol
;                       ebx - jCol
;
; we should avoid EDX because multiplications trashes EDX: the result is in EDX:EAX
;
; To multiply by 4 we can use shl:  x * 4 = shl x, 2
;==============================================================================
.data
       ; column 1  2  3
       ;...................
_arrayA     dd  1, 2, 3      ; line 1
            dd  4, 5, 6      ; line 2
            dd  7, 8, 9      ; line 3
            dd 10,11,12      ; line 4
            dd 13,14,15      ; line 5
.code
;==============================================================================
; Address of element (iLin,jCol) = esi + (iLin-1)* maxCol * 4 + (jCol-1)*4
;
; Assigning Registers:
;                       eax - iLin
;                       ecx - maxCol
;                       ebx - jCol
;
; Output:
;           EAX     - element in iLin, jCol
;
; Info:
;           Preserves all registers except EDX
;
GetElement  proc    pMtx:DWORD, iLin:DWORD, jCol:DWORD, maxCol:DWORD, maxLin:DWORD
            push    ebx
            push    ecx
            push    esi
            ;
            mov     esi, pMtx
           
            mov     ebx, jCol           ; jCol must be 1 - maxCol
            sub     ebx, 1              ; it cannot be 0
            ;
            mov     ecx, maxCol
            mov     eax, iLin           ; iLin must be 1 - maxLin
            sub     eax, 1              ; it cannot be 0
           
            ; ---------------------------
            ; calculate (iLin-1) * maxCol
            ;   the result is in EAX
            ; ---------------------------
            mul     ecx
            ; -------------
            ; multiply by 4
            ; -------------
            shl     eax, 2
            ; -----------------------------
            ; Starting address of line iLin
            ; -----------------------------
            add     esi, eax
            ; --------------------------------
            ; now we can access the element in
            ;    address [esi+ebx*4]
            ; --------------------------------
            mov     eax, dword ptr [esi+ebx*4]
            ;
            pop     esi
            pop     ecx
            pop     ebx
            ret
GetElement  endp
;
; now we can copy, paste and change to get SetElement,...
;
;==============================================================================
start:
;==============================================================================
            MAXCol = 3
            MAXLin = 5
            ;
            mov     edi, 0          ; Line EDI
            ;
_nextlin:   add     edi, 1
            ;   
            mov     ebx, 0          ; column EBX
            ;
_nextcol:   add     ebx, 1
                              ;    pMtx,     iLin, jCol, maxCol, maxLin       
            invoke  GetElement, addr _arrayA, edi, ebx, MAXCol, MAXLin

            push    eax                             ; preserve EAX
                fn MessageBox,0,str$(edi),"LINE",MB_OK
                fn MessageBox,0,str$(ebx),"COLUMN",MB_OK
            pop     eax
           
            fn MessageBox,0,str$(eax),"Element",MB_OK

            ;
            cmp     ebx, MAXCol
            jb      _nextcol
            ;
            cmp     edi, MAXLin
            jb      _nextlin

            inkey
            exit
;=========================================================
end start

RuiLoureiro

In matrix2.asm we have GetElement, SetElement, MulLinbyCol and MultiplyAbyB
In this example we dont test if line/column is outside the range
Each line goes from 1 to maxLin and each column goes from 1 to maxCol.


; File:     matrix2.asm     version 1
;        by RuiLoureiro
; Date:  19/02/2013
;==============================================================================
include \masm32\include\masm32rt.inc

GetElement      proto   :DWORD,:DWORD,:DWORD,:DWORD,:DWORD
SetElement      proto   :DWORD,:DWORD,:DWORD,:DWORD,:DWORD
MulLinbyCol     proto   :DWORD,:DWORD,:DWORD,:DWORD
MultiplyAbyB    proto   :DWORD,:DWORD,:DWORD

;==============================================================================
; note: see arrayA definition
;
; Len      = length of each element array = 1 DWORD = 4 bytes
;
; maxCol   = maximum number of columns = 3
; maxLin   =    "      "    of lines   = 5
;
; iLin     = current line   = number from 1 to maxLin
; jCol     =    "    column =   "      "  1 to maxCol
;
; LenLin   = length of each line = maxCol * Len = 3 * 4 = 12 bytes
;
; esi      = Base address of array = offset arrayA
;
; Starting address of line iLin = esi + (iLin-1) * LenLin
;                               = esi + (iLin-1) * maxCol * Len
;
; Address of element (iLin,jCol)= Starting address of line iLin + (jCol-1)*Len
;                               = esi + (iLin-1) * maxCol * Len + (jCol-1)*Len
;
; Replacing Len by 4 (each element is 4 bytes), we have:
;
; Address of element (iLin,jCol) = esi + (iLin-1)* maxCol * 4 + (jCol-1)*4
;
; Assigning Registers:
;                       eax - iLin
;                       edx - maxCol
;                       ebx - jCol
;
; we should avoid EDX because multiplications trashes EDX: the result is in EDX:EAX
;
; To multiply by 4 we can use shl:  x * 4 = shl x, 2
;==============================================================================
.data
       ; column 1  2  3
       ;...................
_arrayA     dd  1, 2, 3         ; line 1
            dd  4, 5, 6         ; line 2
            dd  7, 8, 9         ; line 3
            dd 10,11,12         ; line 4
            dd 13,14,15         ; line 5

MAXLinA     equ 5
MAXColA     equ 3


       ; column 1  2  3  4  5
       ;.....................
_arrayB     dd  1, 2, 3, 1, 0   ; line 1
            dd  4, 5, 1, 0, 1   ; line 2
            dd  0, 8, 9, 6, 7   ; line 3

MAXLinB     equ 3
MAXColB     equ 5

_arrayC     dd   9, 36, 32, 19, 23
            dd  24, 81, 71, 40, 47
            dd  39,126,110, 61, 71
            dd  54,171,149, 82, 95
            dd  69,216,188,103,119
           
            dd 100 dup (0)      ; for 10*10 array

MAXLinC     equ 5
MAXColC     equ 5
;----------------------------------------------------------------
; Results from The Calculator v1.10 by RuiLoureiro
; ------------------------------------------------

; a=[1,2,3 ; 4,5,6; 7,8,9; 10,11,12; 13,14,15];
; b=[1,2,3,1,0 ; 4,5,1,0,1 ;  0,8,9,6,7 ];
;
; c=a*b
;
;c=[ 9.0,  36.0,  32.0,  19.0,  23.0;
;   24.0,  81.0,  71.0,  40.0,  47.0;
;   39.0, 126.0, 110.0,  61.0,  71.0;
;   54.0, 171.0, 149.0,  82.0,  95.0;
;   69.0, 216.0, 188.0, 103.0, 119.0];
;----------------------------------------------------------------
.code
;==============================================================================
; Address of element (iLin,jCol) = esi + (iLin-1)* maxCol * 4 + (jCol-1)*4
;
; Assigning Registers:
;                       eax - iLin
;                       edx - maxCol
;                       ebx - jCol
;
; Output:
;           EAX     - element in iLin, jCol
;
; Info:
;           Preserves all registers except EDX
;
GetElement  proc    pMtx:DWORD, iLin:DWORD, jCol:DWORD, maxLin:DWORD, maxCol:DWORD
            push    ebx
            push    esi
            ;
            mov     esi, pMtx
           
            mov     ebx, jCol           ; jCol must be 1 - maxCol
            sub     ebx, 1              ; it cannot be 0
            ;
            mov     edx, maxCol
            mov     eax, iLin           ; iLin must be 1 - maxLin
            sub     eax, 1              ; it cannot be 0
           
            ; ---------------------------
            ; calculate (iLin-1) * maxCol
            ;   the result is in EAX
            ; ---------------------------
            mul     edx
            ; -------------
            ; multiply by 4
            ; -------------
            shl     eax, 2
            ; -----------------------------
            ; Starting address of line iLin
            ; -----------------------------
            add     esi, eax
            ; --------------------------------
            ; now we can access the element in
            ;    address [esi+ebx*4]
            ; --------------------------------
            mov     eax, dword ptr [esi+ebx*4]
            ;
            pop     esi
            pop     ebx
            ret
GetElement  endp
;==============================================================================
; Address of element (iLin,jCol) = esi + (iLin-1)* maxCol * 4 + (jCol-1)*4
;
; Assigning Registers:
;                       eax - iLin
;                       edx - maxCol
;                       ebx - jCol
; Input:
;           EAX     - element to store
;
; Output:
;           EAX     - element in iLin, jCol
;
; Info:
;           Preserves all registers except EDX
;
SetElement  proc    pMtx:DWORD, iLin:DWORD, jCol:DWORD, maxLin:DWORD, maxCol:DWORD
            push    ebx
            push    ecx
            push    esi
            ;
            mov     ecx, eax            ; save EAX in ecx
           
            mov     esi, pMtx
           
            mov     ebx, jCol           ; jCol must be 1 - maxCol
            sub     ebx, 1              ; it cannot be 0
            ;
            mov     edx, maxCol
            mov     eax, iLin           ; iLin must be 1 - maxLin
            sub     eax, 1              ; it cannot be 0
           
            ; ---------------------------
            ; calculate (iLin-1) * maxCol
            ;   the result is in EAX
            ; ---------------------------
            mul     edx
            ; -------------
            ; multiply by 4
            ; -------------
            shl     eax, 2
            ; -----------------------------
            ; Starting address of line iLin
            ; -----------------------------
            add     esi, eax
            ; --------------------------------
            ; now we can access the element in
            ;    address [esi+ebx*4]
            ; --------------------------------
            mov     dword ptr [esi+ebx*4], ecx
            ;
            pop     esi
            pop     ecx
            pop     ebx
            ret
SetElement  endp
; ««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««
; Multiply iLin of MatrixA by jCol of MatrixB
;
; Output:
;           EAX     - result
;
; Info:
;           Preserves all registers except EDX
;
MulLinbyCol proc    pMtxA:DWORD, iLin:DWORD, pMtxB:DWORD, jCol:DWORD
            push    ebx
            push    ecx
            push    edi
           
            ; -------------------
            ; Final result in edi
            ; -------------------
            xor     edi, edi
           
            ; -----------------------
            ; loop from column 5 to 1
            ; -----------------------
            mov     ecx, MAXColA        ; = MAXLinB
            ;
    @@:     invoke  GetElement, pMtxA, iLin, ecx, MAXLinA, MAXColA
            mov     ebx, eax
            ;
            invoke  GetElement, pMtxB, ecx, jCol, MAXLinB, MAXColB
            ;
            mul     ebx
            ;
            add     edi, eax
            ;
            sub     ecx, 1
            jnz     short @B
            ;
            mov     eax, edi
            ;
            pop     edi
            pop     ecx
            pop     ebx
            ret
MulLinbyCol endp
;==============================================================================
MultiplyAbyB    proc    pMtxA:DWORD, pMtxB:DWORD, pMtxC:DWORD
                push    ebx
               
                mov     ecx, MAXLinA          ; Line   ECX of _arrayA
                ;
    _nxtlin:    mov     ebx, MAXColB          ; column EBX of _arrayB
                ;
    _nxtcol:    invoke  MulLinbyCol, pMtxA, ecx, pMtxB, ebx

                invoke  SetElement, pMtxC, ecx, ebx, MAXLinC, MAXColC
                ;
                sub     ebx, 1
                jnz     short _nxtcol
                ;
                sub     ecx, 1
                jnz     short _nxtlin

                pop     ebx
                ret
MultiplyAbyB    endp
;==============================================================================
start:
;==============================================================================

            mov     edi, 0          ; Line EDI
            ;
_nextlin:   add     edi, 1
            ;   
            mov     ebx, 0          ; column EBX
            ;
_nextcol:   add     ebx, 1
                              ;    pMtx,     iLin, jCol, maxLin, maxCol
            invoke  GetElement, addr _arrayA, edi, ebx, MAXLinA, MAXColA

            push    eax                             ; preserve EAX
            ;    fn MessageBox,0,str$(edi),"LINE",MB_OK
            ;    fn MessageBox,0,str$(ebx),"COLUMN",MB_OK
            pop     eax
           
            ;fn MessageBox,0,str$(eax),"Element",MB_OK

            ;
            cmp     ebx, MAXColA
            jb      _nextcol
            ;
            cmp     edi, MAXLinA
            jb      _nextlin
;.............................................................................

            ; -----------------------------------------------------------
            ;     multiply arrayA by arrayB put the result in arrayC
            ; ------------------------------------------------------------
            invoke  MultiplyAbyB, addr _arrayA, addr _arrayB, addr _arrayC

;.............................................................................
; note: MessageBox trashes ECX,EDX we need to use EDI
           
            mov     edi, 0          ; Line EDI
            ;
_nextlin1:  add     edi, 1
            ;   
            mov     ebx, 0          ; column EBX
            ;
_nextcol1:  add     ebx, 1
                              ;    pMtx,     iLin, jCol, maxLin, maxCol
            invoke  GetElement, addr _arrayC, edi, ebx, MAXLinC, MAXColC

            push    eax                             ; preserve EAX
                fn MessageBox,0,str$(edi),"LINE",MB_OK
                fn MessageBox,0,str$(ebx),"COLUMN",MB_OK
            pop     eax
           
            fn MessageBox,0,str$(eax),"Element",MB_OK

            ;
            cmp     ebx, MAXColC
            jb      _nextcol1
            ;
            cmp     edi, MAXLinC
            jb      _nextlin1


            inkey
            exit
;==============================================================================
end start


RuiLoureiro

In matrix3.asm we have GetElement, SetElement, MulLinbyCol and MultiplyAbyB
To show, we have ShowArrayX

Now:
. Each line goes from 0 to maxLin-1 and each column goes from 0 to maxCol-1.
. GetElement and SetElement has only 4 arguments  (not 5 as before)
. We never test if iLin/jCol is outside the range in GetElement or SetElement.
   
    well, what was written in MulLinbyCol can be written in MultiplyAbyB but
    this is to show the steps so i didnt do that.
   
    problem that was not solved in this example:
    we need to define constants like MAXColA and this is a problem when we need to multiply 3 or 4 arrays one after another.

    have you one solution to this problem ?

matrix3.zip is (.exe, .asm)


; File:     matrix3.asm     is matrix2.asm version 2
;        by RuiLoureiro
; Date:  19/02/2013
;=========================================================
include \masm32\include\masm32rt.inc

GetElement      proto   :DWORD,:DWORD,:DWORD,:DWORD
SetElement      proto   :DWORD,:DWORD,:DWORD,:DWORD
MulLinbyCol     proto   :DWORD,:DWORD,:DWORD,:DWORD
MultiplyAbyB    proto   :DWORD,:DWORD,:DWORD
ShowArrayX      proto   :DWORD,:DWORD,:DWORD,:DWORD
;=========================================================
;      In this version each line must be called from 0 to maxLin-1
;          end each column must be called from 0 to maxCol-1
;========================================================
; note: see arrayA definition
;
; Len      = length of each element array = 1 DWORD = 4 bytes
;
; maxCol   = maximum number of columns = 3
; maxLin   =    "      "    of lines   = 5
;
; iLin     = current line   = number from 0 to maxLin-1
; jCol     =    "    column =   "      "  0 to maxCol-1
;
; LenLin   = length of each line = maxCol * Len = 3 * 4 = 12 bytes
;
; esi      = Base address of array = offset arrayA
;
; Starting address of line iLin = esi + iLin * LenLin
;                               = esi + iLin * maxCol * Len
;
; Address of element (iLin,jCol)= Starting address of line iLin + jCol*Len
;                               =     esi + iLin * maxCol * Len + jCol*Len
;
; Replacing Len by 4 (each element is 4 bytes), we have:
;
; Address of element (iLin,jCol) = esi + iLin* maxCol * 4 + jCol*4
;
; Assigning Registers:
;                       eax - iLin
;                       edx - maxCol
;                       ebx - jCol
;
; we should avoid EDX because multiplications trashes EDX: the result is in EDX:EAX
;
;=========================================================
.data
       ; column 1  2  3
       ;...................
_arrayA     dd  1, 2, 3         ; line 1
            dd  4, 5, 6         ; line 2
            dd  7, 8, 9         ; line 3
            dd 10,11,12         ; line 4
            dd 13,14,15         ; line 5

MAXLinA     equ 5
MAXColA     equ 3


       ; column 1  2  3  4  5
       ;.....................
_arrayB     dd  1, 2, 3, 1, 0   ; line 1
            dd  4, 5, 1, 0, 1   ; line 2
            dd  0, 8, 9, 6, 7   ; line 3

MAXLinB     equ 3
MAXColB     equ 5

_arrayC     dd   9, 36, 32, 19, 23
            dd  24, 81, 71, 40, 47
            dd  39,126,110, 61, 71
            dd  54,171,149, 82, 95
            dd  69,216,188,103,119
           
            dd 100 dup (0)      ; for 10*10 array

MAXLinC     equ 5
MAXColC     equ 5
;----------------------------------------------------------------
; a=[1,2,3 ; 4,5,6; 7,8,9; 10,11,12; 13,14,15];
; b=[1,2,3,1,0 ; 4,5,1,0,1 ;  0,8,9,6,7 ];
;
; Result from The Calculator v1.10 by RuiLoureiro
;
;c=[ 9.0,  36.0,  32.0,  19.0,  23.0;
;   24.0,  81.0,  71.0,  40.0,  47.0;
;   39.0, 126.0, 110.0,  61.0,  71.0;
;   54.0, 171.0, 149.0,  82.0,  95.0;
;   69.0, 216.0, 188.0, 103.0, 119.0];
;----------------------------------------------------------------
.code
;========================================================
; Address of element (iLin,jCol) = esi + iLin* maxCol * 4 + jCol*4
;
; Assigning Registers:
;                       eax - iLin
;                       edx - maxCol
;                       ebx - jCol
;
; Output:
;           EAX     - element in iLin, jCol
;
; Info:
;           Preserves all registers except EDX
;           We dont test iLin and iCol values here
;
GetElement      proc    pMtx:DWORD, iLin:DWORD, jCol:DWORD, maxCol:DWORD
                push    ebx
                push    esi
                ;
                mov     esi, pMtx
               
                mov     ebx, jCol           ; jCol must be 0 - maxCol-1
                ;
                ;mov     edx, maxCol
                mov     eax, iLin           ; iLin must be 0 - maxLin-1
           
                ; ---------------------------
                ;   calculate iLin * maxCol
                ;   the result is in EAX
                ; ---------------------------
                ;mul     edx
                mul     dword ptr maxCol
                ; -------------
                ; multiply by 4
                ; -------------
                shl     eax, 2
                ; -----------------------------
                ; Starting address of line iLin
                ; -----------------------------
                add     esi, eax
                ; --------------------------------
                ; now we can access the element in
                ;    address [esi+ebx*4]
                ; --------------------------------
                mov     eax, dword ptr [esi+ebx*4]
                ;
                pop     esi
                pop     ebx
                ret
GetElement      endp
;========================================================
; Address of element (iLin,jCol) = esi + iLin* maxCol * 4 + jCol*4
;
; Assigning Registers:
;                       eax - iLin
;                       ecx - maxCol
;                       ebx - jCol
; Input:
;           EAX     - element to store
;
; Output:
;           EAX     - element in iLin, jCol
;
; Info:
;           Preserves all registers except EDX
;           We dont test iLin and iCol values here
;
SetElement      proc    pMtx:DWORD, iLin:DWORD, jCol:DWORD, maxCol:DWORD
                push    ebx
                push    ecx
                push    esi
                ;
                mov     ecx, eax            ; save EAX in ecx
               
                mov     esi, pMtx
               
                mov     ebx, jCol           ; jCol must be 0 - maxCol-1
                ;
                ;mov     edx, maxCol
                mov     eax, iLin           ; iLin must be 0 - maxLin-1
           
                ; ---------------------------
                ; calculate (iLin-1) * maxCol
                ;   the result is in EAX
                ; ---------------------------
                ;mul     edx   
                mul     dword ptr maxCol
                ; -------------
                ; multiply by 4
                ; -------------
                shl     eax, 2
                ; -----------------------------
                ; Starting address of line iLin
                ; -----------------------------
                add     esi, eax
                ; --------------------------------
                ; now we can access the element in
                ;    address [esi+ebx*4]
                ; --------------------------------
                mov     dword ptr [esi+ebx*4], ecx
                ;
                pop     esi
                pop     ecx
                pop     ebx
                ret
SetElement      endp
; «««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««
; Action:
;           Multiply iLin of MatrixA by jCol of MatrixB
;
; Output:
;           EAX     - result
;
; Info:
;           Preserves all registers except EDX
;
MulLinbyCol     proc    pMtxA:DWORD, iLin:DWORD, pMtxB:DWORD, jCol:DWORD
                push    ebx
                push    ecx
                push    edi
           
                ; -------------------
                ; Final result in edi
                ; -------------------
                xor     edi, edi
           
                ; -----------------------
                ; loop from column 5 to 1
                ; -----------------------
                mov     ecx, MAXColA        ; = MAXLinB
                ;
        @@:     sub     ecx, 1
                js      short _exit
                ;
                invoke  GetElement, pMtxA, iLin, ecx, MAXColA
                mov     ebx, eax
                ;
                invoke  GetElement, pMtxB, ecx, jCol, MAXColB
                ;
                mul     ebx
                ;
                add     edi, eax
                jmp     short @B
                ;
        _exit:  mov     eax, edi
                ;
                pop     edi
                pop     ecx
                pop     ebx
                ret
MulLinbyCol     endp
;======================================================
; Action:
;           Multiply MatrixA by MatrixB
;           the result goes to MatrixC
;
; Info:
;           Preserves all registers except EDX and ECX
;
;
MultiplyAbyB    proc    pMtxA:DWORD, pMtxB:DWORD, pMtxC:DWORD
                push    ebx
               
                mov     ecx, MAXLinA          ; Line   ECX of _arrayA
                jmp     _start
                ;
    _nxtlin:    mov     ebx, MAXColB          ; column EBX of _arrayB
                ;
        @@:     sub     ebx, 1
                js      short _start
               
                invoke  MulLinbyCol, pMtxA, ecx, pMtxB, ebx

                invoke  SetElement, pMtxC, ecx, ebx, MAXColC
                jmp     short @B
                ;
    _start:     sub     ecx, 1
                jns     short _nxtlin

                pop     ebx
                ret
MultiplyAbyB    endp
; «««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««««
ShowArrayX      proc    pMtxX:DWORD, maxLin:DWORD, maxCol:DWORD, pTit:DWORD
                push    ebx
                push    edi
                ;
                mov     edi, 0          ; Line EDI
                ;
    _nextlin:   mov     ebx, 0          ; column EBX
                ;
                ;                      pMtx,     iLin, jCol, maxCol
    _nextcol:   invoke  GetElement, pMtxX, edi, ebx, maxCol

                push    eax                             ; preserve EAX
                    fn MessageBox,0,str$(edi),"LINE",MB_OK
                    fn MessageBox,0,str$(ebx),"COLUMN",MB_OK
                pop     eax

                    fn MessageBox,0,str$(eax), pTit, MB_OKCANCEL
                   
                cmp     eax, IDCANCEL
                je      short _exit
                ;
                add     ebx, 1
                cmp     ebx, maxCol
                jb      _nextcol
                ;
                add     edi, 1
                cmp     edi, maxLin
                jb      _nextlin
                ;
    _exit:      pop     edi
                pop     ebx
                ret
ShowArrayX      endp
;=========================================================
start:
;=========================================================

            invoke  ShowArrayX, addr _arrayA, MAXLinA, MAXColA, chr$("Element array A")

            invoke  ShowArrayX, addr _arrayB, MAXLinB, MAXColB, chr$("Element array B")
           
            ; -----------------------------------------------------------
            ;     multiply arrayA by arrayB put the result in arrayC
            ; ------------------------------------------------------------
            invoke  MultiplyAbyB, addr _arrayA, addr _arrayB, addr _arrayC


            invoke  ShowArrayX, addr _arrayC, MAXLinC, MAXColC, chr$("Result C= A * B")

            inkey
            exit
;=========================================================
end start


RuiLoureiro

Well,
now we have matrix4.asm to multiply arrays one after another
We have GetElement, SetElement and MultiplyAbyB.

matrix4.zip is (.exe and .asm)