How to write a C binding to call a Fortran subroutine with character argument z1*(*)?

Is the below the correct C prototype to use to call the below Fortran subroutine?

SUBROUTINE TEST (Z1)
CHARACTER Z1*(*)

END

void test_(char* z1, int leng);

int main ()
{
char *z1;
int leng = 10;
test_(z1,leng);
}

That subroutine is not compatible with C, nor have you used it correctly on the C side if it were.

First, if Iā€™m not mistaken, the syntax CHARACTER Z1*(*) is not standards conforming, but I believe the first * is just superfluous. Somebody please correct me if Iā€™m wrong, but I believe this is equivalent to character(len=*) :: z1.

Many compilers do silently add a length argument to the compiled code for keeping track of the length, but it is not dictated how they should do so, and may differ between compilers and versions. The C prototype youā€™ve provided may work sometimes, but not others.

You havenā€™t actually allocated any memory on the C side, so when you pass the pointer to Fortran, who knows what itā€™s pointing at, and whatever itā€™s pointing at wasnā€™t what was intended.

I give an example of how to properly pass a C string to Fortran in this video: Just Talk to Each Other: Getting Fortran and C to Work Together - YouTube

Edit: In this example, the first * is actually not superfluous, but the equivalent declaration I gave is equivalent to the original code.

Edit: The example that demonstrates this starts around the 18 minute mark in that video. Itā€™s slightly different from OPā€™s example, in that the original string has already been created on the Fortran side, and thus itā€™s already been allocated by the time C gets hold of it. In OPā€™s case, he needs to manually allocate space for the string on the C side.

No, the standard currently only marks the CHARACTER*char_length form of declaration as redundant in the obsolescent features section under Appendix. Unfortunately the chances are very high the support for this form will never be deleted from the standard; also, you can be more certain the current crop of compilers will continue supporting this feature than you can be of death and taxes!

Nonetheless, CHARACTER(len=*) is the suggested form even according to the standard.

Separately I donā€™t think OP is interested in standard compliance. OP would do well to frame inquiries better in the original post, say along the following lines: tell me which small change can make x/y/z work using gfortran on Windows without having to use BIND(C).

1 Like

As an exercise in ā€œminimal changesā€, your original code would technically ā€œworkā€, but is missing some key aspects. The change you made is actually not valid Fortran (I think, unless itā€™s some syntax Iā€™m not aware of). To illustrate the danger here, letā€™s try and actually do stuff with the string.

subroutine test(z1)
    character(len=*) :: z1
    print *, z1
    z1 = "Hello, Fortran!"
end subroutine
#include <stdio.h>
#include <string.h>

void test_(char* z1, int leng);

int main ()
{
  char *z1 = "Hello, C!";
  test_(z1,strlen(z1));
  printf("%s\n", z1);
}
$ gfortran -c -g test.f90 -o test.o    
$ gcc -c -g main.c -o main.o           
$ gfortran -g test.o main.o -o main.exe
$ ./main.exe 
 Hello, C!
zsh: segmentation fault (core dumped)  ./main.exe

Just because the program appears to work you should not conclude that the code is correct. Nor can you expect someone to tell you all the things that can go wrong with your code, particularly if you are going to make changes to it later.

Make one small change to the Fortran source: add a space before the exclamation mark:

    z1 = "Hello, Fortran !"

Compile and run the changed program, and try to understand what went wrong, and why.

@giraffe ,

Well, your original post doesnā€™t indicate anything in terms of any enhancements, so how do you think any reader can use that as a basis to suggest any improvements.

Generally though, if you want to work securely and portably with standard Fortran and are willing to put up with considerable verbosity, boilerplate code, and the care demanded by mixed-language programming, especially with strings and structs, shown below is something you can consider.

Try it out and comment here if you would like a brief ā€œcommentaryā€ on the various aspects it includes and I can type it for you in a separate post.

Surely this will all appear painstaking to you but paying attention to all the details will help you in the long run, especially with needing to start fewer threads online and experiencing far fewer disappointments!

  • Fortran code
module m
   use, intrinsic :: iso_c_binding, only : c_char, c_size_t, c_loc, c_f_pointer, c_null_char
contains
   subroutine Fsub(s, lens) bind(C, name="Fsub")
      ! Argument list
      character(kind=c_char,len=1), intent(inout), target :: s(*)
      integer(c_size_t), intent(in), value :: lens
      block
         character(kind=c_char, len=lens), pointer :: str
         integer(c_size_t) :: n
         call c_f_pointer( cptr=c_loc(s), fptr=str )
         print *, str
         str = c_char_"Hello, Fortran!"
         n = min( lens, len_trim(str, kind=c_size_t)+1 )
         str(n:) = c_null_char
         str => null()
      end block
   end subroutine
end module
  • C code
#include <stdlib.h>
#include <string.h>
#include <stdio.h>

extern void Fsub(char *, size_t);

int main()
{
   enum SLEN { SLEN = 21 }; // some desired string length + 1 for null termination
   char *str;
   str = (char *) malloc((SLEN)*sizeof(char));
   memset( str, '\0', sizeof(char)*SLEN );
   int l = snprintf(str, SLEN, "%s", "Hello C!"); 
   Fsub(str, (size_t)SLEN);
   printf("%s\n", str);
   free(str);
   return(0);
}
  • Program behavior using GCC/gfortran:

