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

Heap corruption from VB callback

David_F_9
Beginner
666 Views

The attached project is a distillation of an error that I am having when calling a Fortran DLL from a VB.Net executable.

We are trying to use a callback from the Fortran to display output in a VB rich text box. The included project is from Visual Studio 2012 and Intel Visual Fortran Composer XE 2013 SP1 Update 1.

This is the routine causing the error:

      SUBROUTINE WRWIN(OUTSTR)
C*
      USE IFCOM               ! defines CONVERTTOBSTR and FREESYSSTRING routines
      USE VB_WRWIN_MOD        ! defines VB_WRITEWINDOW VB routine
      
      INTEGER           IRC           ! <i> - screen unit to write to
      CHARACTER*(*)     OUTSTR        ! <i> - string to print

      POINTER      ( P2, MY_STR_OUT )
      INTEGER*2      MY_STR_OUT(128)
      
      P2 = CONVERTSTRINGTOBSTR( TRIM(OUTSTR) )
      CALL VBWRITEWINDOW1( P2, IRC )
      
      RETURN
      END

After the call to VBWRITEWINDOW1, execution stops in Visual Studio with "Windows has triggered a breakpoint in HelloWorld_Basic.exe. This may be due to a corruption of the heap, which indicates a bug in HelloWorld_Basic.exe or any of the DLLs it has loaded.

Added complications:

If I choose the Target Framework for the VB project as ".NET Framework 2.0", the program compiles and runs fine. This error only occurs when I change the framework to .NET Framework 4.5.

SLN file is in the HelloWorld_Basic folder. Both VB and Fortran projects are included in the same solution.

Any help would be greatly appreciated.

dave

0 Kudos
10 Replies
FortranFan
Honored Contributor II
666 Views

Dave,

I don’t wish to relive the days of working with VB6/COM data types, BSTRs, fixed-form source, old Cray-style POINTER extension, and such like.  Instead, I suggest an alternate approach where the Fortran code uses standard features for C interoperability and where the Visual Basic .NET code is kept fairly simple using the “Cdecl” calling convention.  With such an approach, you use .NET StringBuilder class for string passing to and from Fortran as shown below:

Option Strict Off
Option Explicit On

Imports System.Text
Imports System.Runtime.InteropServices

Public Class frmHelloWorld

   <UnmanagedFunctionPointer(CallingConvention.Cdecl)> _
   Public Delegate Sub WriteDelegate(SomeString As StringBuilder, ByRef Irc As Integer)

   <DllImport("HelloWorld_Fortran.DLL", CallingConvention:=CallingConvention.Cdecl)> _
   Public Shared Sub HelloWorld_Fortran(MsgString As StringBuilder, _
                                        <MarshalAs(UnmanagedType.FunctionPtr)> fPtr As WriteDelegate)
   End Sub

   Private Sub btnRun_Click(ByVal sender As System.Object, ByVal e As System.EventArgs) Handles btnRun.Click

      Dim strMessage As StringBuilder
      Dim IRC As Integer

      strMessage = New StringBuilder("From VB.NET: Hello World")

      Call RTBDisplayStatus(New StringBuilder("From VB.NET: Starting Fortran"), IRC)
      Call HelloWorld_Fortran( _
              strMessage, _
              AddressOf RTBDisplayStatus)

      Call RTBDisplayStatus(New StringBuilder("From VB.NET: Finished Fortran"), IRC)

   End Sub

   Public Sub RTBDisplayStatus(s1 As StringBuilder, ByRef irc As Integer)
      '
      'frmHelloWorld.vb / RTBDisplayStatus
      '
      RichTextBox1.Text += s1.ToString() & vbCrLf
      System.Windows.Forms.Application.DoEvents()
      '
   End Sub

End Class

The Fortran code that interoperates with the above VB.NET class is Fortran 2003 standard compliant barring the !DEC$ ATTRIBUTES for DLLEXPORT: note the use of ISO_C_BINDING intrinsic module for binding the procedures and for interoperable data types.  In addition, note the dummy argument for the string type is set up effectively as a character array of length 1 since strings in C are better viewed as a char array or a pointer to a char array.  Also, you will notice this argument is null-terminated.  These are all standard aspects of modern Fortran interoperability with C or a companion processor that is C-like which is what P/Invoke interoperability layer in ,NET becomes when "Cdecl" calling convention is used and marshaling is done as above in the Visual Basic setup.

