user2495967
user2495967

Reputation: 21

call an Ada procedure from Fortran via DLL

I'm having problems with the mixed-language programming as mentioned in the title, more precisely getting arrays from Ada to the Fortran code. My Ada procedure declaration looks like:

    procedure Get_Double_Array
      (Double_Array    : in System.Address;
       Length_of_Array : in System.Address);
    pragma Export(Fortran, Get_Double_Array, "Get_Double_Array_");

The corresponding body of my procedure is

    procedure Get_Double_Array
      (Double_Array : in System.Address;
       Length_Of_Array : in System.Address)
    is
        use Interfaces.Fortran;

        Array_Length : Fortran_Integer;
        for Array_Length'Address use Length_Of_Array;

        Result_Array : Double_Precision_Array(1..3);
        for Result_Array'Address use Double_Array;
    begin
        Result_Array(1) := Double_Precision(1.0);
        Result_Array(2) := Double_Precision(2.0);
        Result_Array(3) := Double_Precision(3.0);

        Array_Length := Fortran_Integer(Result_Array'Last);
    end Get_Double_Array;

The declaration of the Double_Precision_Array looks like

    type Double_Precision_Array is (Fortran_Integer range <>) of Double_Precision;
    pragma Convention(Fortran, Double_Precision_Array);

Making this procedure available in the DLL is already working. dumpbin /exports on the created dll shows the Get_Double_Array_ as expected.

The Fortran program looks like

    PROGRAM TPROG
    IMPLICIT NONE

    INTERFACE
    SUBROUTINE GETARR(DPARR, LENGTH)
    cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : '_Get_Double_Array_' :: GETARR
    DOUBLE PRECISION, DIMENSION (:) :: DPARR
    INTEGER :: LENGTH
    END SUBROUTINE
    END INTERFACE

    DOUBLE PRECISION, DIMENSION(3) :: XDOT
    INTEGER :: LENGTH
    CALL GETARR(XDOT, LENGTH)
    END PROGRAM TPROG

The fortran code is compiled with gfortran and linked with the lib corresponding to the created dll. The command line is

    gfortran -o test.exe test.f Ada_Lib.lib

When I inserted debugging output into the fortran code before the Call statement I can see that the Get_Double_Array procedure is called but I get the exception

    raised PROGRAM_ERROR: Name_Of_The_Ada_Body.adb: misaligned address value

The line number in this message is the one where I declare the Array_Length variable. I know about the Ada Attribute 'Alignment, but I don't know how to use it in this situation, because I'm already using Fortran compatible data types (at least I think so).

When I export the C Convention on the Ada side and also use the C convention for the array declaration and adapt the cDEC$ line in Fortran with 'C, DLLIMPORT, ALIAs', the Length value is always correct but the contents of the array are completely useless.

The range of the Arrays is only fixed for debugging. Later the Array can be of any length, which is why I also need to return the length of the array.

Any useful tipps or explanations what I'm doing wrong and what I can try next?

Upvotes: 2

Views: 633

Answers (2)

Simon Wright
Simon Wright

Reputation: 25501

The problem is that Fortran has no way of passing an unconstrained array to Ada in a way that Ada understands (there's a clear correspondence to Fortan 90's assumed-shape arrays, but no way that I can see of telling the Ada side that that's what to expect).

I've been experimenting with the problem, and on Mac OS X with GCC 4.8.0 - after I remember to link in the Ada runtime - it gives the same exception that you got (by the way, what version of the compiler(s) are you using?).

When I tried passing an unconstrained array to the procedure,

   procedure Get_Double_Array
     (Double_Array        :    out Double_Precision_Array;

the compiler said

problem.ada:7:07: warning: type of argument "Get_Double_Array.Double_Array" is unconstrained array
problem.ada:7:07: warning: foreign caller must pass bounds explicitly

(why this is a warning and not an error I don't know!) and the same exception at run time.

I think what you could do is to declare an enormous array type (never actually creating one, of course):

with Interfaces.Fortran; use Interfaces.Fortran;
package Problematic is

   type Double_Precision_Array is
     array (Fortran_Integer range 1 .. Fortran_Integer'Last)
     of Double_Precision;
   pragma Convention (Fortran, Double_Precision_Array);

   procedure Get_Double_Array
     (Double_Array        :    out Double_Precision_Array;
      Double_Array_Length : in     Fortran_Integer;
      Output_Length       :    out Fortran_Integer);
   pragma Export(Fortran, Get_Double_Array, "get_double_array_");

end Problematic;

(note the lower-cased exported name), with body

package body Problematic is

   procedure Get_Double_Array
     (Double_Array        :    out Double_Precision_Array;
      Double_Array_Length : in     Fortran_Integer;
      Output_Length       :    out Fortran_Integer)
   is
   begin
      Double_Array(1) := Double_Precision (1.0);
      Double_Array(2) := Double_Precision (2.0);
      Double_Array(3) := Double_Precision (3.0);

      Output_Length := Fortran_Integer (3);
   end Get_Double_Array;

end Problematic;

with the test program changed to

  PROGRAM TPROG
  IMPLICIT NONE

  DOUBLE PRECISION, DIMENSION(4) :: XDOT
  INTEGER :: LENGTH, J
  CALL GET_DOUBLE_ARRAY(XDOT, 4, LENGTH)
  PRINT *, 'output length is ', LENGTH
  PRINT *, (XDOT(J), J=1,LENGTH)
  END PROGRAM TPROG

(The compiler couldn't handle your INTERFACE section).

Note! so far, the Ada doesn't call up any Ada runtime facilities. If it did, you'd have to

  • arrange for the runtime to be linked in
  • initialize it, and possibly finalize it.

I think those would be another question!

Upvotes: 4

user2495967
user2495967

Reputation: 21

After experimenting a bit more and getting help from a few colleagues we have found a soultion using C conventions.

  1. I forgot the AdaInit and AdaFinal procedures. These functions are created by the binder during the creation of the dll. You must call the AdaInit function before using any functionality. Our approach to this is exporting a function like

    procedure Init_Dll;
    pragma Export(C, Init_Dll, "initdll_");
    

In the private part of the declaration we added

    procedure AdaInit;
    pragma Import(C, AdaInit);

    procedure AdaFinal;
    pragma Export(C, AdaFinal);

The body of our Init_Dll is straight forward

    procedure Init_Dll
    is
    begin
        AdaInit;
    end Init_Dll;

Then using gnatmake and gnatdll we created the Ada dll and with the windows command line

    lib -machine:IX86 -def:Name_Of_Ada_Package.def -out:Name_Of_Ada_Package.lib > nul

the corresponding lib

  1. On the Fortran side we now used the external command instead of interfaces so the program looks like

    PROGRAM TEST
    IMPLICIT NONE
    EXTERNAL initdll
    EXTERNAL getdblarray
    INTEGER :: LENGTH
    DOUBLE PRECISION, DIMENSION(3):: ARR
    CALL initdll
    CALL getdblarray(ARR, LENGTH)
    END PROGRAM TEST
    

Compiling and linking this program against the created lib works just fine

Upvotes: 0

Related Questions