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

Tricky Delphi .exe to F90/95 .dll interface problem

Elias_Sabbagh
Beginner
1,380 Views
Hi folks!

Using Delphi 2009, IVF 8.1.2279.2003.

I'm trying to call a routine in a DLL written in F90/95 from a EXE written in Delphi. The Delphi client code calls a F90 subroutine, and passes as actual parameters to the F90 routine some pointers to Delphi internal procedures -- that is, procedures contained in the client calling routine. On the F90 side, those pointers are associated with interface blocks corresponding to the Delphi internal procedures, through the use of Cray pointers. The idea is that the F90 routine will use the Delphi internal procedure pointers to access data that's far easier for the Delphi code to access than it would be for F90 to access -- database middleware, XML DOM hierarchies, etc. By using internal procedures, I can avoid placing the data/objects in the global Delphi scope, and just pass the data to the client code from elsewhere. The Delphi internal procedures will be able to access the data via normal Delphi scoping rules, and things ought to be threadsafe and properly hidden.

Some big assumptions I'm making are 1) Delphi doesn't do anything too nutty to internal procedures, and I can just pass their addresses around via the '@' operator like any other procedure; 2) IVF will be able to treat these pointers just like any other address and actually call back using them, since the EXE and the DLL share the same address space; 3) simply giving the internal procedures the STDCALL attribute on both the Delphi side and the IVF side is enough to not screw up the stack; 4) EXPORT'ing the routines from Delphi like they were in a library is unnecessary, since the F90 DLL isn't going to use GetProcAddress() to get the address -- it's being fed the address directly.

Things compile OK and start up OK, and the DLL is dynamically-loaded correctly. But, as I step through the code with the Delphi compiler, I notice that the internal procedures are being called in the wrong order, and after the first incorrect call, the EXE throws an exception. If I run the EXE and attach the IVF debugger, then break right at the point where the first Delphi internal procedure is called back, I see that the correct routine should be getting called at that point -- but it's not. So, somehow, the stack is getting mangled and/or I haven't defined the interface blocks properly. Can anyone see what I'm doing incorrectly below? Please don't tell me that this approach won't work :)...

Here's some (stripped-down) code:

First, the Delphi calling routine:
----------------------------------------------

{Define the type of the F90 DLL routine so we can dynamically attach to it. }
type
TF90Function = function(isterminated: pointer; putversion: pointer; putresourceusage: pointer; ...): integer;

procedure Run(...{Data is passed in here}...);
var
...
F90Function: TF90Function;
pisterminated, pputversion, pputresourceusage, ...: pointer;
res: integer;

{ The following internal procedures can all see the data passed into Run() due to scoping rules. }
function IsTerminated: boolean; stdcall;
begin
Result := ...{Check whether or not thread has been terminated by examining data passed in to Run()}...;
end;

procedure PutVersion(major: smallint; minor: smallint; build: smallint); stdcall;
begin
...{Update data passed in to Run() by noting what version numbers the F90 code passes over}...;
end;

procedure PutResourceUsage(memused: Int64; diskused: Int64); stdcall;
begin
...{Update data passed in to Run() by noting what resources the F90 code says it used}...;
end;

{ Other internal procedures that get/set all sorts of data go here... }

{ Now the actual code of Run() itself. }
begin
{ Load the F90 DLL and attach to the entry point. }
libhandle := LoadLibrary(libname);
if( libhandle = 0 ) then
raise Exception.CreateFmt(CouldNotLoadLibraryMsg, [libname]);
try
@F90Function := GetProcAddress(libhandle, procname);
if( @F90Function = nil ) then
raise Exception.CreateFmt(CouldNotFindEntryPointMsg, [procname]);
{ Pass over the internal procedure addresses. }
pisterminated := @IsTerminated;
pputproductlogversion := @PutProductLogVersion;
pputproductlogusage := @PutProductLogUsage;
{ Call F90Function. }
res := F90Function(pisterminated,pputproductlogversion,pputproductlogusage,...);
{ Check error status of F90Function. }
case( res ) of
0: ;
1: ;
2: ;
end;
finally
FreeLibrary(libhandle);
end;
end;

Now, the relevant F90 code:
--------------------------------

module importsmod
implicit none

