Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28381 Discussions

Fortran DLL inside VBA, 64bit vs 32bit

Lorenzo_W_
Beginner
1,777 Views

I'm writing a Fortran DLL that has to bread by several tools, including Excel, so I'm writing an Excel extension (.xla).

Until now, I am able to correctly work with 32bit version of Excel but now I would like to write something compatible with both versions of Excel.

This is a working 32bit example (FORTRAN):

module my_module
contains
    subroutine div_num(A,B,C,ierr,errstring)! bind(c, name='div_num')
        !!============================================================================================  
        !! ** Division of two numbers: C = A/B **  
        !!INPUT : A, B  
        !!OUTPUT: C  
        !!============================================================================================  
        !DEC$ ATTRIBUTES DLLEXPORT, STDCALL, REFERENCE, ALIAS:"div_num" :: div_num
        implicit none
        real*8             , intent(in)    :: A                !! First number  
        real*8             , intent(in)    :: B                !! Second number  
        real*8             , intent(out)   :: C                !! Result  
        logical            , intent(out)   :: ierr             !! Logical stating if there is an error  
        character(256)     , intent(out)   :: errstring        !! String containing the error  
        !DEC$ ATTRIBUTES REFERENCE :: A,B,C,ierr,errstring
        !------------------------------------------------------------------------
        if (B .EQ. 0.0d0) then
            ierr = .TRUE.
        else
            ierr = .FALSE.
        endif
        !
        if (ierr) then
            C = -1.0d6
            errstring = "Error: you can't divide by zero!"
            return
        else
            C = A/B
            errstring = ""
        endif
        !
    end subroutine div_num
end module my_module

 

VBA :

Option Explicit
Option Base 1
'
'-----------------------------------------------------------------------------------------------------------------------------------
' Common declarations
Dim ierr            As Boolean
Dim errstring       As String * 256
'
'-----------------------------------------------------------------------------------------------------------------------------------
' Lettura dll
#If Win64 Then
    Declare PtrSafe Sub div_num Lib "S:\Winchler_Lorenzo\testDLL_x64_Debug.dll" (A As Double, B As Double, C As Double, ierr As Boolean, ByVal errstring As String)
#Else
    Declare Sub div_num Lib "S:\Winchler_Lorenzo\testDLL_Win32_Debug.dll" (A As Double, B As Double, C As Double, ierr As Boolean, ByVal errstring As String)
#End If

'-----------------------------------------------------------------------------------------------------------------------------------
Public Function VBA_div(x1 As Double, x2 As Double) As Double
    '------------------------------------------------------------------------------------------------------
    ' Division of two numbers
    '
    ' INPUTS:
    ' - x1:                 first number
    ' - x2:                 second number
    '
    ' OUTPUTS:
    ' - VBA_div:        division between the numbers
    '---------
    ' declarations
    Dim xOUT            As Double
    '---------
    '
    Call div_num(x1, x2, xOUT, ierr, errstring)
    '
    VBA_div = xOUT
    '
End Function
'-----------------------------------------------------------------------------------------------------------------------------------

The only modification I made inside VBA is the "PtrSafe" declaration, but it's not working inside 64bit Excel. Obviously I am pointing at the right dll, differently for the 32-64bit case.

The documentation provides the example only for 32bit case, and I don't know what I have to change to make the dll work inside 64bit Excel.

Thank you for your help

 

Lorenzo

0 Kudos
1 Solution
avinashs
New Contributor I
1,777 Views

I have struggled with using Fortran DLLs in 64-bit Office too. I have a few comments that may help based on my experience but not a complete solution. I am hoping this will be resolved although it is really a Microsoft Office problem as well.

Comments:

1. Microsoft recommends using 32-bit Office unless the memory requirements exceed 2 GB (more than enough for many applications).
2. Microsoft also cautions that VBA code that contains the Declare Sub or Declare Function may not work with 64-bit across the board without error. Hence, stick to 32-bit. This tells me that have identified some problems too.
3. You may have to include some new declarations such as LongLong, LongPtr and PtrSafe for certain data types. I am not sure how they map to Fortran data types.
4. The API function CopyMemory has trouble in 64-bit with variables passed through the DLL. This appears to be a problem faced by many developers for DLLs created in other languages as well (C,C++).
5. For 64-bit, I build the IVF dll in Release x64 configuration with /iface:cvf option and libs:static. In fact, even in 32-bit, only that configuration works in all cases.
6. I have trouble with the VBA directives #Win64 etc. in 64-bit. The interpreter does not allow declaring a sub without PtrSafe even for the 32-bit case. In particular, the Microsoft recommended method in the following pseudocode results in errors.

	#if Vba7 then 
	'  Code is running in the new VBA7 editor 
		 #if Win64 then 
		 '  Code is running in 64-bit version of Microsoft Office 
		 #else 
		 '  Code is running in 32-bit version of Microsoft Office 
		 #end if 
	#else 
	' Code is running in VBA version 6 or earlier 
	#end if 
	 
	#If Vba7 Then 
		Declare PtrSafe Sub ... 
	#Else 
		Declare Sub ... 
	#EndIf

