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

64bit Fortran DLL works when called from VBA but not from VB.NET

dfousekcres_gr
Beginner
1,042 Views

Hi !

I want to port my 32bit VB-Fortran code to the 64bit platform, consisting in calling a fortran DLL both from VBA (ie: Excel) and VB.NET. In the attached pieces of code, everything runs fine in 32bit OS. In 64bit OS, VBA (64bit Excel) works fine, but VB.NET  (calling the same 64bit DLL) crashes.
All fortran compilations (both 32bit and 64bit) were done as: ifort -dll -static polar.for 
Does anybody has an idea what am I doing wrong?

VB.NET code
    Private Declare Sub check1 Lib "c:\temp\polar.dll" (ByRef s1 as Single, ByRef i1 As Integer)
    Private Declare Sub check0 Lib "c:\temp\polar.dll" (ByRef d1 As Double, ByRef i1 As Integer)

 

        Dim aa As Single, ii As Integer : aa = 0.5 : ii = 6
        Call check1(aa, ii) 'works OK
        MsgBox("aa=" & aa.ToString & " ii=" & ii.ToString)

        Dim bb(0 To 1000 - 1) As Double, jj(0 To 1000 - 1) As Integer
        Call check0(bb(0), jj(0)) 'crashes !!!
        MsgBox("bb(0)=" & bb(0).ToString & " jj(0)=" & jj(0).ToString)

VBA code
        Private Declare PtrSafe Sub check1 Lib "c:\temp\polar.dll" (s1 As Single, i1 As Long)
        Private Declare PtrSafe Sub check0 Lib "c:\temp\polar.dll" (d1 As Double, i1 As Long)

        Dim aa As Single, ii As Long: aa = 0.5: ii = 6
        Call check1(aa, ii) 'works OK
        MsgBox "aa=" & Str$(aa) & " ii=" & Str$(ii)

        Dim bb(0 To 1000 - 1) As Double, jj(0 To 1000 - 1) As Long
        Call check0(bb(0), jj(0)) 'works OK
        MsgBox "bb(0)=" & Str$(bb(0)) & " jj(0)=" & Str$(jj(0))

 

FORTRAN code
      SUBROUTINE check1 (a,n)
!dec$ attributes dllexport,stdcall,reference,alias : "check1" :: check1
      REAL*4 a
      INTEGER*4 n
      a = a + 1.0
      n = n - 1
      RETURN
      END

      SUBROUTINE check0 (a,n)
!dec$ attributes dllexport,stdcall,reference,alias : "check0" :: check0
      REAL*8 a(0:999)
      INTEGER*4 n(0:999)
      a = 3.14159
      n = -999
      RETURN
      END

 

0 Kudos
1 Solution
FortranFan
Honored Contributor II
1,042 Views

dfousekcres.gr wrote:

Hi FortranFan !

It works on x86 systems, therefore why stdcall  would be performed differently on x64 systems?

Dimitri

Dimitri,

With C calling convention and standard C interoperability features in Fortran, both x86 and x64 seem to work as shown below.  Perhaps you can take this and adapt it for your needs.  I've long left stdcall behind and can't recall many of the details, but I thought it was largely irrelevant for x64 systems - so you may want to investigate on MSDN.com.  But then I don't know if the code below would work with VBA,  You can try it out and report back here. 

By the way, are you really interested in passing fixed size arrays across?  A better option might be to have assumed size arrays on Fortran side with an additional parameter for the size and on the .NET side, just pass arrays by reference along with the size parameter.

Good luck,

Fortran code:

module m

   use, intrinsic :: iso_c_binding, only : c_int, c_double, c_float

   implicit none

   private

   public :: check1
   public :: check0

contains

   subroutine check1(a, n) bind( c, name="check1" )

      !.. argument list
      real(kind=c_float), intent(inout)  :: a
      integer(kind=c_int), intent(inout) :: n

      a = a + 1.0_c_float
      n = n - 1_c_int

      return

   end subroutine check1

   subroutine check0(a, n) bind( c, name="check0" )

      !.. argument list
      real(kind=c_double), intent(inout) :: a(0:999)
      integer(kind=c_int), intent(inout) :: n(0:999)

      a = 3.14159_c_double
      n = 999_c_int

      return

   end subroutine check0

end module m

VB.NET code:

Imports System.Collections.Generic
Imports System.Text
Imports System.Runtime.InteropServices

Namespace Fortran

   Public Class Testdll

      Public Const N As Integer = 1000

      <DllImport("TESTDLL.DLL", CallingConvention := CallingConvention.Cdecl)> _
      Friend Shared Sub check1(ByRef a As Single, ByRef n As Integer)
      End Sub

      <DllImport("TESTDLL.DLL", CallingConvention := CallingConvention.Cdecl)> _
      Friend Shared Sub check0(<MarshalAs(UnmanagedType.LPArray, SizeConst := N)> a As Double(), <MarshalAs(UnmanagedType.LPArray, SizeConst := N)> n__1 As Integer())
      End Sub

   End Class

End Namespace
Imports System.IO
Imports System.Text
Imports System.Runtime.InteropServices