MODULE FortranDll

   USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_CHAR, C_NULL_CHAR, C_INT

   IMPLICIT NONE

   PROCEDURE(VBWriteWindowInterface), POINTER :: VBWriteWindow

   ABSTRACT INTERFACE

      SUBROUTINE VBWriteWindowInterface(SomeString, ErrorCode) BIND(C)
         IMPORT :: C_CHAR, C_INT
         CHARACTER(KIND=C_CHAR,LEN=1), INTENT(INOUT) :: SomeString(*)
         INTEGER(C_INT), INTENT(INOUT) :: ErrorCode
      END SUBROUTINE VBWriteWindowInterface

   END INTERFACE

CONTAINS

   !DEC$ ATTRIBUTES DLLEXPORT::HelloWorld_Fortran
   SUBROUTINE HelloWorld_Fortran( InputString, fPtr_VBWriteWindow ) BIND(C, NAME="HelloWorld_Fortran")

      !.. Argument list
      CHARACTER(KIND=C_CHAR,LEN=1), INTENT(INOUT) :: InputString(*)
      PROCEDURE(VBWriteWindowInterface) :: fPtr_VBWriteWindow

      !.. Local variables
      CHARACTER(KIND=C_CHAR,LEN=1), ALLOCATABLE :: OutString(:) !.. Work char array
      CHARACTER(KIND=C_CHAR,LEN=:), ALLOCATABLE :: TempString   !.. Work Fortran string
      INTEGER(KIND=C_INT) :: Irc
      INTEGER :: StringLen
      INTEGER :: Istat
      INTEGER :: I

      !.. Set the procedure pointer
      VBWriteWindow => fPtr_VBWriteWindow

      ! Create our message, and pass both it and the return code to VbWriteWindow
      TempString = 'From Fortran: Hello World'
      StringLen = LEN_TRIM(TempString)
      !.. Allocate the work char array to StringLen+1 for null-termination
      ALLOCATE( CHARACTER(KIND=C_CHAR,LEN=1) :: OutString(StringLen+1), STAT=Istat)
      IF (Istat /= 0) THEN
         RETURN
      END IF

      !.. Copy string
      FORALL (I = 1:StringLen)
         OutString(I)(1:1) = TempString(I:I)
      END FORALL
      OutString(StringLen+1)(1:1) = C_NULL_CHAR !.. Null terminate

      Irc = 0
      CALL VBWriteWindow( OutString, Irc)

      !.. Clear the work areas for second message
      DEALLOCATE(TempString, STAT=Istat)
      IF (Istat /= 0) THEN
         RETURN
      END IF
      DEALLOCATE(OutString, STAT=Istat)
      IF (Istat /= 0) THEN
         RETURN
      END IF

      !.. Determine input string length; check for null-termination
      StringLen = 0
      Loop_SizeVec: DO !
         IF (InputString(StringLen+1) == C_NULL_CHAR) THEN
            EXIT Loop_SizeVec
         END IF
         StringLen = StringLen + 1
         IF (StringLen == 2048) THEN !.. Replace: arbitrary large length
            EXIT Loop_SizeVec
         END IF
      END DO Loop_SizeVec
      IF (StringLen == 0) RETURN

      ALLOCATE( CHARACTER(KIND=C_CHAR,LEN=StringLen) :: TempString, STAT=Istat)
      IF (Istat /= 0) THEN
         RETURN
      END IF
      !.. Copy string
      FORALL (I = 1:StringLen)
         TempString(I:I) = InputString(I)(1:1)
      END FORALL

      !
      ! Create our message, and pass both it and the return code to VbWriteWindow1
      TempString = 'Through Fortran: ' // TempString
      StringLen = LEN_TRIM(TempString)
      ALLOCATE( CHARACTER(KIND=C_CHAR,LEN=1) :: OutString(StringLen+1), STAT=Istat)
      IF (Istat /= 0) THEN
         RETURN
      END IF

      !.. Copy string
      FORALL (I = 1:StringLen)
         OutString(I)(1:1) = TempString(I:I)
      END FORALL
      OutString(StringLen+1)(1:1) = C_NULL_CHAR !.. Null terminate
      
      Irc = 0
      CALL VBWriteWindow( OutString, Irc)

      !..
      RETURN

   END SUBROUTINE HelloWorld_Fortran

END MODULE FortranDll

I've also attached the zip file of the Visual Studio 2012 solution.  When you run this, you should get results as shown below and no heap corruption issues.

Results.png

