Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.
29282 Discussions

Yet another question on Fortran calling C

Jon_D
New Contributor II
1,676 Views
I have a number of procedures in a static library written and compiled using Visual C++. I am trying to call these functions from IVF using ISO_C_BINDING intrinsic module. The prototype for a simple C function is as follows:

void closf_ (int *ihandle, int *istat)

My wrapper function on the Fortran side looks like this:

SUBROUTINE closf(ihandl,istat)
USE,INTRINSIC :: iso_c_binding , ONLY : C_LOC
IMPLICIT NONE

INTERFACE
SUBROUTINE closf_can(ihandl,istat) BIND(C , NAME='closf_')
USE,INTRINSIC :: iso_c_binding , ONLY : C_PTR
IMPLICIT NONE
TYPE(C_PTR),VALUE :: ihandl,istat
END SUBROUTINE closf_can
END INTERFACE

INTEGER,TARGET :: ihandl,istat

CALL closf_can(C_LOC(ihandl),C_LOC(istat))

END SUBROUTINE closf


When compiled, I get "error LNK2019: unresolved external symbol closf_ referenced in function _CLOSF". I tried different ways of adding the C component into my Fortran project: a) added the C++ project into the solution and made my Fortran project dependant on it, b) added the compiled C library (.lib file) to the Fortran project, c) added the closf_.obj file to the Fortran project. None of them worked.

I am using IVF 10.0.27 with VS2005 Professional.

Any help will greatly be appreciated.

Thanks,
Jon
0 Kudos
20 Replies
Steven_L_Intel1
Employee
1,671 Views
Is your C source in a file named with a .cpp file type? if so, you need to prefix the function prototype with

extern "C"

otherwise you get C++ name mangling.

The other thing that comes to mind is that on IA-32, the actual external name will be _closf_ so you may need to add the leading underscore. I'll have to reread that part of the standard to see if that in fact ought to be necessary.
0 Kudos
Jon_D
New Contributor II
1,671 Views
Steve,

The C source code is in a ".c" file. I will try adding the leading underscore and hopefully that will work. This has been the only thing that is stopping me to migrate from CVF to IVF.

Thanks,
Jon
0 Kudos
Steven_L_Intel1
Employee
1,671 Views
Eh? Tell me how you got BIND(C) to work in CVF. If you do your C compatibility directives the same as CVF, it should work without problems.

From a Fortran Build Environment command prompt, do a:

dumpbin -symbols ccode.obj

on your C onbject file to see what the "decoration" of the symbol is. I haven't done the test myself to see if BIND is doing the right thing - I will do that.
0 Kudos
Jon_D
New Contributor II
1,671 Views
The C code is part of a static library (mixed Fortran and C) that I acquired in compiled form in CVF. I have been using it with no problems in my own programs compiled with CVF. When IVF came onboard, I contacted the developers of the library and asked them to send me the IVF-compiled version of the library so that I could migrate my programs to IVF. Although they granted my request, I have never been able to use the IVF-compiled library; certain procedures in it kept messing up the stack when called. Finally, I got the source code from the developers and now am trying to compile it myself by wrapping the C functions with Fortran code using F2003 standard.

Your suggestion of adding underscore in front of the C function names seemed to work. At least I got it compiled, although I haven't tested the library for produced results yet.

Thanks,
Jon
0 Kudos
Steven_L_Intel1
Employee
1,671 Views
I have confirmed that this is a compiler bug. It is supposed to be "decorating" the name you specify in NAME= but is not.

A workaround that will not break once the compiler is fixed is to add:

!DEC$ ATTRIBUTES DECORATE :: routine_name

to the interface block.
0 Kudos
Jon_D
New Contributor II
1,671 Views
Hi,

I have another problem regarding Fortran calling C procedures using ISO_C_BINDING intrinsic module. It would be great if somebody could help.

The issue is related to passing a character variable to a C procedure:

#include
#include

