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

Pass char* from C to Fortran

jura__julien
Beginner
2,437 Views

 

Hello,

I'm upgrading a huge C/Fortran project from VS6/Fortran PowerStation to vs2017/Intel Visual Fortran.
As i'm a total newbie with Fortran, I need your help to pass string data from a C function call to a Fortran subroutine.

I read a lot about this but there's so many way to achieve this so i prefer create a new post.

Until now C code call Fortran subroutine with string arg this way :

// C Side

extern void		FORTRAN BOUTON(float*,float*,float*,float*,char*,UINT,ENTIER*,ENTIER*,char*,UINT);

void BarresIcons_Bouton(float x, float y, float dx, float dy, char *texte, char *icone, ENTIER id, char *AideFR, char *AideUS)
{
	ENTIER	iCoul	= 16;
	ENTIER	iDesTex	= 0;
	char	*Aide;

	BOUTON(&x, &y, &dx, &dy, texte, &iCoul, &iDesTex, icone);

	// ...
}

// FORTRAN Side

SUBROUTINE bouton (x1,y1,a,b,texte,icoul,icout,icon)

	INCLUDE 'xxxxxxxx'
	INCLUDE 'xxxxxxxx'
      
	DIMENSION	x(10),y(10)
	DIMENSION	windo(4)
	CHARACTER*(*) texte
	CHARACTER*(*) icon

c      // etc ....

END SUBROUTINE

With C passing some hidden args to compute char * length
Note bouton subroutine own 8 args but extern "C" declaration has 10

Now i would know the best way to deal with char * of any size from C to Fortran because actually I can't just recompile the source code :
- calling convention has changed from __stdcall to __cdecl
- when C call Fortran subroutine, the call stack crash because args num mismatch
- it seems ther's no more char * "hidden args" passed

 

Best regards
Julien

 

ps : i read those topics before but there so many question about Bind(C), ISO_C_BINDING & the new fortran syntaxe. All the existing code is written in Fortran 77

0 Kudos
13 Replies
JVanB
Valued Contributor II
2,437 Views

How did you change from __stdcall to __cdecl? Did you just change the Fortran compiler switch from /iface:cvf to /iface:default? I think this means you have to also add /iface:mixed_str_len_arg to the Fortran command line. I think that the issue with UINT being the wrong type for string lengths on 64-bit systems won't be a problem provided the C compiler always zeros the high 32 bits of the value it places on the stack and you aren't passing your entire genome as a character string. To be safer you could pass SIZE_T lengths rather than UINT ones.

 

0 Kudos
TimP
Honored Contributor III
2,437 Views

The default scheme when you don't use iso_c_binding has the hidden length arguments at the end of the list.  This has been more frequently used in the past than the mixed length scheme, but still not portable.  I don't know whether mixed order is possible after switching to c_decl, but I wouldn't recommend returning to cvf stdcall mixed scheme.

iso_c_binding eliminates the hidden length arguments, and is a portable scheme.  Any of the advices about c_binding character strings you will find on the internet will work with any of the compilers.  Typically, you must deal with appended NUL characters in order to handle variable length strings this way.

0 Kudos
jura__julien
Beginner
2,437 Views

 

@Repeat Offender: For the calling convention : I didn't change anything in the vfproj properties because default are set to __cdecl (from the doc)
I just change in c/c++ project properties. Note that each imported Fortran method
(see my code) is prefixed by extern "C" __cdecl (my FORTRAN define directive is set to __cdecl)

