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

Passing strings from VBA to Fortran DLL

cb
Beginner
1,469 Views

I have a Fortran DLL created using Compaq Fortran that is called from Excel VBA.  Since being switched to a machine with Intel Fortran, I could not recompile the DLL.  I added the STDCALL attribute as suggested by the error message.  I've been able to get it to transfer scalar and array data with no problem but can't get it to transfer strings consistently.  The attached file has stripped down versions of the VBA declaration and call to the DLL, the Fortran module, and the system and software information.  Any help on this would be greatly appreciated.  Thanks in advance.

0 Kudos
14 Replies
IanH
Honored Contributor II
1,469 Views

(The attached file appears to have been stripped down just a little too much - it's missing!  Edit your post, drag the files onto the "Drag files here" region again - then make sure you hit "Start upload" before you hit "Submit".)

In the meantime - you have a few choices with string passing.  You can initially pass the string as a "BSTR" (a handle to the string) and manipulate it as such (this allows you to change the string contents, including its length) or you can pass the string as a relatively low level sequence of characters, in which case the length of the string is fixed.  One differences between CVF and IVF in this regard is the expected position of the hidden string length argument - perhaps this is tripping you up.  See the documentation for the compiler directive attribute MIXED_STR_LEN_ARG for more info.

I prefer to be explicit over passing the string length - having it as an explicit argument and then telling the compiler not to expect a hidden argument by explicitly specifying the reference attribute for the character argument.  Something like:

[fortran] 
  SUBROUTINE SomeProcedureName(filename, filename_len, ...)
  !DEC$ ATTRIBUTES DLLEXPORT, STDCALL :: SomeProcedureName
  !DEC$ ATTRIBUTES ALIAS:'SomeProcedureName' :: SomeProcedureName
    USE ExcelUtils, ONLY: ExcelIK   ! integer kind to match Long in Excel.
    !---------------------------------------------------------------------------
    INTEGER(ExcelIK), INTENT(IN) :: filename_len
    CHARACTER(filename_len), INTENT(IN) :: filename
    !DEC$ ATTRIBUTES REFERENCE :: filename
[/fortran]

which in VBA looks like a bit like...

[plain]Public Declare Sub SomeProcedureName Lib "NefariousUtilities.DLL" _
    (ByVal filename As String, ByVal filename_len As Long, ...)

Call SomeProcedureName(some_string, Len(some_string), ...)[/plain]

0 Kudos
cb
Beginner
1,469 Views

Sorry about that.  Let 's try it again.

0 Kudos
Anthony_Richards
New Contributor I
1,469 Views

Attached are a Visual Basic 2008 express project that can send a string TO a Fortran DLL routine and which can then GET a string from another Fortran DLL routine (the Fortran modifies a string sent by the VB calling program and sends it back in response to the GET). Interaction with the user is via buttons on a form. Messages are displayed showing each step in the progress of reading a string from a text box and sending it to the Fortran, which responds with a message that displays the received message. The VB program then confirms the GOT message into a text box.

Attached also is a zipped archive of the Intel Visual Fortran projects defining the Fortran routines that are exported and called.

(in order to reduce the file size so that it uploaded OK, I have removed the relatively large .DLL and the debug .PDB files from the /DEBUG/ folder of the FCALL project, so you will have to rebuild to get the .DLL.)

0 Kudos
cb
Beginner
1,469 Views

I wanted to thank both of you for the replies.  I tried Ian's approach and still had problems passing the string.  There was no error but when interrogating the string in Visual Studio, I got 'Undefined Address'.  I didn't try Anthony's because it seems so much more involved than what was necessary for Compaq Fortran.  I've tried numerous variations on whether the string is passed by value or by reference and with property settings for Calling Convention and String Length Argument Passing, but I always get a problem of some sort.  If I don't use STDCALL, the string is successfully passed into Fortran, but then I get an error on return to VBA.  I'm not sure where to go from here; it's frustrating to get stuck simply trying to transfer a string!

0 Kudos
IanH
Honored Contributor II
1,469 Views

The debugger gets confused sometimes with STDCALL procedures, with the amount of confusion varying by compiler/VS integration version (confusion still exists with 13.1+).  I think the debugger is still expecting the string length to be in the argument list where the compiler would put the string length in the absence of compiler directives to the contrary.  If the debugger is all you are relying upon to check that things are (or are not) working, then you may have been mislead. 

In your subroutine, open a text file, print the string to it (and perhaps the length of the string), close the text file, inspect the results. 

(You are using compiler version 11.0 according to your text file, which is getting a bit long in the tooth and may have its own specific issues that I can't check - been a long time since I had that one installed.)

Excel 32 bit absolutely requires STDCALL for VBA stuff.  If you don't have STDCALL you will corrupt the stack and then bad things will happen.

0 Kudos
andrew_4619
Honored Contributor II
1,469 Views

I have no experiance with VB but looking at the file DLL.txt you posted the VB string is passed by value and the fortran string is not specified so I would expect by referance......

0 Kudos
IanH
Honored Contributor II
1,469 Views

ByRef (which is the default if not specified) for a VBAstring (the A is significant - talking about the macro language variant of VB that is equivalent to VB version 6 in many ways, though I forget that on a cycle that has a period of about a year) means that the string is passed as a BSTR handle.  ByVal on the VBA side is what is required here - VBA will "dereference" the BSTR and pass a pointer to its contents.  Hidden length parameter aside, that's consistent with the Fortran receiving a CHARACTER variable by reference.

0 Kudos
andrew_4619
Honored Contributor II
1,469 Views

As I said no experiance.... But very interesting! That would not intuitivly be what I would expect.

0 Kudos
Anthony_Richards
New Contributor I
1,469 Views

You said you were converting to Intel Fortran, so I supplied an IVF project to create DLL's containing code that could be called from Visual Basic.
I repeat here the comments I have added for guidance into my Fortran code for the routines that I have programmed:

(from the routine that sends Fortran a string)
! The Visual Basic calling code specifies using the first argument by value (ByVal)
! hence the character string is supplied, whose Value is automatically
! assumed to be provided as the first argument, hence the character type for the first argument.
!
! The length of the character string has been made available by Visual Basic in its calling code
! as a second 'hidden' argument that Fortran expects and uses to set the amount of storage to
! reserve for the character string.
!
! Although Visual Basic stores strings as unicode (2 bytes per character) it automatically
! converts from unicode to Ascii when sending strings to external code
! (as indicated by the Declare statement in the VB code) such as C,C++ and, in the present
! case, Fortran). Hence the supplied string consists of ASCII characters (1 byte per character).

!
  SUBROUTINE SENDFORTRANSTRING (MYSTRINGIN)
  !DEC$ ATTRIBUTES DLLEXPORT, ALIAS : "SendFortranString" :: SENDFORTRANSTRING

(Now comments from the routine that grabs a string from Fortran):
! The Visual Basic calling code specifies using the first argument by reference (ByRef)
! hence a pointer to the character string is supplied, whose Value is automatically
! assumed to be provided as the first argument, hence the Integer type for the first argument.
!
! The length of the buffer made available by Visual Basic to take the returned string
! MUST be supplied, so that no more than this number of characters will be copied to the
! memory address pointed to by the first argument, thus removing the risk of buffer over-run.
! This length is explicitly supplied as the second argument, by value, and is not supplied
! as a 'hidden' argument (which would be the case if the first argument was supplied
! by value).
!
! Although Visual Basic stores strings as unicode (2 bytes per character) it automatically
! converts from unicode to Ascii when sending strings to external code
! (as indicated by the Declare statement in the VB code) and when receiveing strings back
! from such external code (such as C,C++ and, in the present case, Fortran)
!
  INTEGER FUNCTION GETFORTRANSTRING (PTRSTRING, BUFFLENGTH)
  !DEC$ ATTRIBUTES DLLEXPORT, ALIAS : "GetFortranString" :: GETFORTRANSTRING
  !DEC$ ATTRIBUTES VALUE:: BUFFLENGTH

If you just load the IVF projects into IVF, compile and build them and then copy the full path to the DLL's over to where they are declared in the Module of the VB project I have provided, then you can run the VB program and exercise both calls to the seperate Fortran routines. one to send a character string from VB to Fortran, the other to grab a character string from Fortran back to VB. Here are my own VB declarations:

Option Strict Off
Option Explicit On
Module Module1
    Declare Sub SendFortranString Lib "C:\Documents and Settings\agr42\My Documents\Visual Studio 2005\Projects\FORTDLLFROMVB\FCall\Debug\FCall.dll" (ByVal A1 As String, ByVal L1 As Integer)
    Declare Function GetFortranString Lib "C:\Documents and Settings\agr42\My Documents\Visual Studio 2005\Projects\FORTDLLFROMVB\FCall2\Debug\FCall2.dll" (ByRef A1 As String, ByVal L1 As Integer) As Short
End Module

I hope this helps.

0 Kudos
cb
Beginner
1,469 Views

Thanks Anthony.  I converted your VB code to VBA and it worked.  That was the way I was originally doing things with Compaq.  Now I realize the only thing I needed to do to get the original code to work was to specify the CVF calling convention in the Fortran external procedures menu.  Still not clear how to do it using the STDCALL convention but for now this works.

0 Kudos
Earl_Geddes
New Contributor I
1,469 Views

I have tried all of these suggestions and I am not getting results.

I use VS2013 and Intel Fortran (the latest version).

I want to pass a string from VB.Net to a FORTRAN DLL.  The string is a simple file path for the name of the file for FORTRAN to open.

Either the code won't compile or I get an error that I accessed forbidden memory.

All of the above seem to assume VBA and a different kind of string than used in VB.net.  Is this an issue?

0 Kudos
FortranFan
Honored Contributor II
1,469 Views

Earl Geddes wrote:

I have tried all of these suggestions and I am not getting results.

I use VS2013 and Intel Fortran (the latest version).

I want to pass a string from VB.Net to a FORTRAN DLL.  The string is a simple file path for the name of the file for FORTRAN to open.

Either the code won't compile or I get an error that I accessed forbidden memory.

All of the above seem to assume VBA and a different kind of string than used in VB.net.  Is this an issue?

See if the discussion in this topic - https://software.intel.com/en-us/forums/topic/509148 - is of help.  There is a fully worked out example in that link.

0 Kudos
DavidWhite
Valued Contributor II
1,469 Views

In one version of VB I have come across (not sure whether it is .NET), there was no way of defining a string length (unlike VBA).

The only way we could get the VBA-compatible fortran iterface to work with the VB code was to initialize the string in the VB code using something like

MyString=Space(20);

In this way, when calling the Fortran routine, the string argument size matched the character variable on the Fortran side.

Regards,

David

0 Kudos
FortranFan
Honored Contributor II
1,469 Views

Look at MSDN sites as http://msdn.microsoft.com/en-us/library/f47b0zy4(v=vs.90).aspx and http://msdn.microsoft.com/en-us/library/skw8dhdd(v=vs.90).aspx for language changes in Visual Basic in .NET Framework for Visual Basic 6.0 (which has a lot of commonality with VBA ) users.

As explained in another topic on this forum (https://software.intel.com/en-us/forums/topic/509148), Visual Basic .NET users can use StringBuilder class on the Visual Basic .NET side and C interoperability features in Fortran (starting with the Fortran 2003 standard) to develop mixed-language solutions.  The same concepts hold true for other .NET language users (e.g., C#) to work with Fortran code.

 

0 Kudos
Reply