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.

Call C++ dll from Fortran

markusda
Beginner
4,722 Views

Hello,

This is my first post in this forum and I'm pretty new at this visual studio stuff, if this is the wrong forum let me know which one it should be in.

I am a FORTRAN user who has a need to make calls and extract data from a C++ routine. I am not familiar with C++, nor am I very familiar with mixed language programming in general. The biggest stumbling block I have is trying to get the two codes to "see" and "like" each other if you will.

Here is what I'm using:

Intel Fortran 12 Compiler

Microsoft Visual Studio2008

I'm going to start out with baby steps first. Below is a Hello World C++ program

[bash]// test.h #define CALL __declspec(dllexport) namespace testfuncs{ class testfuncs extern "C" void CALL cwrite_ (); } // testfuncs.cpp #include "test.h" #include #include using namespace std; namespace testfuncs { extern "C" void CALL cwrite_ (); }[/bash]

This seems to build okay and it creates a DLL named Cdll.dll.

First Problem ... There is no *.lib

I simply want to call this from a simple FORTRAN routine such as

program Forcall
implicit none
call write
end program Forcall

Any ideas?

0 Kudos
24 Replies
IanH
Honored Contributor III
4,025 Views
(Your C++ shows two declarations of a function named cwrite_ but no definition (there's no function body after the cwrite_ in the cpp file, so that's just another statement that says that a function named cwrite_ exists somewhere else). So your C++ dll has no useful code - so the linker doesn't bother creating an export library.)

(Do you really need to have the C++ code in a DLL - i.e. are the functions that are going to be in the DLL going to be shared across applications, or in the nature of a customisable plug-in or similar? I assume that you do in the following.

Do you really want the C++ name to end in an underscore? That's how some Fortran compilers decorated the linker names for procedures etc, but relying on that/creating such names today is needlessly fragile. I assume you don't in the following.)

Perhaps as a starting point:[cpp]// test.h #define CALL __declspec(dllexport) namespace testfuncs { extern "C" void CALL cwrite(); }[/cpp]
[cpp]// test.cpp #include "test.h" #include namespace testfuncs { extern "C" void CALL cwrite() { // do something visible. std::cout << "Hello world" << std::endl; } } [/cpp]
[fortran]! fortcall.f90 PROGRAM ForCall IMPLICIT NONE INTERFACE SUBROUTINE write() BIND(C,NAME='cwrite') END SUBROUTINE write END INTERFACE CALL write END PROGRAM ForCall[/fortran]
Within the relevant project properties in Visual Studio you will need to make sure that the C++ and Fortran projects have consistent settings for the run time library (they are both multithreaded [debug] DLL) and that the DLL is "findable" by the Fortran executable (perhaps by making the output directory for the two projects the same directory).
0 Kudos
markusda
Beginner
4,025 Views
Thanks a lot lanH. Now it works
0 Kudos
markusda
Beginner
4,025 Views
Hello,
I now have a problem with the parameters. I can put in easily characters and change them.
Putting in a REAL or a INTEGER doesn't work.
Here my code:
[bash]// cppdjj.h #define CALL __declspec(dllexport) namespace testfuncs{ extern "C" CALL void hello_world(); extern "C" CALL void get_integer(int I); extern "C" CALL void get_real(float* I); extern "C" CALL void get_character(char* I); } // cppdjj.h#define CALL __declspec(dllexport) namespace testfuncs{ extern "C" CALL void hello_world(); extern "C" CALL void get_integer(int I); extern "C" CALL void get_real(float* I); extern "C" CALL void get_character(char* I);} // cppdll.cpp #include "cppdjj.h" #include using namespace std; namespace testfuncs { extern "C" void CALL hello_world(){ cout <<"test"<
________________________________________
And here the Fortran Code:
[bash]program calldll implicit none integer :: a real :: d character*255 :: c INTERFACE SUBROUTINE hello_world() BIND(C,NAME='hello_world') END SUBROUTINE hello_world END INTERFACE INTERFACE SUBROUTINE get_real(re) BIND(C,NAME='get_real') REAL, INTENT(IN) :: re END SUBROUTINE get_real END INTERFACE INTERFACE SUBROUTINE get_integer(in) BIND(C,NAME='get_integer') INTEGER :: in END SUBROUTINE get_integer END INTERFACE INTERFACE SUBROUTINE get_character(ch) BIND(C,NAME='get_character') CHARACTER, INTENT(IN) :: ch END SUBROUTINE get_character END INTERFACE a = 4 d = 1.346 c = "hurz" !Calling C++ Dll call hello_world call get_real(d) call get_integer(a) call get_character(c) end[/bash]
____________________________________________________________________
This gives me the following output:
Input Real: 0018FE70
Enlarged: 0018FE74
Input Integer: 1637996
Enlarged: 1637997
Input Character: hurz
Changed Character: der Wolf, der hase
Any ideas how to handle this?
0 Kudos
JVanB
Valued Contributor II
4,025 Views
Your program is working well! You told the Fortran code to pass argument re of subroutine get_real by reference, and that is just what it did, passing the address of variable d by value. Then the C++ code was all ready to receive a pointer to float by value, and it printed out that value as Z'0018FE70'. It could also have printed out the value of the float pointed to by I as cout << *I << endl, but you chose not to do that. In C++, adding 1 to I adds 1*sizeof(*I) to the address that I represents, so after that I = Z'0018FE74'. If you wanted that to point at anything useful you should have declared d as real d(2) in the Fortran program and pased d(1) to get_real.

Now, your C++ code for get_integer calls for an int by value dummy argument, but your Fortran interface block specifies an int by reference. Thus Fortran passed C++ the address of a by value. If you wanted it to pass a by value, you would have changed the declaration of in in the interface body for get_integer to

INTEGER, VALUE :: in

Then the C++ get_integer function interprets the address it got by value as in int, so it get printed out in decimal, also adding 1 to an int just adds 1, not 1*sizeof(what?).

The character stuff is kind of strange, though. You have no guarantee that a terminating ASCII NUL will be present in the Fortran code as written. Had you said c = "hurz"//achar(0) it would have worked for sure. Also, a Fortran compiler might have chosen to make a temporary copy of c(1:1) and passed the address of that to get_character. If you don't want that to happen, declare argument ch in the interface block as

CHARACTER, INTENT(IN) ::ch(*)

Notice that get_character doesn't actually modify c because it just changes the argument I which is a pointer to char passed by value.
0 Kudos
markusda
Beginner
4,024 Views
Thanks a lot. But what if i want to put in just the value of a character?


[bash]INTERFACE SUBROUTINE func() BIND(C,NAME='func') CHARACTER :: path(*) END SUBROUTINE func END INTERFACE [/bash]
_____________________________
cpp:
[bash] extern "C" dllfunc void func(char path){ cout <<"Input Path: "<<
The char doesn't get to the dll. Any ideas?
0 Kudos
mecej4
Honored Contributor III
4,024 Views
This comment is based solely on inspection of the code that you showed in #4.

The interface block shows func as having no arguments, which is not consistent with the way that the function is declared in C/C++. Did you mean to write SUBROUTINEfunc(path)BIND(C,NAME='func') ?

Please show the actual code with the stated problem. Note also that C-interoperability does not cover Fortran character types of length other than 1.
0 Kudos
JVanB
Valued Contributor II
4,024 Views
The interface block corresponding to your C++ prototype is

[bash]INTERFACE SUBROUTINE func(path) BIND(C,NAME='func') USE ISO_C_BINDING IMPLICIT NONE CHARACTER(LEN=1,KIND=C_CHAR), VALUE :: path END SUBROUTINE func END INTERFACE [/bash]
0 Kudos
markusda
Beginner
4,024 Views
Hello,
is it possible to call a c++ function in fortran that needs a struct. Here is an example for the
c++ header:
[bash]#define dllfunc __declspec(dllexport) namespace testfuncs{ extern "C" struct interface_dll; extern "C" dllfunc void berechnung(interface_dll a); }[/bash]
c++ code:
[bash]#include "din743.h" #include using namespace std; namespace testfuncs { //declare the interface extern "C" { struct interface_dll{ int i; float r; char c; } ; } extern "C" void dllfunc berechnung(interface_dll a){ cout <<"integer "<<
Now I want to call this in FORTRAN:
here is my code:
[bash]program calldll implicit none structure /interface_dll/ integer:: i ! real:: r ! character*255:: c end structure record /interface_dll/:: interf INTERFACE SUBROUTINE berechnung(interf) BIND(C,NAME='berechnung') structure /interface_dll/ integer:: i ! real:: r ! character*255:: c end structure record /interface_dll/:: interf END SUBROUTINE berechnung END INTERFACE interf%i= 7 interf%r = 1.2345 interf%c = "interface_test" call berechnung(interf) end[/bash]
the output of the dll is the following:
integer 5093696
real 2.124 e-12
character !
So how to put a struc into a c-dll? any ideas? thanks,
Markus
0 Kudos
IanH
Honored Contributor III
4,024 Views
Yes. Fortran types can also be given the BIND(C) attribute, which tells the compiler that the type needs to be laid out in memory in a manner which is compatible with C.

(In Fortran, every type definition that does not have the BIND(C) attribute and is not a SEQUENCE type is unique - it describes a new type even if the text of two type definitions are identically the same. This is the reason for the error you observed - the interface_dll type defined on line 4 is treated as a completely separate type from the interface_dll type defined on line 15, and you attempt to pass an object of one variant in where another was expected.

Types definitions with the BIND(C) attribute are treated as being equivalent as long as the definition of the type has the same type, order and name for all the components; the definitions have no private components and the type parameters are the same (not relevant for ifort of today). The name of the type in the definition doesn't matter. Similarly for SEQUENCE types.)

You need to be mindful of pass by value/pass by reference issues discussed in #4 above. The following uses pass by reference - a pointer to the struct's data is passed rather than the struct's data itself. Whether that is appropriate depends on your needs.

To save typing in two declarations of the same type I have used the fortran 2003 import statement (I could repeat the definition if I wanted to, as it has the BIND(C) attribute as discussed above, but I am lazy).

Note that the fact that the C++ code is built into a dll is almost irrelevant here. I've rejigged your C++ a bit too.

[cpp]// testfuncs.h #define dllfunc __declspec(dllexport) namespace testfuncs { struct interface_dll { int i; float r; char c; }; // declare the function extern "C" dllfunc void berechnung(interface_dll* a); } [/cpp]

[cpp]// testfuncs.cpp // cl /EHsc /LD testfuncs.cpp #include "testfuncs.h" #include using namespace std; namespace testfuncs { // define the function extern "C" void dllfunc berechnung(interface_dll* a) { cout << "test" << a->i << endl; } } [/cpp]
[fortran]! ifort fortran.f90 testfuncs.lib program call_dll use, intrinsic :: iso_c_binding, only: c_int, c_char, c_float implicit none type, bind(c) :: interface_dll integer(kind=c_int) :: i real(kind=c_float) :: r character(kind=c_char) :: c end type interface subroutine berechnung(interf) bind(c,name='berechnung') import :: interface_dll implicit none type (interface_dll) :: interf end subroutine berechnung end interface type(interface_dll):: interf interf%i=7 call berechnung(interf) end program call_dll [/fortran]
0 Kudos
markusda
Beginner
4,025 Views
Super. Thanks a lot.
Now the only thing that is not working is how to handle characters.
Here my c++ code again:
Header:
[bash]#define dllfunc __declspec(dllexport) namespace testfuncs{ struct interface_dll; extern "C" dllfunc void berechnung(interface_dll *a); }[/bash] cpp:
[cpp]#include "din743.h" #include using namespace std; namespace testfuncs { //declare the interface // extern "C" { struct interface_dll{ int integer_value; float real_value; char character_value; char name; } ; // } extern "C" void dllfunc berechnung(interface_dll *a){ cout <<"integer "<integer_value<real_value<character_value<name<real_value = a->real_value+1; a->integer_value = 9; // a->character_value = "changed"; // a->name = "also_changed"; }[/cpp]
Here my fortran code:
[bash]program calldll use, intrinsic:: iso_c_binding, only: c_int, c_char, c_float implicit none type interface_dll integer (kind=c_int) :: integer_value real (kind=c_float) :: real_value character (kind=c_char,len=255) :: character_value, name end type type(interface_dll):: interf INTERFACE SUBROUTINE berechnung(interf) BIND(C,NAME='berechnung') import::interface_dll implicit none type(interface_dll) ::interf END SUBROUTINE berechnung END INTERFACE interf%integer_value= 7 interf%real_value = 1.2345 interf%character_value = "char_value_test" interf%name = "name_test" call berechnung(interf) end[/bash]
What works:
change of values (real and integer) by c++ dll
What doesn't work:
changing and using characters. the c++ dll does only get simple chars...
console:
real_value 1.2345
character_value c
name h
How to handle this? any ideas? thanks,
markus
0 Kudos
TimP
Honored Contributor III
4,025 Views
c_char applies directly only to arrays of single characters, although it supports a degree of compatibility with Fortran character strings. You would need to append a null character //achar(0) to make it work as a string in C or C++. There are plenty of examples ready for your search engine to discover.
0 Kudos
JVanB
Valued Contributor II
4,025 Views

Only character variables with len=1 are allowed in a type with the bind(C) property. This means you want to change the way you define the type in Fortran. Also you will want to change the type definition in C++ because as it stands you only have room for one char each.A statement such as

a->character_value = "changed"

makes no sense in C++ because it is trying to set a variable that can only hold a single char to a pointer value which holds 4 or 8 chars and has itself no sensible char value, or as changed to modify a pointer whose existence is really only implicit.You can use strcpy() or strstreams to do something more intuitive.Also the Fortran code gets more exciting because achar(0)-terminated arrays of length-1 character array aren't as convenient as length-255 scalars.Fortran does provide a syntax, however.

[bash]#define dllfunc __declspec(dllexport) namespace testfuncs { struct interface_dll; extern "C" dllfunc void berechnung(interface_dll *a); } #include #include using namespace std; namespace testfuncs { struct interface_dll { int integer_value; float real_value; char character_value[255]; char name[255]; }; extern "C" void dllfunc berechnung(interface_dll *a) { cout << "integer " << a->integer_value << endl; cout << "real " << a->real_value << endl; cout << "character " << a->character_value << endl; cout << "character " << a->name << endl; a->real_value = a->real_value+1; a->integer_value = 9; strcpy(a->character_value,"changed"); strcpy(a->name,"also_changed"); } } [/bash]
[bash]program calldll use, intrinsic :: iso_c_binding implicit none type, bind(C) :: interface_dll integer(kind=c_int) integer_value real(kind=c_float) real_value character(len=1,kind=c_char) character_value(255) character(len=1,kind=c_char) name(255) end type interface_dll type(interface_dll) interf interface subroutine berechnung(interf) bind(C,name='berechnung') import implicit none type(interface_dll) interf end subroutine berechnung end interface interf%integer_value = 7 interf%real_value = 1.2345 interf%character_value = & transfer([character(size(interf%character_value)):: & "char_value_test"//achar(0)],interf%character_value) interf%name = & transfer([character(size(interf%name)):: & "char_value_test"//achar(0)],interf%name) call berechnung(interf) write(*,'(a,i0)') 'interf%integer_value = ',interf%integer_value write(*,'(a,f0.4)') 'interf%real_value = ',interf%real_value write(*,'(256a)') 'interf%character_value = ', & interf%character_value(1: & index(transfer(interf%character_value, & repeat('A',size(interf%character_value))),achar(0))) write(*,'(256a)') 'interf%name = ', & interf%name(1: & index(transfer(interf%name, & repeat('A',size(interf%name))),achar(0))) end program calldll [/bash]
[bash]integer 7 real 1.2345 character char_value_test character char_value_test interf%integer_value = 9 interf%real_value = 2.2345 interf%character_value = changed interf%name = also_changed[/bash]
0 Kudos
markusda
Beginner
4,025 Views
Thanks. That would work. But is there no way to get a string like 'test' into the dll and change it to 'changed' in the dll by defining another type of character?
0 Kudos
markusda
Beginner
4,025 Views
thanks a lot. that really helped me
0 Kudos
markusda
Beginner
4,025 Views
Hello. I've a problem calling a dll-function that is written in cpp from my fortran project.
Unfortunately, I'm not able to receive the sources of the cpp-project. But here is what I have:
[cpp]namespace XYZ{ struct F_interface{ // declare the FVA-interface int int_value; float real_value; char text_value[80]; char name[32]; } ; extern "C" dllfunc int calc_XYZ(F_interface in[100]); } [/cpp]
dllfunc is defined in the header:
#define dllfunc __declspec(dllexport)
Here is how I want to call the function calc_XYZ from my fortran project:
[fortran]subroutine calldll use, intrinsic:: iso_c_binding , only: c_int, c_char, c_float implicit none integer :: error, i type F_interface character :: name*32, text_value*80 integer (kind=c_int):: int_value real (kind=c_float):: real_value end type type(F_interface) :: fv_interf(100) INTERFACE integer function dllfunc(fv_interf) BIND(C,NAME='calc_XYZ') import::FVA_interface implicit none type(F_interface) ::fv_interf(100) end function dllfunc END INTERFACE do i=1, 100 call INTERF_INIT(fv_interf(i)) enddo error = 1 error = dllfunc(fv_interf) end[/fortran]
The .lib is added. The dll is in the right folder. But I get the error:
LNK2019: unresolved symbol _calc_XYZ in _CALLDLL
Any ideas how to handle that?
Thanks
0 Kudos
Steven_L_Intel1
Employee
4,025 Views
I do not see, for the C++ project, however, a __declspec(dllexport) for dllfunc. Before someone jumps in and says you're missing a !DEC$ ATTRIBUTES DLLIMPORT on the Fortran side, that is optional for procedures. Are you sure that dllfunc is exported?
0 Kudos
markusda
Beginner
4,025 Views
Thanks for your answer Steve. I've checked the dll with a tool and found out, that the name of the exported func wasn't correct. Now it works.
Greets,
Markus
0 Kudos
markusda
Beginner
4,025 Views
Hello, i have a problem calling a c++ dll from fortran. The argument is an array of a type (fva_interface) ... here is what i have: Header in c++: // testfunc.h #define dllfunc __declspec(dllexport) namespace testfuncs{ struct FVA_interface; extern "C" dllfunc int testfunc(FVA_interface a[100]); } testfunc.cpp: // testfunc.cpp #include "testfunc.h" #include using namespace std; namespace testfuncs { //declare the interface struct FVA_interface{ int int_value; float real_value; char text_value[80]; char name[32]; } ; extern "C" int dllfunc testfunc(FVA_interface a[100]){ //test input cout <<"integer_value "<=' ';}; strcpy(a[0].text_value,"changed"); //character: name for(int i=0;i=' ';}; strcpy(a[0].name,"also_changed"); return 13; } } Here the Fortran-Code: PROGRAM CALL_TESTFUNC !DEC$ ATTRIBUTES DLLIMPORT USE, INTRINSIC:: ISO_C_BINDING , ONLY: C_INT, C_CHAR, C_FLOAT TYPE FVA_INTERFACE CHARACTER ...
0 Kudos
markusda
Beginner
4,025 Views
here again the testfunc.cpp #include "testfunc.h" #include using namespace std; namespace testfuncs { //declare the interface struct FVA_interface{ int int_value; float real_value; char text_value[80]; char name[32]; } ; extern "C" int dllfunc testfunc(FVA_interface a[100]){ //test input cout <<"integer_value "<
0 Kudos
Lorri_M_Intel
Employee
3,610 Views
The layout of your structures do not match. The Fortran derived type is defined as : TYPE FVA_INTERFACE CHARACTER :: NAME*32, TEXT_VALUE*80 ! These are defined first in the structure INTEGER (KIND=C_INT) :: INT_VALUE ! this is the third field REAL (KIND=C_FLOAT) :: REAL_VALUE ! this is the fourth field END TYPE The C struct is declared as: struct FVA_interface{ int int_value; //this is the first field float real_value; // this is the second field char text_value[80]; // this is the third field char name[32]; } ; Also, you should set the Fortran type as BIND(C) as: TYPE, BIND(C) :: FVA_INTERFACE That way the fields will stay in the same order as you specified them. Which will be good once you change the two declarations to match, of course. --Lorri
0 Kudos
Reply