The ideal case would be minimal changes to existing sources (there's huge) so keeping the hidden string length args would be perfect in my case. Actually String Length argument passing is set to After All argument (Thanks for pointing it)

@Tim : Nice precisions. Is it possible to use ISO_C_BINDING only for fortran to C interface, not in fortran to C call ? Actually all my FORTRAN subroutine include a module which define interface to C function

SUBROUTINE bouton (x1,y1,a,b,texte,icoul,icout,icon)
       USE win32_C

	INCLUDE 'yyyyyy'
	INCLUDE 'xxxxxx'
      
	DIMENSION	x(10),y(10)
	DIMENSION	windo(4)
	CHARACTER*(*) texte
	CHARACTER*(*) icon

with win32_C module defined as follow :

c INTERFACE FORTRAN - C 32 bits

      MODULE win32_C

	  USE, INTRINSIC :: ISO_C_BINDING
      USE ISO_C_BINDING
      IMPLICIT NONE

	  INTERFACE

      SUBROUTINE funcA(a,b,c,d,e)
     * bind(c, name="funcA")
      USE ISO_C_BINDING
      IMPLICIT NONE
      integer			a [VALUE]
      integer			b [VALUE]
      real				c [VALUE]
      real				d [VALUE]
      real				e [VALUE]
      end

      SUBROUTINE funcB(a,b,c,d)
     * bind(c, name="funcB")
      USE ISO_C_BINDING
      IMPLICIT NONE
      integer			a [VALUE]
      integer			b [VALUE]
      CHARACTER(KIND=C_CHAR), DIMENSION(*) ::		c
      integer			d [VALUE]
       end

Maybe theses 3 lines at the top of module should be removed ?

USE, INTRINSIC :: ISO_C_BINDING
USE ISO_C_BINDING
IMPLICIT NONE

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,437 Views

When tim_p says "iso_c_binding" he really means "bind(C)". Two different things.

0 Kudos
jura__julien
Beginner
2,437 Views

I've modified the String Length argument passing as suggested by Repeat Offender and now calling Fortran from C is OK ! fine !
I'm still using __cdecl calling convention, not __stdcall.

I suspect call from Fortran to C to crash the app. Is this kind of Fortran to C interface still supported in Visual Fortran ?

 interface to subroutine Tbl_Init
     * [C, ALIAS:"_Tbl_Init"] (a,b,c,d,e)
      integer			a [VALUE]
      integer			b [VALUE]
      real				c [VALUE]
      real				d [VALUE]
      real				e [VALUE]
      end

      interface to subroutine Tbl_Texte
     * [C, ALIAS:"_Tbl_Texte"] (a,b,c,d)
      integer			a [VALUE]
      integer			b [VALUE]
      character*(*)		c [REFERENCE]
      integer			d [VALUE]
       end

      interface to subroutine Tbl_Entier
     * [C, ALIAS:"_Tbl_Entier"] (a,b,c)
      integer			a [VALUE]
      integer			b [VALUE]
      integer			c [VALUE]
       end

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,437 Views

That's a Microsoft Fortran PowerStation extension. It is still supported, but I would strongly recommend that you switch to the Fortran standard syntax, as follows:

interface
    subroutine Tbl_Init (a,b,c,d,e) bind(C,NAME="Tbl_Init")
    integer, value :: a
    integer, value :: b
    integer, value :: c
    integer, value :: d
    integer, value :: e
    end subroutine Tbl_Init

    subroutine Tbl_Texte (a,b,c,d) bind(C,NAME="Tbl_Texte")
    integer, value :: a
    integer, value :: b
    character :: c(*)
    integer, value :: d
    end subroutine Tbl_Texte

    subroutine Tbl_Entier (a,b,c) bind(C,NAME="Tbl_Entier")
    integer, value :: a
    integer, value :: b
    integer, value :: c
    end subroutine Tbl_Entier
end interface

The one thing this doesn't do is pass the length of character value c to Tbl_Texte. If that is needed, you would probably want to add a separate argument with the length. The way you're doing it now is highly non-portable and also won't work in a 64-bit build.

0 Kudos
FortranFan
Honored Contributor II
2,437 Views

jura, julien wrote:

.. The ideal case would be minimal changes to existing sources (there's huge) so keeping the hidden string length args would be perfect in my case. ..

@jura, julien,

As you indicated in the original post, there are several ways to handle this, ultimately you and your team will need to decide the best way to handle this, particularly define for yourself what "minimal changes" really mean.  By defining UINT in your C code to be an alias for size_t, you might be able to leave all your C code as is.  Then depending on your needs, you can go with an Intel Fortran only approach or a truly portable using the C interoperability features available in Fortran since the 2003 standard revision.  Here's an example based on the code snippet in your original post:

C code - note the typedef for UINT to size_t:

#include <stdio.h>
#include <stdlib.h>
#include <string.h>

typedef size_t UINT;
typedef int ENTIER;

extern void BOUTON(float*,float*,float*,float*,char*,UINT,ENTIER*,ENTIER*,char*,UINT);
extern void BOUTON_IFORT_ONLY(float*, float*, float*, float*, char*, UINT, ENTIER*, ENTIER*, char*, UINT);


int main() {

   enum L { L = 12 };
   enum N { N = 25 };

   float x, y, dx, dy;
   char texte;
   ENTIER iCoul;
   ENTIER iDesTex;
   char icone;

   x = 1.0f; y = 2.0f; dx = 0.1f; dy = 0.2f;
   strncpy( texte, "Hello World!", (size_t)L );
	iCoul	= 16;
	iDesTex	= 0;
   strncpy( icone, "Mary had a little lamb", (size_t)N );

   BOUTON(&x, &y, &dx, &dy, texte, (size_t)L, &iCoul, &iDesTex, icone, (size_t)N);
   BOUTON_IFORT_ONLY(&x, &y, &dx, &dy, texte, (size_t)L, &iCoul, &iDesTex, icone, (size_t)N);

   return 0;

}

Fortran code: note the 2 possible ways of defining your Bouton procedure, the first is the recommended portable approach but the second is limited to Intel Fortran compiler:

module m

   use, intrinsic :: iso_c_binding, only : c_char, c_int, c_float, c_size_t, c_ptr, c_f_pointer

   implicit none

   private

   public :: bouton
   public :: bouton_ifort_only

contains

   subroutine bouton(x1, y1, a, b, cp_texte, lentexte, icoul, icout, cp_icon, lenicon)                &
      bind(C, name="BOUTON")

      ! Argument list
      real(c_float), intent(inout) :: x1
      real(c_float), intent(inout) :: y1
      real(c_float), intent(inout) :: a
      real(c_float), intent(inout) :: b
      type(c_ptr), intent(in), value :: cp_texte
      integer(c_size_t), intent(in), value :: lentexte
      integer(c_int), intent(inout) :: icoul
      integer(c_int), intent(inout) :: icout
      type(c_ptr), intent(in), value :: cp_icon
      integer(c_size_t), intent(in), value :: lenicon

      ! Local variables
      character(kind=c_char,len=:), allocatable :: texte
      character(kind=c_char,len=:), allocatable :: icon

      print *, "In bouton:"
      print *, "x1 = ", x1
      print *, "y1 = ", y1
      print *, "a = ", a
      print *, "b = ", b
      blk1: block
         character(kind=c_char,len=lentexte), pointer :: fp_texte
         call c_f_pointer( cptr=cp_texte, fptr=fp_texte )
         texte = fp_texte
         print *, "texte = ", texte
         fp_texte => null()
      end block blk1
      print *, "icoul = ", icoul
      print *, "icout = ", icout
      blk2: block
         character(kind=c_char,len=lenicon), pointer :: fp_icon
         call c_f_pointer( cptr=cp_icon, fptr=fp_icon )
         icon = fp_icon
         print *, "icon = ", icon
         fp_icon => null()
      end block blk2

      return

   end subroutine bouton

   subroutine bouton_ifort_only(x1, y1, a, b, texte, icoul, icout, icon)
   !DIR$ ATTRIBUTES C, MIXED_STR_LEN_ARG, REFERENCE, ALIAS : 'BOUTON_IFORT_ONLY' :: bouton_ifort_only

      ! Argument list
      real, intent(inout) :: x1
      real, intent(inout) :: y1
      real, intent(inout) :: a
      real, intent(inout) :: b
      character(len=*), intent(inout) :: texte
      integer, intent(inout) :: icoul
      integer, intent(inout) :: icout
      character(len=*), intent(inout) :: icon

      ! Local variables

      print *, "In bouton_ifort_only:"
      print *, "x1 = ", x1
      print *, "y1 = ", y1
      print *, "a = ", a
      print *, "b = ", b
      print *, "texte = ", texte
      print *, "icoul = ", icoul
      print *, "icout = ", icout
      print *, "icon = ", icon

      return

   end subroutine bouton_ifort_only

end module

Build and execution:

C:\temp>ifort /logo
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R
) 64, Version 18.0.1.156 Build 20171018
Copyright (C) 1985-2017 Intel Corporation.  All rights reserved.

ifort: command line error: no files specified; for help type "ifort /help"

C:\temp>cl /c c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.11.25508.2 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c.c

C:\temp>ifort /c /standard-semantics /warn:all f.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R
) 64, Version 18.0.1.156 Build 20171018
Copyright (C) 1985-2017 Intel Corporation.  All rights reserved.


