Linking Excel to Fortran – 2

In this post the procedures described for C++ here will be replicated for Fortran:

The spreadsheet, fortran source code, and compiled dll described in this code may be downloaded from Cubic.zip

As always, it is better to use the downloaded code, rather than copying from the post, because the WordPress software changes quotes (“”) and several other characters, so that code copied and pasted from the post will often not run without editing.

This post describes:

  • Transferring arrays between VBA and Fortran.
  • Writing and compiling a simple Fortran function to solve quadratic equations, and linking to it from Excel.
  • Compiling a Fortran function to solve cubic equations, and linking from Excel. 
  • The Fortran code for the quadratic function (QUADA) is shown below:


    F_stdcall FUNCTION QUADA(qdat, ResA, NumRows)
    IMPLICIT NONE

    INTEGER, intent(in) :: NumRows
    REAL(2), intent(in) :: qdat(NumRows, 3)
    REAL(2), intent(out) :: ResA(NumRows,2)

    REAL(2) :: QUADA
    REAL(2) :: P, DIS

    INTEGER I

    DO I=1, NumRows

    IF (qdat(I,1).NE.0.D+0) THEN

    ! quadratic problem
    P=5.D-1*qdat(I,2)/qdat(I,1)
    DIS=P**2-qdat(I,3)/qdat(I,1)
    IF (DIS.GE.0.D+0) THEN
    ! two real solutions!
    ResA(I,1)=-P-SQRT(DIS)
    Resa(I,2)=-P+SQRT(DIS)
    QUADA=2
    ELSE
    ! no real solution!
    QUADA=0
    END IF

    ELSE IF (qdat(I,2).NE.0.D+0) THEN

    ! linear equation
    ResA(I,1)=-qdat(I,3)/qdat(I,2)
    QUADA=1

    ELSE
    ! no equation
    QUADA=0
    END IF
    END DO

    RETURN
    END FUNCTION QUADA

    Note that:

    • The function is preceded with “F_stdcall”
    • The function parameters: qdat, ResA, and NumRows are declared as either intent(in) or intent(out); intent(inout) is also allowed.
    • The arrays qdat and ResA are dynamic, and will be sized at run time to the size specified in NumRows
    • Paramaters that are specified as double in VBA are REAL(2) in Fortran
    • Parameters specified as Long in VBA are Integers in Fortran
    • It is essential to ensure that both the data types and the sizes of arrays in the VBA and Fortran routines match.

    The fortran routine is compiled as a dll as before, and may then be called from a VBA routine.  The dll has been named cubic.dll, since it contains both the quadratic and cubic functions:


    Declare Function QUADA Lib "D:\Users\...\Cubic\Release\Win32\Cubic.dll" (qdat As Double, ResA As Double, NumRows As Long) As Double

    Function FQuada(QuadData As Variant) As Variant
    Dim xa() As Double
    Dim A As Double, b As Double, c As Double
    Dim ResA() As Double, NumRows As Long
    Dim Retn As Double, i As Long, j As Long
    On Error Resume Next

    QuadData = QuadData.Value2
    NumRows = UBound(QuadData) – LBound(QuadData) + 1

    ReDim xa(1 To NumRows, 1 To 3)
    ReDim ResA(1 To NumRows, 1 To 2)
    For i = 1 To NumRows
    For j = 1 To 3
    xa(i, j) = QuadData(i, j)
    Next j
    Next i
    Retn = QUADA(xa(1, 1), ResA(1, 1), NumRows)

    FQuada = ResA

    End Function

    As for C++ dlls, array parameters are passed by reference by entering the first member of the array. Unlike C++, in Fortran the array members are named in the same way as VBA; i.e. ArrayName(Row No, Column No).

    A screen shot showing the output of the quadratic function is shown below:

    Output from QuadA

    Output from QuadA

    Fortran code for two Cubic functions, and the resulting dll, are included in the download files.  The code to call these functions from VBA is shown below:
    Declare Function CUBIC Lib “D:\Users\…\Cubic\Release\Win32\Cubic.dll” (cdat As Double, ResA As Double) As Double
    Declare Function CUBICA Lib “D:\Users\..,\Cubic\Release\Win32\Cubic.dll” (cdat As Double, ResA As Double, NumRows As Long) As Double

    Function FCUBIC(P As Variant) As Variant
    Dim P1(1 To 4) As Double, Res(1 To 1, 1 To 3) As Double
    Dim cval As Double, i As Long

    P = P.Value

    For i = 1 To 4
    P1(i) = P(1, i)
    Next i

    cval = CUBIC(P1(1), Res(1, 1))

    FCUBIC = Res

    End Function

    Function FCubica(CubicData As Variant) As Variant
    Dim xa(1 To 4) As Double
    Dim ResA1() As Double, ResA(1 To 1, 1 To 3) As Double, NumRows As Long
    Dim Retn As Double, i As Long, j As Long
    On Error Resume Next

    CubicData = CubicData.Value2
    NumRows = UBound(CubicData) – LBound(CubicData) + 1

    ReDim ResA1(1 To NumRows, 1 To 3)
    For i = 1 To NumRows
    For j = 1 To 4
    xa(j) = CubicData(i, j)
    Next j
    Retn = CUBIC(xa(1), ResA(1, 1))
    For j = 1 To 3
    ResA1(i, j) = ResA(1, j)
    Next j
    Next i

    FCubica = ResA1

    End Function

    Function FCubica2(CubicData As Variant) As Variant
    Dim xa() As Double
    Dim ResA() As Double, NumRows As Long
    Dim Retn As Long, i As Long, j As Long
    On Error Resume Next

    CubicData = CubicData.Value2
    NumRows = UBound(CubicData) – LBound(CubicData) + 1
    ReDim xa(1 To NumRows, 1 To 4)
    ReDim ResA(1 To NumRows, 1 To 3)
    For i = 1 To NumRows
    For j = 1 To 4
    xa(i, j) = CubicData(i, j)
    Next j
    Next i
    Retn = CUBICA(xa(1, 1), ResA(1, 1), NumRows)

    FCubica2 = ResA

    End Function

    The code includes one function that operates on one equation at a time, and two alternative array functions that provide much better performance by avoiding the transfer of data between the spreadsheet and VBA. For comparison VBA cubic functions are also included in the download file.

    Screenshot of cubic function output and relative performance results:

    cubic

    This entry was posted in Excel, Fortran, Link to dll, Maths, UDFs, Uncategorized, VBA and tagged , , , , , . Bookmark the permalink.

    23 Responses to Linking Excel to Fortran – 2

    1. R. Mitchell says:

      The procedure does’nt work in excel 2007

      Like

    2. dougaj4 says:

      R. Mitchell – It does work in Excel 2007. Did you read the previous posts?:

      https://newtonexcelbach.wordpress.com/2008/11/24/silverfrost-personal-fortran/

      https://newtonexcelbach.wordpress.com/2008/12/01/linking-excel-to-fortran/

      If you read those and it still doesn’t work for you please post exactly what the problem is and I’ll see if I can help.

      Like

    3. Pingback: Distributing Silverfrost Fortran Applications « Newton Excel Bach, not (just) an Excel Blog

    4. Jason says:

      dougaj4,

      Thanks alot for these posts about linking vba and Fortran, they have been an immense help. This site is a great resource!!

      Here is something that I learned that might be of help to others doing mixed language programming. If you want to package your dll’s along with your excel sheet and not worry about copying your files to a certain directory to maintain the paths to your subroutine calls, here’s what you can do.

      In your main subroutine paste these lines:

      Private Sub CommandButton1_Click()
      ChDrive (ThisWorkbook.Path)
      ChDir (ThisWorkbook.Path)

      Now in your module where you declare your subroutines you can just call the dll’s by name without the path:

      Declare Sub DUPEFILTER2 Lib “RainflowApp.dll” (ByRef input_array As Single, ByRef inp_index As Long)
      Declare Sub SORTMAX Lib “RainflowApp.dll” (ByRef dataspectrum As Single, ByRef counter As Long)

      As long as your dll’s are in the same location as your spreadsheet you only have to call the dll name in the declare statement.

      Cheers,
      Jason

      Like

    5. Bill Dowsland says:

      The 2nd of two excellent articles. Just to note that with recent Silverfrost versions you cannot use the Check mode of Plato (it does not work), but code works fine with Release Win32.

      (Noted on Silverfrost support site)

      Many Thanks

      Bill

      Like

      • Nuno says:

        Could you give more information on how to compile the dll on gfortran or Release Win32 ? I am not able to create a dll that works, however if I download the dll from this site everything works fine…

        Thank you

        Like

        • dougaj4 says:

          Nuno – I’m afraid I won’t have time to look into gfortran, but if you let me know exactly what problems you are having with the Silverfrost compiler I will see if I can help.

          Like

    6. dougaj4 says:

      Bill – thanks for comments.

      Like

    7. mmanu says:

      hey…is it possible to read the values from excel( more than 2000) in fortran perform operations on it and take the average of the intermediate values??

      Like

      • dougaj4 says:

        mmanu – I’m not exactly clear what you are wanting to do, but if you create variables in VBA and pass them to the Fortran code, you can then access the variables from VBA after they have been processed by the Fortran.

        Does that answer your question?

        Like

    8. colin troth says:

      The above DLL approach seems interesting but all I require is to write out an x/y array of data to a named excel workbook to utilise the excel graphics..can anyone help?

      Like

      • dougaj4 says:

        Colin – I’m assuming your x/y array is in a Fortran routine.

        Probably the simplest thing would be to write the array to a text file, then have a macro in Excel to read the text file and plot the data.

        Alternatively if you are using 2007 or 2010 you could probably write the data to an Excel file in the new format, but I haven’t looked into that.

        Finally you could do it with a dll set up to work with Excel, which would be more work, but you could set the whole thing up to use Excel as the pre and post processor, without needing to keep track of text files.

        Like

    9. mollam says:

      Hi

      really useful stuff so thanks

      I am totally okay to pass 1D arrays but when it comes to 2D arrays the excel crashes. I do not know why. I am using Excel 2007. Recently downloaded Excel 2010 but nothing changed it still crashes with 2D arrays.

      Like

    10. mollam says:

      Hi

      I think I found the problem, you should build the dll with Release Win 32 option selected at the PLATO of silverfrost. default is checkmate 32. Now it is working. anyway welcome to other comments as well.

      Like

    11. dougaj4 says:

      mollam – I didn’t have the same problem with 2D arrays with Checkmate 32; I wonder if you changed something else between the two compilations?

      Anyway, the Release Win 32 is the appropriate option for the final compilation, after you have finished debugging.

      Like

    12. mollam says:

      Hi

      no I did not change anything. but thanks mentioning though.

      one more thing is declaration of the VBA arrays for example if you are passing K() and F() to dll then declare them in seperate lines otherwise excel is crashing (at least in my case)

      working
      dim K() as double
      dim F() as double

      crash
      dim K(),F() as double (although true in excel itself)

      hope will help somebody in trouble with dlls. I found by trial and error, VBA is really unforgiving, unhelpful when calling fortran dlls.

      Like

    13. mollam says:

      BTW

      when compiling if you use optimization options then you can really get amazing results. for gauss elimination (operating on symmetric banded matrix in rectangular form) section of my code I got almost 50 times speedup. really amazing. so I am thinking what is the problem with VBA numerical performance why it is so inferior I mean 50 times like day and night..

      Like

    14. dougaj4 says:

      dim K(),F() as double will dimension F() as a double, but K() as a variant. You have to specify the data type for every variable, even if they are all intended to be the same.

      dim K() as double, F() as double
      should work.

      You are right about it being unforgiving using VBA with dlls (applies to c++ as well). Every variable passed between VBA and the dll must be the same data type, and if you try and write outside the bounds of an array it usually causes an immediate crash.

      As for speed, yes for maths intensive things like Gaussian elimination linking to a compiled dll will give a huge speedup, but 50 times sounds on the high side. Are you working with an array of doubles in the VBA? Using a range really slows things down.

      Like

    15. mollam says:

      himm thanks… that should be the case then, anyway there should be away for debugging this dll mixed programming. have you ever tried this?

      yes I am working with doubles. actually at first I could not believe it but it is true: speedup is around 50 for gauss elimination. it is a FEA for a nonlinear solid mechanics problem. so it is computationally intensive. the second part I converted to the dll is the formation of stiffness matrices and speedup in this sector is close to 10.. this dll stuff is really becoming sweet 🙂

      BTW although very convenient and clear for dll the silverfrost does not support parallel processing as my understanding. it would be great if it was doing so.. dougaj4 as I see you are also doing lots of numerical simulations, have you ever construct dlls in fortran or c/c++ running on multiple CPUs and call them from VBA as usual?

      Like

    16. dougaj4 says:

      mollam – I can’t be a lot of help with your questions I’m afraid. I haven’t managed to get a smooth debugging process working, although I think it should be possible. The only advice I can give is that if you have unexplained crashes happening check the data type and array size of everything being passed btween the VBA and the dll. as the first thing to look at.
      I haven’t done anything with multiple CPUs either, but as long as all the logic for handling that part was in the compiled code I can’t see why it wouldn’t work.

      Like

    17. Pingback: Daily Download 31: Linking to Fortran | Newton Excel Bach, not (just) an Excel Blog

    18. Pingback: ¿Cómo utilizar programas en Fortran desde Excel?

    Leave a comment

    This site uses Akismet to reduce spam. Learn how your comment data is processed.