C:\Temp>gfortran -c c.c

C:\Temp>gfortran -c m.f90

C:\Temp>gfortran c.o m.o -o c.exe

C:\Temp>c.exe
Hello C!
Hello, Fortran!

1 Like

Why bother to work on the code at all if youā€™re going to convert it to another language? And if you get it running, why do you then need to convert it to another language?

1 Like

@giraffe , in any subsequent threads you start anywhere in the cyberspace, especially at this Discourse, please state this clearly and boldly upfront. That way the readers will know better how to make best use of their time.

Generally it appears StackOverflow will be a good place to make your inquires: that forum strives for discipline with both questions as well as replies. Thatā€™s a very useful thing to have in the threads you start.

As to discipline, please try to refrain from vague statements such as, ā€œbased on the original post what improvements can be made.ā€

The code you have shown in various threads require far too many changes and improvements in both your C and Fortran snippets even toward your immediate goal, ā€œjust have to get the program to run on a 64 bit machine.ā€

So what you and/your employer have stuck to in terms of workarounds only with Fortran only to throw it all away to migrate to another language soon is itself too onerous for any meaningful engagement online.

Please understand this and use that to respect othersā€™ time.

2 Likes

@giraffe,

Please note if you share further details e.g., your programming background and strengths and interested and also convey a willingness to learn and quickly adopt modern Fortran facilities even for a short duration of getting this code with your employer to run on 64-bit platform before itā€™s all rewritten in another language, you will likely get further pointers that can really speed this all up for you and your employer and enable rapid migration away from Fortran.

Say you indicate your strengths and interests lie in C or C++, that might indicate one approach; or Python or Julia, some other.

For now let us presume your background and interests are in the C language. And now that you think iso_c_binding is interesting (by the way itā€™s BIND(C) that really matters, not the module), you might be further intrigued by ā€œISO_Fortran_binding.hā€, the C header that enables the binding to Fortran on the C side.

Iā€™m surprised no one has pointed ISO_Fortran_binding.h out to you yet, perhaps itā€™s because of pending issues with gfortran implementation.

But with this, if someone whose expertise lies with C and is willing to do a bit of work on the C side of the code can make matter simpler on the Fortran side of the fence.

Take the modified version of the code in your original post: you will still be advised to

  1. CONTAIN it in a MODULE in Fortran,
  2. use BIND(C) and use interoperable types and kinds instead of the default ones in Fortran

And just for illustration purposes, assume the Fortran subprogram is to receive a string of length 20 and the Fortran subprogram the defines the dummy argument with some value, like so.

module m
   use, intrinsic :: iso_c_binding, only : c_char
contains
   subroutine test(s) bind(C, name="test_")
      ! Argument list
      character(kind=c_char,len=*), intent(inout) :: s
      print *, "In Fsub: len(s) = ", len(s), "; expected is 20"
      s = c_char_"Hello Fortran!"
   end subroutine
end module

So then a C program as shown below can be a caller for this Fortran subroutine:

#include <stdio.h>
#include "ISO_Fortran_binding.h"

extern void test_(CFI_cdesc_t *);

int main()
{
   enum SLEN { SLEN = 20 }; // some desired string length
   char s[SLEN] = "";
   CFI_CDESC_T(0) sdat; // employ a macro defined in Fortran binding header
   int i = CFI_establish((CFI_cdesc_t *)&sdat, s, CFI_attribute_other,
                          CFI_type_char, (size_t)SLEN, (CFI_rank_t)0, (CFI_index_t)0); 
   test_((CFI_cdesc_t *)&sdat);
   printf("%s\n", s);
   return 0;
}

So here, note how the C code sets up a char array of desired length, it sets up a C descriptor type for interoperation with Fortran, and consumes the Fortran subprogram.

You can see how the Fortran side is now far less verbose and more importantly, the Fortran subprogram has a dummy argument of assumed-length (character(len=*)) which is otherwise not permitted in interoperable procedures. Note this is made workable by specific instructions on the C side using the descriptors and also the CFI_establish function. These became available starting Fortran 2018.

Click to see program behavior

C:\Temp>cl /c /W3 /EHsc c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.29.30038.1 for x64
Copyright (C) Microsoft Corporation. All rights reserved.

c.c

C:\Temp>ifort /c /standard-semantics m.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

C:\Temp>link c.obj m.obj /subsystem:console /out:c.exe
Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.

C:\Temp>c.exe
In Fsub: len(s) = 20 ; expected is 20
Hello Fortran!

The (len=*) part should be attached to the character keyword, not to the variable. I.e. character(len=*) C, not character C(len=*)

You should understand that the problem here is not a buffer overflow made in Fortran part, as Fortran does know the length of z1 and will not copy more characters from the RHS. The problem is that Fortran will not put ā€˜\0ā€™ character to mark the end of the string, as (almost all) C functions expect. And thatā€™s one of the reasons other people here have been encouraging you (unsuccessfully :frowning: ) to use proper Fortran-C interoperability mechanisms. Now with your conclusion

it proves to be even worse waste of their time.

1 Like