Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.

Problem linking in assembler code

anthonyrichards
New Contributor III
594 Views
I have an IVF (11.1.067) console program which references a subroutine in a COFF object file compiled from MASM assembler code that I have written. In the Assembler code and COFF .obj file the procedure name is _GETDOTPROD@20. It takes 5 arguments by reference.
I have added the GETDOTPROD.OBJ coff file to the solution. When I try and build the solution, the link fails with the message
Source2.obj : error LNK2019: unresolved external symbol _GETDOTPROD referenced in function _MAIN__

The console project program code is given below. I have tried to define an alias '_GETDOTPROD@20' for GETDOTPROD but this appears not to work. Any suggestions? By the way, Compaq VF has no problem linking in the identical fORTRAN and assembly code and finding _GETDOTPROD@20.

program timedotproduct
USE DFPORT
implicit none

INTERFACE
SUBROUTINE GETDOTPROD(A,B,N,K,X)
!$DEC ATTRIBUTES ALIAS: "_GETDOTPROD@20":: GETDOTPROD
!$DEC ATTRIBUTES REFERENCE:: A,B,N,K,X
INTEGER(4) N,K
REAL(8) A(N),B(N),X
END SUBROUTINE
END INTERFACE

INTEGER, PARAMETER::N=10000
REAL(8) A(N), B(N),X,Y
REAL(4) T1, T2, T3, T4
REAL(4) TFORT, TASSEM
INTEGER(4) I,J, M, K
CALL CPU_TIME(T1)
do i=1,N
A(I)=dble(I)
B(I)=2.0D0*dble(I)
enddo
!
!GETDOTPROD returns the dot product of arrays A and B up
! to the Kth element. The dot product is returned in X
! compare the assembler code with standard Fortran code
! to confirm no errors
!
TFORT=0.0D0
TASSEM=0.0D0
K=N
CALL CPU_TIME(T1)
DO J=1,100000
CALL DOTPROD(A,B,N,K,Y)
end do
CALL CPU_TIME(T2)
TFORT=T2-T1
CALL CPU_TIME(T3)
! GETDOTPROD code is in getdotprod.obj COFF file.
DO J=1,100000
call getdotprod(A,B,N,K,X)
END DO
CALL CPU_TIME(T4)
TASSEM=T4-T3
PRINT *,"TFORT =",TFORT,", TASSEM = ",TASSEM
PAUSE
end program timedotproduct

SUBROUTINE DOTPROD(A,B,N,K,SUM)
! Simplest dot-product code to compute the dot product up to the kth element
INTEGER(4) N
REAL(8) A(N),B(N), SUM
INTEGER(4) I
SUM=0.0D+0
DO I=1,K
SUM=SUM+A(I)*B(I)
END DO
RETURN
END
0 Kudos
3 Replies
anthonyrichards
New Contributor III
594 Views
Just to see what happens, I changed the procedure name in the assembler code from _GETDOTPROD@20 to _GETDOTPROD and rebuilt the COFF file and this time the IVF build and link worked. However, when I ran the program, the assembler code failed after four calls with an access violation.
My assembler code clears the stack of the five 4-byte arguments that are pushed there by the caller by using a 'ret 20' command. Then I recalled that, depending on the calling convention in operation, the calling program may clean up the stack and my assembler procedure should then just execute a 'ret' command. So I changed

pop esi ; recover all registers used in code:edx, eax, ecx, edi, esi from the stack
pop edi ; in reverse order
pop ecx
pop eax
pop edx
mov esp, ebp ; Restore stack pointer from epb and restore the base pointer
pop ebp
ret 20 ;Epilogue - drop the five arguments on the stack and return
_GETDOTPROD@20 ENDP
END

to

pop esi ; recover all registers used in code:edx, eax, ecx, edi, esi from the stack
pop edi ; in reverse order
pop ecx
pop eax
pop edx
mov esp, ebp ; Restore stack pointer from epb and pop the base pointer
pop ebp
ret ;Epilogue - drop the five arguments on the stack and return
_GETDOTPROD ENDP
END

and this time the program linked and ran OK without error. So I guess the IVF compiler was adding code to clean up the stack for me.

Unfortunately, I discovered that whereas the CVF-compiled dot-product code took 4.7 seconds compared to the 1.4 seconds that the assembler dot-product code took, the IVF dot-product code took 1.125 seconds compared to the 1.39 seconds that the assembler code took! So no gain there then, except I can now program a little in MASM X86 assembler!

P.S. I was able to remove some instructions from the assembler code and now I get TFORT = 11.31250 seconds , TASSEM = 11.81250 seconds for 100,000 dot-products of two vectors with 100,000 elements.
0 Kudos
Les_Neilson
Valued Contributor II
594 Views
Try

!DEC$ ATTRIBUTES STDCALL, DECORATE, ALIAS:'GETDOTPROD' :: 'GETDOTPROD'

The "stdcall" says to append the @n info

Les
0 Kudos
jimdempseyatthecove
Honored Contributor III
594 Views
Anthony,

When I am confronted with mixing MASM and FORTRAN in trying to get the calling convention and attributes etc. I find following a set of rules often does not show you what is going on. Therefore, I often find it useful to make a dummy shell function in .F90. Then compile with the options to produce assembler output. The resulting assembler listing of the shell function can then be cut and pasted into your MASM file. You will also see if the !DEC$ ATTRIBUTES may not have been set the way you expected.

Jim Dempsey
0 Kudos
Reply