void
isonlocaldrive_ (char *pathName, int *isLocal, int len_pathName)
{

char absPath[_MAX_PATH];
char *filePart;
GetFullPathName(pathName, _MAX_PATH, absPath, &filePart);
.
.
.
}

The Fortran wrapper for this procedure is

SUBROUTINE isonlocaldrive(pathName,isLocal)
USE,INTRINSIC :: iso_c_binding
IMPLICIT NONE
CHARACTER(LEN=*) :: pathName
INTEGER :: isLocal

INTERFACE
SUBROUTINE isonlocaldrive_can(c_pathName,isLocal,len_pathName) BIND(C , NAME='_isonlocaldrive_')
USE,INTRINSIC :: iso_c_binding
IMPLICIT NONE
CHARACTER(C_CHAR),DIMENSION(*) :: c_pathName
INTEGER(C_INT) :: isLocal
INTEGER(C_INT),VALUE :: len_pathName
END SUBROUTINE isonlocaldrive_can
END INTERFACE

CALL isonlocaldrive_can(pathName,isLocal,LEN(pathName))

END SUBROUTINE isonlocaldrive


This set-up seems to work fine until the GetFullPathName (a WIN32 API) function in the C code is invoked. In the debugger I can see the values of *isLocal, len_pathName and the first character of *pathName correctly. But after the GetFullPathName is called *pathName and *isLocal seem to loose the address they are pointing to (as much as I can tell with my very limited C knowledge). Later in the C code *isLocal is assigned a value and at this stage I get an access violation error.

I would very much appreciate if somebody can help me on this. I read whatever information I could find on passing character variables from Fortran to C, but I still can't figure out what the problem is.

Thanks,
Jon

0 Kudos
Steven_L_Intel1
Employee
1,671 Views
I don't see a problem with the Fortran code. Comparing your C code with the MSDN example for GetFullPathName, I'd suggest removing the & in front of filePart and see what that does for you.
0 Kudos
Jon_D
New Contributor II
1,671 Views
When I remove "&" in fornt of filePart I get the following run-time error:

Run-Time Check Failure #3 - The variable 'filePart' is being used without being initialized.
0 Kudos
Steven_L_Intel1
Employee
1,671 Views
Hmm. What happens if you just pass NULL for filePart?

Here's the MSDN sample excerpt - maybe try its method?

DWORD retval=0;
BOOL success; char buffer[BUFSIZE]="";
char * lpPart[BUFSIZE]={NULL};
// Retrieve a full path name for a file. The file does not need to
// exist.

retval = GetFullPathName("c:testfile.txt", BUFSIZE, buffer, lpPart);
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,671 Views

Jon,

