- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
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" #includeThis 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?
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
(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
[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).
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
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.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
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.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
[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]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
(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
[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]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
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]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]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page