C:\temp>link c.obj f.obj /subsystem:console /out:p.exe
Microsoft (R) Incremental Linker Version 14.11.25508.2
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>p.exe
 In bouton:
 x1 =  1.000000
 y1 =  2.000000
 a =  0.1000000
 b =  0.2000000
 texte = Hello World!
 icoul =  16
 icout =  0
 icon = Mary had a little lamb
 In bouton_ifort_only:
 x1 =  1.000000
 y1 =  2.000000
 a =  0.1000000
 b =  0.2000000
 texte = Hello World!
 icoul =  16
 icout =  0
 icon = Mary had a little lamb

C:\temp>

 

0 Kudos
jura__julien
Beginner
2,437 Views

So i checked with my team and it was really quick because i'm the only one on this project :)

- It's ok to define a constant and change UINT to size_t in the C world.
- for Fortran subroutine declaration i'm currently pretty close to the first one method except bind(C) and arguments type's kind and intent are missing but actually Fortran calls from C are ok.

As far as i understand : to tell how to expose FORTRAN subroutine to C in a portable way, i should add bind(c) to each subroutine. And adding bind(c) means "I want to use the news fortran 2003 approach ISO_C_BINDING" so i have to tell for each arguments the type, kind and intent. Also the win32_C module which currently expose all the fortran subroutine is no more needed. I'm right ?