I find this approach a lot cleaner and simpler to work with.  But if you prefer the old style, then I'll leave it to one of the more patient readers who will have a fix your problem (perhaps a simple tweak in your original VB code to ByRef vs ByVal).

Hope this helps,

0 Kudos
DavidWhite
Valued Contributor II
666 Views

I'm not able to download either of these files - I keep getting a file not found error.

---Edit

But the link properties have now changed, and I can download them.  What is happening on the forum???---

David

0 Kudos
DavidWhite
Valued Contributor II
666 Views

Can you tell me what I need to set up in the VB project to get it to work in VS2010?  I can't open the 2012 VB project.

Thanks,

David

0 Kudos
FortranFan
Honored Contributor II
666 Views

David White wrote:

Can you tell me what I need to set up in the VB project to get it to work in VS2010?  I can't open the 2012 VB project.

..

David

Suggest 3 options:

  1. Install SP1 for Visual Studio 2010; with this, many VS2012 projects open in VS2010.  The project in this case is simple enough that this option might work.
  2. Install a freeware converter such as VSProjectConverter at http://vsprojectconverter.codeplex.com/ and use it to convert the VS2012 back to VS2010.
  3. Note again the project in this case is very simple with just one source file, frmHelloWorld.vb, the updated version of which is available in the zip in Quote #2.  So just start afresh: create a new VB project for a Windows application in VS2010, add the file (may be you need frmHelloWorld.Designer.vb file as well which is also in the zip), and build the solution.

 

0 Kudos
David_F_9
Beginner
666 Views

Many thanks to FortranFan. I will look into implementing this for our projects.

Any possible help with the existing code would be appreciated. (implementing anything new on the Fortran side would involve touching 20 separate programs. Fixing the VB would only involve one program.)

Thanks to all who have looked so far!

0 Kudos
DavidWhite
Valued Contributor II
666 Views

Thanks, for the tips.  Eventually got it working under VS2010.

Just a couple of points:

1. DLL name is case sensitive, my VS creates *.dll, so had to change the name in the VB code.

2. DLL needs to be on PATH; VB code could not find it.  I added full path to DLL but adding location to PATH would work too.

3. Minor change needed in Fortran code to Deallocate Outstring before attempting to Allocate it.  Otherwise, clicking on Run a second time causes the Fortran routine to return prematurely.  Immediatelly before the allocate statement, need:

IF (ALLOCATED(OutString)) DEALLOCATE(OutString)

Regards,

David

0 Kudos
FortranFan
Honored Contributor II
666 Views

David White wrote:

...

1. DLL name is case sensitive, my VS creates *.dll, so had to change the name in the VB code.

2. DLL needs to be on PATH; VB code could not find it.  I added full path to DLL but adding location to PATH would work too.

3. Minor change needed in Fortran code to Deallocate Outstring before attempting to Allocate it.  Otherwise, clicking on Run a second time causes the Fortran routine to return prematurely.  Immediatelly before the allocate statement, need:

...

David,

Very good catches:

  1. But I'm surprised about DLL name being case sensitive.  Where do you see that?  The only place in VB where the name appears is in DLLImport attribute and I have never noticed any case sensitivity: I just tried the same DLL name with several different cases, but didn't find any issues.
  2. The setup in the original post used side-by-side execution i.e., the VB exe and the Fortran DLL in the same folder.  This will work too.
  3. I normally use the default local storage setting for Fortran projects in Visual Studio i.e., /QAuto.  With this, local variables in Fortran do not get the SAVE attribute unless specified as such.  This works well with ALLOCATABLE variables in "modern" Fortran as one of the benefits is they get deallocated automatically upon RETURN from a procedure.  In my hurry, I didn't realize the OP had /QSave setting in the Fortran project; if this is changed to /QAuto, then the code in Quote #2 should work as-is.  Regardless, it can be considered good practice to employ IF (ALLOCATED(object)) query prior to any ALLOCATE statement.

 

0 Kudos
Steven_L_Intel1
Employee
666 Views

David White wrote:

But the link properties have now changed, and I can download them.  What is happening on the forum???---

 

The forum is now (after a LONG time of not doing so) storing attachments in separate folders - perhaps there was some migration going on.

 

0 Kudos
David_F_9
Beginner
666 Views

Thanks again to FortranFan. I was able to implement these changes in our development code, and everything is running smoothly again, updated to Visual Studio 2012 and .NET 4.5.
 

0 Kudos
FortranFan
Honored Contributor II
666 Views

Glad to read you were able to make use of the suggested changes.

0 Kudos
Reply