! Define interfaces to the proxy routines provided by the Delphi wrapper.
! N.B.: We don't explicitly state the kind of the integer, so this should
! work for both 32-bit and 64-bit machines.
integer, save:: Is_Terminated
integer, save:: Put_Version
integer, save:: Put_Resource_Usage
...
interface
logical function IsTerminated
!DEC$ ATTRIBUTES STDCALL::IsTerminated
end function IsTerminated
subroutine PutVersion(major,minor,build)
!DEC$ ATTRIBUTES STDCALL::PutVersion
integer(2), intent(out):: major
integer(2), intent(out):: minor
integer(2), intent(out):: build
end subroutine PutVersion
subroutine PutResourceUsage(memused,diskused)
!DEC$ ATTRIBUTES STDCALL::PutResourceUsage
integer(8), intent(out):: memused
integer(8), intent(out):: diskused
end subroutine PutResourceUsage
...
end interface
pointer(Is_Terminated, IsTerminated)
pointer(Put_Version, PutVersion)
pointer(Put_Resource_Usage, PutResourceUsage)

end module importsmod

integer function F90Function(pisterminated,pputversion,pputresourceusage,...)
!DEC$ ATTRIBUTES STDCALL,DLLEXPORT::F90Function
!DEC$ ATTRIBUTES ALIAS :'F90FUNCTION'::F90FUNCTION

use importsmod
...
implicit none
! Variable declarations
integer pisterminated
integer pputversion
integer pputresourceusage
...
integer(8) memused, diskused
integer(2) major, minor, build

! Bind the incoming pointers to their proxy routines.
Is_Terminated = pisterminated
Put_Version = pputproductlogversion
Put_Resource_Usage = pputproductlogusage
...
memused = 0
diskused = 0
major = 1_2
minor = 0_2
build = 0_2
call PutVersion(major, minor, build); ! <---- THE WRONG DELPHI PROCEDURE IS CALLED HERE!
! Do a bunch of stuff here, allocate memory, chew up disk, check for thread termination, set error status, etc.
if( IsTerminated.eq..TRUE. ) then
! Clean up and leave
endif
! Do more stuff...
call PutResourceUsage(memused, diskused);
F90Function = 0
return
end function F90Function

---------------------------

Thanks for any tips,

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
1 Solution
jimdempseyatthecove
Honored Contributor III
1,380 Views
>>still have the containing routine's data remain in scope

I missed this point of your problem statement.

I think the compiler will do this for self called contained subroutines. I do not know the actual method it uses but it may be through use of not setting ebp/rbp in the called routine. Or using FS/GS segment register or other..... this is an implementation issue. I think it be best not using a contains subroutine and pass a context (struct) pointer with the call or extend the number of args in the call.

Jim Dempsey

View solution in original post

0 Kudos
17 Replies
jimdempseyatthecove
Honored Contributor III
1,380 Views
If you are on x64 platform do not assume INTEGER is size of a pointer.

integer(kind=INT_PTR_KIND()) :: p_YourPointer

.or.

use, intrinsic :: iso_c_binding
...

integer(kind=C_FUNPTR) :: p_YourFunctionPointer
integer(kind=C_PTR) :: p_YourObjectPointer

Also look at C_F_POINTER it may be of use.

As for on the Delphi, you may have to do something similar

Jim Dempsey
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
OK, a bit of progress has been made: in the Delphi declaration of the F90Function type, I forgot to add the 'stdcall' directive, like so:

type
TF90Function = function(isterminated: pointer; putversion: pointer; putresourceusage: pointer; ...): integer; stdcall;


That takes care of the incorrect ordering of the parameters passed from Delphi to F90 -- the correct F90 interfaces are getting wired up to the correct Delphi internal procedures. However, once I actually execute the first call to PutVersion() in the F90 DLL, which is wired up to the Delphi procedure, the Delphi procedure throws an exception at the first statement, which reads something like this:

procedure PutVersion(major: smallint; minor: smallint; build: smallint); stdcall;
begin
{note that vtj is an object that is in the scope of PutVersion, and it has a property named 'Major.'}
vtj.Major := major; {<--- Exception thrown here! Interestingly, the Delphi debugger sees the correct
vtj.Minor := minor; values for the major, minor, and build parameters, but actually using them on
vtj.Build := build; the right-hand-side of the assignments seems to be broken. }
end;

Clearly there's still something wrong with the F90 interface, which looks like this:

subroutine PutVersion(major,minor,build)
!DEC$ ATTRIBUTES STDCALL::PutVersion
integer(2), intent(out):: major
integer(2), intent(out):: minor
integer(2), intent(out):: build
end subroutine PutVersion