Thank Steve for precision. I've already modified the MS Powerstation interface def to something like this :

 

c INTERFACE FORTRAN - C 32 bits

      MODULE win32_C

	  USE, INTRINSIC :: ISO_C_BINDING

	  INTERFACE

c =======================================
C Tableaux
c =======================================
      SUBROUTINE funcA(a,b,c,d,e)
     * bind(c, name="funcA")
      USE ISO_C_BINDING
      IMPLICIT NONE
      integer			a [VALUE]
      integer			b [VALUE]
      real				c [VALUE]
      real				d [VALUE]
      real				e [VALUE]
      end

      SUBROUTINE funcB(a,b,c,d)
     * bind(c, name="funcB")
      USE ISO_C_BINDING
      IMPLICIT NONE
      integer			a [VALUE]
      integer			b [VALUE]
      CHARACTER(KIND=C_CHAR), DIMENSION(*) ::		c
      integer			d [VALUE]
       end

MS Powerstation alias were changed to bind(c, name"xxxxx") and each subroutine in the interface contains "USE_ISO_C_BINDING". CHARACTER(KIND=C_CHAR), DIMENSION(*) :: c style definition was used to deal with characters. i'm good ? (even I don't specify any intent).

0 Kudos
FortranFan
Honored Contributor II
2,437 Views

jura, julien wrote:

.. As far as i understand : to tell how to expose FORTRAN subroutine to C in a portable way, i should add bind(c) to each subroutine. And adding bind(c) means "I want to use the news fortran 2003 approach ISO_C_BINDING" so i have to tell for each arguments the type, kind and intent. Also the win32_C module which currently expose all the fortran subroutine is no more needed. I'm right ? ..

Well, if you want to be sure of how to setup the callback in a portable manner, show the C function prototypes for funcA and funcB.

Btw, it's spelt Fortran and not FORTRAN, it's been so "officially" for over 25 years now: https://en.wikipedia.org/wiki/Fortran#Naming

And it was that way in the very beginning too: The Fortran Automatic Coding System for the IBM 704 (15 October 1956), the first Programmer's Reference Manual for Fortran

Fortran_acs_cover (1).jpeg

 

0 Kudos
Steve_Lionel
Honored Contributor III
2,437 Views

Julien, that looks good so far.

0 Kudos
jura__julien
Beginner
2,437 Views

Thanks everyone for your help. Fortran project upgrade is done !

0 Kudos
Valerio_F_
Beginner
2,437 Views
I'm dealing with the same problem of julien. I followed the the first is the recommended portable approach and all works fine, in the sense that character are passed correctly from c to fortran and the fortran simple reads the values But now I have to deal with a string that has to be passed to fortran and fortran modify it. In the case reported for example if you modify texte variable inside fortran this modification is kept until the conter is inside fortran routine but nothing happens on c side. Probably iso binding convention allocates inside fortran another array copy value fron c pointer and use it. How can I deal if I want to read and after change the value inside fortran ? Thanks
0 Kudos
Steve_Lionel
Honored Contributor III
2,437 Views

Valerio, please create a new thread and attach a small but complete example that demonstrates your problem. There is no copying unless you declare the argument with the VALUE attribute.

0 Kudos
Reply