I do not know if this is your problem or not but GetFullPathName takes as the 2nd argument the size of the destination buffer in TCHARs. A TCHAR is two bytes. So either declare your buffer as TCHAR Buffer[[_MAX_PATH] (not char) or request the number of chars in the array declaration as char Buffer[_MAX_PATH*sizeof(TCHAR)].

As to wether char's or TCHAR's are returned it is not clear by the documentation.

Jim Dempsey

0 Kudos
Jon_D
New Contributor II
1,671 Views
Steve,

I tried your suggestion of passing NULL instead of filePart. It didn't work. I haven't tried Jim's suggestion yet.

I have another C function that expects char *cname that I wrap with Fortran using the exact same approach. That C function calls CreateFile API to open file with *cname. Although the pointers don't loose their targets, the CreateFile function fails. This makes me wonder if there is indeed a problem with the Fortran side of my code. I inhereted the C code from someone else and supposedly it worked fine when linked to CVF-compiled (without using the iso_c_binding modulke, of course) Fortran code.

Below are the part of C code that uses CreateFile and its Fortran wrapper:

void 
openf_ (char *cname, int *iaccess, int *ihandl, int *istat, int len_cname)
{
 HANDLE hFile;

hFile = CreateFile (cname,
       GENERIC_READ | GENERIC_WRITE,
       FILE_SHARE_READ | FILE_SHARE_WRITE,
       NULL,
       OPEN_ALWAYS,
       FILE_ATTRIBUTE_NORMAL,
       NULL);
}

SUBROUTINE openf(cname,iaccess,ihandl,istat)
USE,INTRINSIC :: iso_c_binding , ONLY : C_LOC
IMPLICIT NONE
CHARACTER(LEN=*) :: cname
INTEGER :: iaccess,ihandl,istat

INTERFACE
SUBROUTINE openf_can(cname,iaccess,ihandl,istat,len_cname) BIND(C , NAME='_openf_')
USE,INTRINSIC :: iso_c_binding , ONLY : C_INT , C_CHAR , C_PTR
IMPLICIT NONE
CHARACTER(C_CHAR),DIMENSION(*) :: cname
INTEGER(C_INT) :: iaccess,ihandl,istat
INTEGER(C_INT),VALUE :: len_cname
END SUBROUTINE openf_can
END INTERFACE

CALL openf_can(cname,iaccess,ihandl,istat,LEN(cname))

END SUBROUTINE openf

Thanks,

Jon

0 Kudos
Jugoslav_Dujic
Valued Contributor II
1,671 Views
JimDempseyAtTheCove:
A TCHAR is two bytes.


No, a TCHAR is a "generic" for either char (1 byte) or WCHAR (2 bytes); the appropriate version will be picked up depending on whether UNICODE is #defined; additionally, it will pick up GetFullPathNameA (ANSI) or GetFullPathNameW (UNICODE) export from the Kernel32.dll. So, unless there's UNICODE defined for the C++ project, that's not a problem.
0 Kudos
Jugoslav_Dujic
Valued Contributor II
1,671 Views
dogrul@water.ca.gov:
StAlthough the pointers don't loose their targets, the CreateFile function fails. This makes me wonder if there is indeed a problem with the Fortran side of my code.

Have you terminated the cname with CHAR(0) in the caller (trim(clen)//char(0))? C expects that for (almost) all strings, and will also normally return char(0)-terminated strings (rather than Fortran-style blank-padded). You have to do the conversion yourself.
0 Kudos
Jon_D
New Contributor II
1,671 Views
Jugoslav,

Yes, cname is null-terminated using CHAR(0).

Jon
0 Kudos
Steven_L_Intel1
Employee
1,671 Views
Please attach a ZIP of a small but complete set of C/Fortran projects that demonstrates the problem. With the excerpts you've given us, the problem might be somewhere else.
0 Kudos
Jon_D
New Contributor II
1,671 Views

Steve,

Attached is a C-static libraryproject and a Fortran console application project. The openf_ function should create a file named "Test.txt" but creates a file with a name full of strange characters (in my full application nothing is created, I get an invalid handle); isonlocaldrive_ function kills the executable.

The projects are compiled by VS2005.

Jon

0 Kudos
Steven_L_Intel1
Employee
1,671 Views
I'll look at this on Monday, but perhaps someone else will be able to try it sooner.
0 Kudos
anthonyrichards
New Contributor III
1,671 Views

I know nothing about 'iso-c-binding' and use Compaq Visual Fortran 6.6c. But I translated your Fortran project as shown below, compiled your three C-files (with no changes)into a static library using Visual C++ and included the .LIB file into my fortran project and built a console project using your two Fortran files as modified below and ran it. The output on the console was as follows:

iaccess= 10
ihandl= 10
istat from openf= 0
istat from isonlocaldrive= 1
Press any key to continue

and an empty file called 'Test.txt' was created. So the code appears OK from the point of view of CVF!

The modified Fortran code follows, using compiler directives to match the calling convention and C-naming (the .C file extension meant that the Visual C++ did not mangle the names).

First, your 'C-wrapper':
-------------------------

SUBROUTINE openf(cname,iaccess,ihandl,istat)
IMPLICIT NONE
CHARACTER(LEN=*) :: cname
INTEGER*4 :: iaccess,ihandl,istat, length

INTERFACE
SUBROUTINE openf_can(cname,iaccess,ihandl,istat,len_cname)
!DEC$ ATTRIBUTES C,REFERENCE :: openf_can
!DEC$ ATTRIBUTES REFERENCE :: cname, iaccess, ihandl, istat
!DEC$ ATTRIBUTES VALUE :: len_cname
!DEC$ ATTRIBUTES ALIAS:'_openf_' :: openf_can
IMPLICIT NONE
CHARACTER(*) cname
INTEGER(4) iaccess,ihandl,istat
INTEGER(4) len_cname
END SUBROUTINE openf_can
END INTERFACE

length=LEN(cName)
CALL openf_can(cname,iaccess,ihandl,istat,length)
END SUBROUTINE openf
!---------------------------------------------------------------------------
SUBROUTINE isonlocaldrive(pathName,isLocal)
IMPLICIT NONE
CHARACTER(LEN=*) :: pathName
INTEGER :: isLocal, length

INTERFACE
SUBROUTINE isonlocaldrive_can(c_pathName,isLocal,len_pathName)
!DEC$ ATTRIBUTES C,REFERENCE :: isonlocaldrive_can
!DEC$ ATTRIBUTES REFERENCE :: c_pathname, islocal
!DEC$ ATTRIBUTES VALUE :: len_pathname
!DEC$ ATTRIBUTES ALIAS:'_isonlocaldrive_' :: isonlocaldrive_can
IMPLICIT NONE
CHARACTER(*) c_pathName
INTEGER(4) isLocal
INTEGER(4) len_pathName
END SUBROUTINE isonlocaldrive_can
END INTERFACE

length=LEN(pathName)
CALL isonlocaldrive_can(pathName,isLocal,length)
END SUBROUTINE isonlocaldrive

Then your test program:
---------------------------

PROGRAM Test_Fortran_C
IMPLICIT NONE

CHARACTER :: cna me*20
INTEGER :: iaccess,ihandl,istat,len_cname

cname = ADJUSTL('Test.txt' // CHAR(0) )
len_cname = LEN_TRIM(cname)+1
iaccess = 10

CALL openf(cname(1:len_cname),iaccess,ihandl,istat)
write(*,*) 'iaccess= ',iaccess
write(*,*) 'ihandl= ',iaccess
write(*,*) 'istat from openf= ',istat
 CALL isonlocaldrive(cname(1:len_cname),istat)
 write(*,*) 'istat from isonlocaldrive= ',istat
END

0 Kudos
Steven_L_Intel1
Employee
1,671 Views
The major problem you have is that the C project is set to use UNICODE, but you are passing 8-bit strings, and CreateFile gets very confused. This is controlled by the project setting Configuration Properties > General > Project Defaults > Character Set. You had it set as "Use UNICODE Character Set", which causes _UNICODE to be defined and the W versions of the Win32 routines to be used. Change this to "Not set" and you'll get ASCII instead and it will be much happier.

From my testing, it looks as if UNICODE is the default when you create a C++ project in VS2005, so this is something to watch out for.

There is a second minor bug in the Fortran code where you have:

cname = ADJUSTL('Test.txt' // CHAR(0) )
len_cname = LEN_TRIM(cname)+1

You want that +1 to be -1.

I will comment that there is a bug in the compiler regarding BIND(C,NAME=) in that, at present, it does not apply the corresponding C compiler's decoration (leading underscore) to the name. You have correctly worked around this, but a future update, when the bug is fixed, will require that you remove the leading underscore from the NAME value.

I will also comment that, at least from the C code I see here, all of this could be done in Fortran quite easily. I don't know why you want to call out to C.
0 Kudos
Jon_D
New Contributor II
1,575 Views
Thanks Steve and anthonyrichards,

Changing the UNICODE character set to "Not set" worked like a charm.

Jon
0 Kudos
Reply