Anybody see what's wrong?

Thanks,

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim-

Thanks for the reminder to explicitly use the KIND= attribute. On the Delphi side, the "pointer" type is automatically the correct size.

I get the same bugs no matter how carefully I've defined the variables, though, so a pointer size problem is not the reason for the bug...

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,380 Views
Elias,

Here are some suggestions.

Create a Delphi function that takes no arguments DelphiNoArgs
On the Fortran side something along the line of

integer(C_INTPTR) :: ret
interface
function DelphiNoArgs()
integer(C_INTPTR):: DelphiNoArgs
end function DelphiNoArgs
end interface
...
write(*,*) "LOC(ret) = ", LOC(ret)
ret = DelphiNoArgs
write(*,*) "LOC(ret) = ", LOC(ret)
write(*,*) "ret = ", ret

Have the Delphi function return a known value (say 123456)

If the location of ret changes then you have a calling convention problemw/rt who cleans up stack

Next, write a second Delphi function. One that takes 3 integer args. Decide if you want to pass by value or by reference (pointer). Declare the appropriate interfaces.

Print out the location and values of the arguments prior to call in the Fortran side. Do the same on the Delphi side. Then print out the location and values after return in the Fortran size.

What you are looking for is discrepancies between calling args: pass via registers, pass via stack, left-to-right/right-to-left order, reference/value.

Consider opening up the dissassembly window and stepping through/into the call to see what is happening. You should notice something relatively quickly and get your Eurika moment.

Jim Dempsey
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim--

That'll be my next line of attack. However, I'm becoming suspicious of whether or not I can actually pass an internal procedure around, and still have the containing routine's data remain in scope. I just replaced the F90 DLL with a performalike version written in Delphi -- and I get a similar Access Violation error (although with a slightly different illegal memory location). It's possible that I introduced a bug in the Delphi DLL, although I don't think so. I'm beginning to think that Delphi internal procedures can only be correctly used inside of their containing routine -- which is a shame, because otherwise, I'd have such a clean solution for what I want to do...

I'm going to ask around on the Delphi fora and see what I learn.

Thanks for your help,

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,381 Views
>>still have the containing routine's data remain in scope

I missed this point of your problem statement.

I think the compiler will do this for self called contained subroutines. I do not know the actual method it uses but it may be through use of not setting ebp/rbp in the called routine. Or using FS/GS segment register or other..... this is an implementation issue. I think it be best not using a contains subroutine and pass a context (struct) pointer with the call or extend the number of args in the call.

Jim Dempsey
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim-

Delphi uses something named the "register" calling convention internally, so there must be some improper things going on with the registers if you pass around internal procedures as though they were regular procedures. Perhaps internal procedures "piggyback" on their containing stack frame registers in some way...

So anyway, your advise is about where I'd ended up today -- forget about internal procedures, and make everything a plain-old procedure. Then, we just pass around a pointer to the Delphi object(s) down in the F90 code, and back on the Delphi side, add the pointer as the first parameter to each "plain-old" procedure. Within each, cast the pointer back to an object of the correct type. It's the obvious and straightforward way to do it, of course, but the cleanliness of the internal procedure approach kind of charmed me into taking it too seriously, I suppose :).

Thanks for the help,

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,380 Views
Elias,

"register" calling convension is otherwise known as "fast call" calling convention. Intel64 (x64) default calling convention is "fast call" whereas x32 default calling convention is via stack. I am not sure how you specify fast call on x32 platform. You might want to research this (assuming you compile as x32 app).

Jim
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Just to follow up: almost everything is working great now, but I had to tell Delphi which parameters are "var" parameters (that is, passed by reference). This also implies that a !DEC$ ATTRIBUTES REFERENCE:: param1, param2, param3,... line was needed in the F90 interface blocks, since the calling convention was stdcall. There is still one pesky F90/Delphi bound routine that isn't passing things by reference properly, and it involves setting elements of an allocated allocatable array, so I think that I'm probably at one level of pointer indirection too many for that routine. I'll keep experimenting until I arrive at the right combination, and post my results later.

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
OK, now this is strange -- I am trying to use a Delphi routine to initialize some F90 variables, and, while the initialization succeeds if the variables are scalar doubles, scalar integers, or even scalar members of a user-defined type, nothing happens if the variables are members of an allocatable array that is itself a member of a user-defined type! What's worse, if I initialize some doubles, and try to use *those* to assign to the elements of the more-complicated type, nothing happens! I don't think that the problem is one of calling conventions anymore, but how my types are defined, and how I'm using (or misusing) allocatable arrays.

