- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
VBA Code:
Option Explicit
Option Base 1
Declare Sub sendarray Lib "C:\\Data\\Constitutive Material Behavior\\Material Modeling\\Templates\\Random Material Field Generator\\vs2008_dlltest\\Dll1\\Dll1\\Debug\\Dll1.dll" (ByRef arr() As Double, ByRef a As Double, ByRef b As Long, ByRef c As Long)
Sub testdll()
Dim i, j As Long
Dim testarray(1 To 3, 1 To 3) As Double
Dim y As Double
y = -1
For i = 1 To 3
For j = 1 To 3
testarray(i, j) = (CDbl(i) ^ 2 + CDbl(j) ^ 2) ^ 0.5
Next j
Next i
Call sendarray(testarray, y, 3, 3)
y = testarray(1, 1)
End Sub
FORTRAN Code:
subroutine sendarray(array,y,nrows,ncols)
!DEC$ ATTRIBUTES STDCALL,DLLEXPORT::sendarray
!DEC$ ATTRIBUTES REFERENCE::array
!DEC$ ATTRIBUTES REFERENCE::y
!DEC$ ATTRIBUTES REFERENCE::nrows
!DEC$ ATTRIBUTES REFERENCE::ncols
implicit none
integer*4,intent(in)::nrows
integer*4,intent(in)::ncols
real*8, intent(in)::array(1:nrows,1:ncols)
real*8, intent(out):: y
logical:: ex
INQUIRE(FILE='C:\\Data\\Constitutive Material Behavior\\Material Modeling\\Templates\\Random Material Field Generator\\vs2005_dlltest\\out.txt', EXIST=ex)
IF (ex) THEN
OPEN (UNIT=1, FILE='C:\\Data\\Constitutive Material Behavior\\Material Modeling\\Templates\\Random Material Field Generator\\vs2005_dlltest\\out.txt', STATUS='OLD')
CLOSE(UNIT=1, STATUS='DELETE')
END IF
OPEN (UNIT=1, FILE='C:\\Data\\Constitutive Material Behavior\\Material Modeling\\Templates\\Random Material Field Generator\\vs2005_dlltest\\out.txt', STATUS='NEW')
WRITE(1,*) nrows
WRITE(1,*) ncols
WRITE(1,*) array(1,1)
WRITE(1,*) array(2,1)
WRITE(1,*) array(3,1)
CLOSE(UNIT=1)
y=array(1,1)
return
end
The results in the file out.txt are below. As you can see the integers nrows and ncols are being passed in correctly, but the array is not.
3
3
2.122641981399731E-314
4.243991583412742E-314
2.642277455900980E-308
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for your response. Can you provide a link? I am using VBA in Excel which is different than standard VB. Do I still need to worry about SafeArray descriptors?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
yeah, I have tried that too. I have the same problem. I sent in a 3x1 array to a slightly modified code that will accept 1D arrays, with array(1)=1.0, but I get out 1.277...E-314.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks. I did find it and was able to look through the code. I saw that you modified it for multidimensional arrays. I must confess that after going through the example, I still do not understand how to apply this to my code. My background is structural mechanics and constitutive material modeling, so I am a bit out of my element. Can you be a bit more explicit about what I need to do? Thanks again!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
If you can manage to use a single-dimension array, things are much easier. See the other VB.NET sample provided for how to do that.
You may want to look instead (or also) at the Excel sample provided, which may be closer to what you are doing.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
(ByRef arr() As Double
to
(ByRef arr As Double
and change the call to address the first element of the array
call sendarray(arr(1,1),
and you will find that that works.
Here is my test code for an EXCEL file that uses a button to activate the code.
Option Explicit
Option Base 1
Declare Sub sendarray Lib "C:\F90\SENDARRAY\Debug\SENDARRAY.dll" (ByRef arr As Double, ByRef a As Double, ByRef b As Long, ByRef c As Long) As Long
Sub Button2_Click()
Dim i, j, nrows, ncols As Long
Dim testarray(1 To 3, 1 To 4) As Double
Dim y As Double
Dim iret As Long
nrows = 3
ncols = 4
y = -1
'Note the array element (i,j) will be given a decimal value 'ij'
'which makes its VBA index pair immediately recognisable from its value
'if it is examined on the Fotran side...
For i = 1 To nrows
For j = 1 To ncols
testarray(i, j) = 10 * CDbl(i) + CDbl(j)
Next j
Next i
MsgBox "Sending array to Fortran..."
iret = sendarray(testarray(1, 1), y, nrows, ncols)
MsgBox "Back from FortranFortran"
MsgBox "Returned value of Y =" + Str(y)
End Sub
The FORTRAN I used is
Subroutine SENDARRAY(ARRAY,Y,NROWS,NCOLS)
! Expose subroutine SENDARRAY to users of this DLL
!
! This will actually export a LOWER CASE name 'sendarray' !
!DEC$ ATTRIBUTES STDCALL, DLLEXPORT::SENDARRAY
!DEC$ ATTRIBUTES REFERENCE::ARRAY
!DEC$ ATTRIBUTES REFERENCE::y
!DEC$ ATTRIBUTES REFERENCE::nrows
!DEC$ ATTRIBUTES REFERENCE::ncols
use dflib
USE DFWIN
implicit none
integer*4,intent(in)::nrows
integer*4,intent(in)::ncols
real*8,intent(in):: array(nrows,ncols)
real*8 ,intent(out)::y
character(15) CHVALUE
character(10) chrow, chcol
INTEGER IRET
WRITE(CHrow,'(i8)') nrows
IRET=MESSAGEBOX(0,'Number of rows= '//chrow,'SENDARRAY dimensions...'c,mb_ok)
WRITE(CHcol,'(i8)') ncols
IRET=MESSAGEBOX(0,'Number of cols= '//chcol,'SENDARRAY dimensions...'c,mb_ok)
WRITE(CHVALUE,'(E15.6)') ARRAY(3,4)
IRET=MESSAGEBOX(0,'Array element (3,4)= '//chvalue,'SENDARRAY array values...'c,mb_ok)
Y=array(3,4)
return
end subroutine SENDARRAY
If you debug the Fortran DLL code by setting Excel as the executable to start the debug and load the attached Excel file when Excel starts, then press the button, you can halt the program in the Fortran .dll by adding a breakpoint to its code. Then, when the break-point is hit, you can inspect the values in the transferred Array and see how the array values are ordered. Surprisingly, I have found that a 3 row, 4 column array in the Visual Basic
code is stored exactly as a Fortran 3-row, 4 column array, in order 11,21,31,12,22,32,13,23,33,14,24,34
(see attached debug screen shot)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
That does indeed work! Thank you so much!!!
Rich
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
One mistake which Fortran programmers make when they work with VB is declaring the variables the Fortran way (here both Richard and Anthony):
Dim i, j, nrows, ncols As Long
In VB this means that only ncols is declared as long and all others are declared as default, which is Variant in VB. This may cause serious problems in many cases. The correct VB declaration is:
Dim i As Long, j As Long, nrows As Long, ncols As Long
Sabalan
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Sabalan and Anthony
Most likely I am missing something subtle here but I think Dim var1, var2 As DataType means that both variables are of DataType.
http://msdn.microsoft.com/en-us/library/7ee5a7s1(v=VS.100).aspx has an example of declaring multiple variables; the example there states that:
Dim a, b, c As Single, x, y As Double, i As Integer => a, b, and c are all Single; x and y are both Double
The above seems to be valid VS2005 onwards. The example given for VS2003 (the version can be chosen from the drop-down at the top of the link) does not explicitly mention this. In fact, the multiple declaration example (at the end of VS2003 help) seems to indicate what Sablan is saying. Or is there something about "Long" that I am missing here?
Abhi
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
that the VB6 DIM behaves differently to VB .NET (or vice - versa).
To quote from there:"
- Multiple Variable Declaration
VB 6 would let you code this line:
Dim var1, var2, var3 As String
But only var1 would actually be a String. In VB.NET, the result is entirely different:
Dim var1, var2, var3 As Date
MsgBox( _
"var1 type is: " & VarType(var1) & vbCrLf & _
"var2 type is: " & VarType(var2) & vbCrLf & _
"var3 type is: " & VarType(var3) _
)
All three are "Type 7" - Date in VB.NET. "- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I had suspected VB6 related issue; but I haven't used that. It is good to know what VBA in Excel 2003 is compatible with. Thanks for digging it out.
Abhi
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Abhi

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page