Namespace Fortran

   NotInheritable Class TestDotNetClass

      Private Sub New()
      End Sub

      Private Shared Sub Main()

         Dim a As Single
         Dim n As Integer
         Dim a_arr As Double()
         Dim n_arr As Integer()

         ' Write header
         Console.WriteLine("*** Test Fortran Interop using VB ***" + vbLf)
         Console.WriteLine(vbLf & vbLf)

         Try

            a = 0F
            n = 1
            Testdll.check1(a, n)

            Console.WriteLine(" a = " + a.ToString("###0.0#") + ", n = " + n.ToString("###0"))

            a_arr = New Double(Testdll.N - 1) {}
            n_arr = New Integer(Testdll.N - 1) {}
            For i As Integer = 0 To Testdll.N - 1
               a_arr(i) = 0.0
               n_arr(i) = 0
            Next

            Testdll.check0(a_arr, n_arr)

            Console.WriteLine(" a_arr = " + a_arr(0).ToString() + ", n = " + n_arr(0).ToString())
         Catch ex As Exception
            Console.WriteLine(ex.Message)
         Finally
            Console.WriteLine("Press any key to continue..")
            Console.ReadKey()
         End Try

      End Sub

   End Class

End Namespace

 

View solution in original post

0 Kudos
4 Replies
FortranFan
Honored Contributor II
1,042 Views

Earlier message deleted.  Not sure what could cause the crash, perhaps stdcall is causing some issues?

0 Kudos
dfousekcres_gr
Beginner
1,042 Views

Hi FortranFan !

It works on x86 systems, therefore why stdcall  would be performed differently on x64 systems?

Dimitri

0 Kudos
FortranFan
Honored Contributor II
1,043 Views

dfousekcres.gr wrote:

Hi FortranFan !

It works on x86 systems, therefore why stdcall  would be performed differently on x64 systems?

Dimitri

Dimitri,

With C calling convention and standard C interoperability features in Fortran, both x86 and x64 seem to work as shown below.  Perhaps you can take this and adapt it for your needs.  I've long left stdcall behind and can't recall many of the details, but I thought it was largely irrelevant for x64 systems - so you may want to investigate on MSDN.com.  But then I don't know if the code below would work with VBA,  You can try it out and report back here. 

By the way, are you really interested in passing fixed size arrays across?  A better option might be to have assumed size arrays on Fortran side with an additional parameter for the size and on the .NET side, just pass arrays by reference along with the size parameter.

Good luck,

Fortran code:

module m

   use, intrinsic :: iso_c_binding, only : c_int, c_double, c_float

   implicit none

   private

   public :: check1
   public :: check0

contains

   subroutine check1(a, n) bind( c, name="check1" )

      !.. argument list
      real(kind=c_float), intent(inout)  :: a
      integer(kind=c_int), intent(inout) :: n

      a = a + 1.0_c_float
      n = n - 1_c_int

      return

   end subroutine check1

   subroutine check0(a, n) bind( c, name="check0" )

      !.. argument list
      real(kind=c_double), intent(inout) :: a(0:999)
      integer(kind=c_int), intent(inout) :: n(0:999)

      a = 3.14159_c_double
      n = 999_c_int

      return

   end subroutine check0

end module m

VB.NET code:

Imports System.Collections.Generic
Imports System.Text
Imports System.Runtime.InteropServices

Namespace Fortran

   Public Class Testdll

      Public Const N As Integer = 1000

      <DllImport("TESTDLL.DLL", CallingConvention := CallingConvention.Cdecl)> _
      Friend Shared Sub check1(ByRef a As Single, ByRef n As Integer)
      End Sub

      <DllImport("TESTDLL.DLL", CallingConvention := CallingConvention.Cdecl)> _
      Friend Shared Sub check0(<MarshalAs(UnmanagedType.LPArray, SizeConst := N)> a As Double(), <MarshalAs(UnmanagedType.LPArray, SizeConst := N)> n__1 As Integer())
      End Sub

   End Class

End Namespace
Imports System.IO
Imports System.Text
Imports System.Runtime.InteropServices

Namespace Fortran

   NotInheritable Class TestDotNetClass

      Private Sub New()
      End Sub

      Private Shared Sub Main()

         Dim a As Single
         Dim n As Integer
         Dim a_arr As Double()
         Dim n_arr As Integer()

         ' Write header
         Console.WriteLine("*** Test Fortran Interop using VB ***" + vbLf)
         Console.WriteLine(vbLf & vbLf)

         Try

            a = 0F
            n = 1
            Testdll.check1(a, n)

            Console.WriteLine(" a = " + a.ToString("###0.0#") + ", n = " + n.ToString("###0"))

            a_arr = New Double(Testdll.N - 1) {}
            n_arr = New Integer(Testdll.N - 1) {}
            For i As Integer = 0 To Testdll.N - 1
               a_arr(i) = 0.0
               n_arr(i) = 0
            Next

            Testdll.check0(a_arr, n_arr)

            Console.WriteLine(" a_arr = " + a_arr(0).ToString() + ", n = " + n_arr(0).ToString())
         Catch ex As Exception
            Console.WriteLine(ex.Message)
         Finally
            Console.WriteLine("Press any key to continue..")
            Console.ReadKey()
         End Try

      End Sub

   End Class

End Namespace

 

0 Kudos
dfousekcres_gr
Beginner
1,042 Views

Hi FortranFan,

The solution that you proposed (thanks for that!) works fine in principle.

I say "in principle" because it implies: i) filling all the numbers in my entire fortran code with the _c_float attribute:

1 a = a + 1.0_c_float
2 n = n - 1_c_int

and ii) it works with 1D arrays, but 2D arrays are of course returned in row-order, instead of, column-order.

Meanwhile the same VBA7 program (x64) works just fine without _c_float and _c_int attributes in the fortran side and with 2D arrays.

What is the secret of the Excel Microsoft VBA?

Kind regards,

Dimitri

0 Kudos
Reply