Here's the F90 code:
------------------------

module types
use kinds
implicit none

! the kinds module defines the double type dk and the integer type ik

type TMaterial
sequence
real(dk) cond ! Conductivity, S/m
real(dk) magl ! Magnetic Loss
real(dk) ptvy ! Absolute Permittivity - *not* relative!
real(dk) perm ! Absolute Permeability - *not* relative!
complex(dk) ksq ! omega**2*perm*(ptvy+cond/(sqrt(-1)*omega)) (derived)
end type TMaterial

type TIsotropicLayer
sequence
type(TMaterial) m
! Thickness is not defined for the "top" layer in either planar or cylindrical geometries, and
! isn't isn't defined for the "bottom" layer in planar geometry. The interface and analysis
! layer-numbering convention is reversed, so we'll have to flip the layers around...
real(dk) thick ! thickness of layer, m
! We obtain Bound from the interface's Workpiece object. It is the inner radius for cylindrical
! geometry, with the "bottom" region value fixed at 0, and other layers non-negative. It is the
! upper boundary for planar geometry, with the "top" region undefined, but set to 1e31.
real(dk) bound ! boundary of layer, m (derived)
end type TIsotropicLayer

type TIsotropicPlanarWorkpiece
sequence
type(TIsotropicLayer), pointer:: l(:) ! layers
integer(ik) gridreg ! grid region (derived)
integer(ik) coilreg ! coil region (derived)
end type TIsotropicPlanarWorkpiece

end module types


module importsmod
use kinds
implicit none
...
interface
subroutine GetIsotropicLayer(obj,index,cond,magl,ptvy,perm,thick,bound)
!DEC$ ATTRIBUTES STDCALL::GetIsotropicLayer
!DEC$ ATTRIBUTES REFERENCE:: cond, magl, ptvy, perm, thick, bound
integer(int_ptr_kind()), intent(in):: obj
integer(4), intent(in):: index
real(8), intent(inout):: cond
real(8), intent(inout):: magl
real(8), intent(inout):: ptvy
real(8), intent(inout):: perm
real(8), intent(inout):: thick
real(8), intent(inout):: bound
end subroutine GetIsotropicLayer
end interface
end module

integer function RunEverything
uses kinds
uses types
uses imports
implicit none
...
integer(pk) obj
integer(ik) nreg ! number of workpiece regions
type(TIsotropicPlanarWorkpiece) w
integer i
...
allocate(w%l(nreg),stat=mem_stat)
...

! Initialize and reorder the first nreg layers of w.
do i=1,nreg
call GetIsotropicLayer(obj,nreg-i,w%l(i)%m%cond,w%l(i)%m%magl,w%l(i)%m%ptvy,w%l(i)%m%perm,w%l(i)%thick,w%l(i)%bound)
sigma = w%l(i)%m%cond + (0.0,1.0)*c%omega*w%l(i)%m%ptvy
mu = w%l(i)%m%perm + w%l(i)%m%magl/((0.0,1.0)*c%omega)
w%l(i)%m%ksq = -(0.0,1.0)*c%omega*mu*sigma
enddo
...
end function RunEverything


-----------------------

None of the child elements of w%l(i) are altered! What the heck is going on here?

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,380 Views
Elias,

In:

[bash]type TIsotropicPlanarWorkpiece
  sequence
  type(TIsotropicLayer), pointer:: l(:) ! layers
[/bash]

When your Delphi code sees this type, the member "l":

is not a C-style pointer to an array of layers (with no descriptor)
i.e. is notequivilent to:

TIsotropicLayer* l;

Rather

is a Fortran style reference to an array descriptor that contains a pointer to the data (aka A0 pointer), a base index, element size, and stride, and number of elements (and other stuff).

Therefore your Delphi code needs to know how to interprete the array descriptor in order to find the memory locations of the array (for initialization). If you want, consider passing LOC(w%l(1)) into the Delphi routine.

Jim Dempsey
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim-