View solution in original post

0 Kudos
2 Replies
avinashs
New Contributor I
1,778 Views

I have struggled with using Fortran DLLs in 64-bit Office too. I have a few comments that may help based on my experience but not a complete solution. I am hoping this will be resolved although it is really a Microsoft Office problem as well.

Comments:

1. Microsoft recommends using 32-bit Office unless the memory requirements exceed 2 GB (more than enough for many applications).
2. Microsoft also cautions that VBA code that contains the Declare Sub or Declare Function may not work with 64-bit across the board without error. Hence, stick to 32-bit. This tells me that have identified some problems too.
3. You may have to include some new declarations such as LongLong, LongPtr and PtrSafe for certain data types. I am not sure how they map to Fortran data types.
4. The API function CopyMemory has trouble in 64-bit with variables passed through the DLL. This appears to be a problem faced by many developers for DLLs created in other languages as well (C,C++).
5. For 64-bit, I build the IVF dll in Release x64 configuration with /iface:cvf option and libs:static. In fact, even in 32-bit, only that configuration works in all cases.
6. I have trouble with the VBA directives #Win64 etc. in 64-bit. The interpreter does not allow declaring a sub without PtrSafe even for the 32-bit case. In particular, the Microsoft recommended method in the following pseudocode results in errors.

	#if Vba7 then 
	'  Code is running in the new VBA7 editor 
		 #if Win64 then 
		 '  Code is running in 64-bit version of Microsoft Office 
		 #else 
		 '  Code is running in 32-bit version of Microsoft Office 
		 #end if 
	#else 
	' Code is running in VBA version 6 or earlier 
	#end if 
	 
	#If Vba7 Then 
		Declare PtrSafe Sub ... 
	#Else 
		Declare Sub ... 
	#EndIf
0 Kudos
Lorenzo_W_
Beginner
1,777 Views

avinashs wrote:

I have struggled with using Fortran DLLs in 64-bit Office too. I have a few comments that may help based on my experience but not a complete solution. I am hoping this will be resolved although it is really a Microsoft Office problem as well.

Comments:

1. Microsoft recommends using 32-bit Office unless the memory requirements exceed 2 GB (more than enough for many applications).
2. Microsoft also cautions that VBA code that contains the Declare Sub or Declare Function may not work with 64-bit across the board without error. Hence, stick to 32-bit. This tells me that have identified some problems too.
3. You may have to include some new declarations such as LongLong, LongPtr and PtrSafe for certain data types. I am not sure how they map to Fortran data types.
4. The API function CopyMemory has trouble in 64-bit with variables passed through the DLL. This appears to be a problem faced by many developers for DLLs created in other languages as well (C,C++).
5. For 64-bit, I build the IVF dll in Release x64 configuration with /iface:cvf option and libs:static. In fact, even in 32-bit, only that configuration works in all cases.
6. I have trouble with the VBA directives #Win64 etc. in 64-bit. The interpreter does not allow declaring a sub without PtrSafe even for the 32-bit case. In particular, the Microsoft recommended method in the following pseudocode results in errors.

	#if Vba7 then 
	'  Code is running in the new VBA7 editor 
		 #if Win64 then 
		 '  Code is running in 64-bit version of Microsoft Office 
		 #else 
		 '  Code is running in 32-bit version of Microsoft Office 
		 #end if 
	#else 
	' Code is running in VBA version 6 or earlier 
	#end if 
	 
	#If Vba7 Then 
		Declare PtrSafe Sub ... 
	#Else 
		Declare Sub ... 
	#EndIf

Thank you for your comments!
Compiling the dll with "/iface:cvf" and "/libs:static" as you suggested me, works like a charm!!!

Regarding the Long/LongPtr: this modification is needed only if your argument is returning a pointer or a location. If it's "just" an integer value, you can leave "Long".

 

Thank you so much

 

Lorenzo

 

0 Kudos
Reply