Yes, at first I thought that that might be the problem -- but I'm actually calling the Delphi code with arguments that have ALREADY been dereferenced on the F90 side. That is, I'm breaking out the elements of l() and passing them down individually, instead of passing down the l() array itself (to avoid things like LOC(w%l(1)). Like this:

[fortran]do i=1,nreg
  call GetIsotropicLayer(obj,nreg-i,w%l(i)%m%cond,w%l(i)%m%magl,w%l(i)%m%ptvy,w%l(i)%m%perm,w%l(i)%thick,w%l(i)%bound)
  sigma = w%l(i)%m%cond + (0.0,1.0)*c%omega*w%l(i)%m%ptvy
  mu = w%l(i)%m%perm + w%l(i)%m%magl/((0.0,1.0)*c%omega)
  w%l(i)%m%ksq = -(0.0,1.0)*c%omega*mu*sigma
enddo
[/fortran]

Doing this leaves w%l(i)%m%cond and the others COMPLETELY UNAFFECTED.

Now, if I create some temp scalar variables named tempcond, tempperm, etc., and pass those down to GetIsotropicLayer(), they are set correctly by the Delphi code -- but when I then try to assign, for example,
[fortran]w%l(i)%m%cond = tempcond
w%l(i)%m%perm = tempperm
[/fortran]
...the w%l(i)%m elements are completely unchanged! The Visual Studio debugger doesn't show any tooltip value when I hover over the variable, and it's though the compiler doesn't even know that the l(:) array has been allocated. I've never seen anything like it.

What could be the problem here? Earlier in the code I successfully passed down other structures' elements individually for initialization, just not the w%l(:) chunk. There's some mind-boggling subtlety with pointers that I'm missing.

Thanks,

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,380 Views
Elias,

This may be a VS integration issue. As a work around try

type(TIsotropicLayer), pointer:: p_wli
...
p_wli => w%l(i)
p_wli%m%cond = tempcond

If that works then experiment with passing p_wli to Delphi then looking at the results upon return from init call.

If this is in Optimized code, I've seen issues in VS2005 where registerized variables (e.g. i above)exhibited problems in the Watch window (and mouse Hover). As for VS 2008, 2010 I cannot say.

Jim Dempsey

Jim
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim-

Well, that did it. Both of your workarounds passed the test. Of course, the target w%l(i)%m%cond and the others don't show their value changing even as the pointer to them shows the change, so you're probably right that Visual Studio is failing. This behavior is appearing for unoptimized code compiled under Visual Studio .NET 2003. Can I assume that passing hierarchies of user-defined types that include dynamically-allocated arrays/pointers down to routines declared with the STDCALL attribute is not supported by the IDE and/or debugger? And, even if that is the case, should I assume anyway that the code emitted by the IVF compiler is correct? Lastly, since I'm using an older compiler (version 8.1), I'm guessing that the chances of any bugfix getting backported to my version are slim to none, right?

I might have to split up my type hierarchy into something a bit more kludgy, which I'm willing to do just for ease of debugging...

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
Steven_L_Intel1
Employee
1,380 Views
Version 8.1 is long, long gone for us.
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,380 Views
>>And, even if that is the case, should I assume anyway that the code emitted by the IVF compiler is correct?

You can verify that it is correct by using the (your) array syntax as argument to Delphi then using the extra pointer to verify the results are going into the correct location. This can be in as a conditional compile section in Debug build.

I have a similar issue with Intel C++ in VS where I have to use a pointer to a static struct in declared namespace. IOW:

Foo.memberVariable

Is not visible in the debugger

t_Foo* p_Foo = &Foo;

Then looking indirect p_Foo works
(myNameSpace::Foo didn't work either)

Often it is easier to create a work around than to file a problem report.
At least with a work around you can go on with your buisness.

Jim Dempsey
0 Kudos
Elias_Sabbagh
Beginner
1,380 Views
Jim-

Yep, I've worked-around the issue. Instead of a struct of an allocated array [l(:)] of a struct of some intrinsic types [cond,perm,etc.], I have a struct of four "unrolled" arrays of doubles [cond(:),perm(:),etc.], which is maintainable as long as I'm working with isotropic layers. Once I get into anisotropic layers, I'll have 12 unrolled parameters to maintain, four for each dimension... Yuck. But at least things work! So, my current understanding is that the IDE likes to see allocated arrays as leaf nodes in a type hierarchy, not as body nodes. Everything works great now, and thanks for all of your low-level knowledge!

Elias Sabbagh
Victor Technologies, LLC
0 Kudos
Reply