C-Fortran interface type in CFI_cdesc_t

I recently started experimenting with the Nvidia nvfortran compiler. I have some code that make use of the C-Fortran interop features and the CFI_cdesc_t descriptor. I immediately noticed some peculiar behavior, and would like to hear with this community what your opinion are.

I have a C++ routine that print the type of a C-interop array from Fortran:

#include <ISO_Fortran_binding.h>

#include <iostream>
#include <cassert>

extern "C" {
    void check_array(CFI_cdesc_t* data) {
        std::cout << "data->type: " << static_cast<int>(data->type) << std::endl;

        // Some implementations does noty differ between different identical integer types
        if (data->type == CFI_type_int) {
            std::cout << "Type: int" << std::endl;
        }
        if (data->type == CFI_type_long) {
            std::cout << "Type: long" << std::endl;
        }
        if (data->type == CFI_type_long_long) {
            std::cout << "Type: long long" << std::endl;
        }
        if (data->type == CFI_type_int32_t) {
            std::cout << "Type: int32_t" << std::endl;
        }
        if (data->type == CFI_type_int64_t) {
            std::cout << "Type: int64_t" << std::endl;
        }
        if (data->type == CFI_type_float) {
            std::cout << "Type: float" << std::endl;
        }
        if (data->type == CFI_type_double) {
            std::cout << "Type: double" << std::endl;
        }
    }
}

With the accompanying Fortran program:

PROGRAM main
    USE, INTRINSIC :: ISO_C_BINDING
    USE, INTRINSIC :: ISO_FORTRAN_ENV
    IMPLICIT NONE

    INTERFACE
        SUBROUTINE check_array(res) BIND(C)
            TYPE(*), INTENT(in) :: res(:)
        END SUBROUTINE check_array
    END INTERFACE

    INTEGER :: default_integer(1)
    INTEGER(c_int) :: c_int_integer(1)
    INTEGER(c_long) :: c_long_integer(1)
    INTEGER(c_long_long) :: c_long_long_integer(1)
    INTEGER(c_int32_t) :: c_int32_t_integer(1)
    INTEGER(c_int64_t) :: c_int64_t_integer(1)

    INTEGER(int32) :: int32_integer(1)
    INTEGER(int64) :: int64_integer(1)

    WRITE(*, '("Size of default_integer: ", I0)') C_SIZEOF(default_integer(1))
    CALL check_array(default_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of c_int_integer: ", I0)') C_SIZEOF(c_int_integer(1))
    CALL check_array(c_int_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of c_long_integer: ", I0)') C_SIZEOF(c_long_integer(1))
    CALL check_array(c_long_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of c_long_long_integer: ", I0)') C_SIZEOF(c_long_long_integer(1))
    CALL check_array(c_long_long_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of c_int32_t_integer: ", I0)') C_SIZEOF(c_int32_t_integer(1))
    CALL check_array(c_int32_t_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of c_int64_t: ", I0)') C_SIZEOF(c_int64_t_integer(1))
    CALL check_array(c_int64_t_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of int32_integer: ", I0)') C_SIZEOF(int32_integer(1))
    CALL check_array(int32_integer)
    WRITE(*, '()')

    WRITE(*, '("Size of int64_integer: ", I0)') C_SIZEOF(int64_integer(1))
    CALL check_array(int64_integer)
    WRITE(*, '()')
END PROGRAM main

Basically, I tried compilers from GNU, Intel, NAG and Nvidia. They fall in two categories: GNU, Intel and NAG gives output like:

Size of default_integer: 4
data->type: 1025
Type: int
Type: int32_t

Size of c_int_integer: 4
data->type: 1025
Type: int
Type: int32_t

Size of c_long_integer: 8
data->type: 2049
Type: long
Type: long long
Type: int64_t

Size of c_long_long_integer: 8
data->type: 2049
Type: long
Type: long long
Type: int64_t

Size of c_int32_t_integer: 4
data->type: 1025
Type: int
Type: int32_t

Size of c_int64_t: 8
data->type: 2049
Type: long
Type: long long
Type: int64_t

Size of int32_integer: 4
data->type: 1025
Type: int
Type: int32_t

Size of int64_integer: 8
data->type: 2049
Type: long
Type: long long
Type: int64_t

This example is output from Gfortran/G++ version 12. Besides the actual value of the data->type which is implementation dependent, both Intel and NAG gives the same output. The key of this is that the c_int kind, which should be interoperable with int in C is of type CFI_type_int and CFI_type_int32_t at the same time, because CFI_type_int == CFI_type_int32_t.

With nvfortran and nvc++ I get a different result:

Size of default_integer: 4
data->type: 9
Type: int32_t

Size of c_int_integer: 4
data->type: 9
Type: int32_t

Size of c_long_integer: 8
data->type: 10
Type: int64_t

Size of c_long_long_integer: 8
data->type: 10
Type: int64_t

Size of c_int32_t_integer: 4
data->type: 9
Type: int32_t

Size of c_int64_t: 8
data->type: 10
Type: int64_t

Size of int32_integer: 4
data->type: 9
Type: int32_t

Size of int64_integer: 8
data->type: 10
Type: int64_t

As you see, the different integers from Fortran all map to either int32_t or int64_t. So if I have a check in my program:

assert (data->type == CFI_type_int);

this will always fail.

I find it peculiar that the type you get when you pass an c_int from Fortran to C is not equal to CFI_type_int… Any opinions on this?

An additional observation is that the header file ISO_Fortran_binding.h provided by the Nvidia nvfortran compiler is very similar to that from the (new) Flang compiler in the LLVM repo. All the symbols and definitions seem to be the same. I do not have access to the new Flang right away, if any of you have it it would be interesting if you could run my example.

1 Like

Could you post the content of ISO_Fortran_binding.h?

The ISO_Fortran_binding.h is very close to the one in the “new” Flang repo:

The constants (CFI_type_int, CFI_type_int32_t) have the same values.

But apparently not when compiled,

extern "C" {

    bool are_equal(){ 
        return CFI_type_int == CFI_type_int32_t;
    }
    bool cnst_true() { return true; }
    bool cnst_false() { return false; }
}
define dso_local signext i8 @are_equal() #0 mustprogress !dbg !85 {

        ret i8 0, !dbg !89
}

define dso_local signext i8 @cnst_true() #0 mustprogress !dbg !92 {

        ret i8 1, !dbg !95
}

define dso_local signext i8 @cnst_false() #0 mustprogress !dbg !97 {

        ret i8 0, !dbg !100
}

are_equal returns the value 0, which matches the constant false.

When I preprocess only, using the flag -E, I get the output:

# 2 "/app/example.cpp" 2

extern "C" {

    bool are_equal(){ 
        return 3 == 9;
    }
    bool cnst_true() { return true; }
    bool cnst_false() { return false; }

}

In the Flang repo they have different values,

#define CFI_type_int 3
...
#define CFI_type_int32_t 9

They don’t… And the comment is important:

/* These codes are required to be macros (i.e., #ifdef will work).
 * They are not required to be distinct, but neither are they required
 * to have had their synonyms combined.
 */
#define CFI_type_int 3
...
#define CFI_type_int32_t 9

On the Fortran side, there is nothing that says that any integer kind should be the same as any other, even if they have the same representation. That said, if that were the case, I would expect those kind values to be preserved across calls in to C, not all mapped to the same kind.

Huh!? “always”!!? You mean only the assertion is not definitive?!

You may help yourself by taking a look at the standard document first and then consulting, say, Modern Fortran Explained, would you have saved you some time. Both touch upon this c.f. the 24-007 proxy document for Fortran 2023:

Section 18.3.1 of the document you refer to has the following:

A Fortran intrinsic type with particular type parameter values is interoperable with a C type if the type and kind type parameter value are listed in the table on the same row as that C type.

From this table 18.2 it is, without any doubt, given an INTEGER(C_INT) on the Fortran side is interoperable with an int on the C side. Anyone disagree?

And then, in table 18.4 you refer to, it is also no doubt about that an int on the C side shall have a type specifier in the CFI_cdesc_t structure corresponding to CFI_type_int - right?

How can it be, that an INTEGER(C_INT) declared in the Fortran side does not result in an CFI_type_int on the C side?

1 Like

I think that this is basically because you could as well write:

integer(kind=4) :: arr(1)

and still have a perfectly valid Fortran code with an interoperable array arr. In such a case what should the compiler put in data->type? Why more CFI_type_int rather than CFI_type_int32_t or CFI_type_int_least32_t ? nvfortran/nvcc just decides that any integer(kind=x) with x=4 is described with CFI_type_int32_t in the descriptor, which is plain correct.

The weird thing is to have different CFI_type_* values that map to the same actual type, but they have maybe some good reason for that.

@hakostra ,

Are you choosing to misinterpret the statement in the standard document, “The values for different C types can be the same; for example, CFI_type_int and CFI_type_int32_t might have the same value.”

Consider a simple example like so:

  • source for the companion C processor
#include <stdio.h>
#include "ISO_Fortran_binding.h"

void f( CFI_cdesc_t *, CFI_cdesc_t * );

void f( CFI_cdesc_t *a, CFI_cdesc_t *b ) {
  printf("In C function f: a->type = %d\n", (int)a->type);
  printf("and b->type = %d\n", (int)b->type);
  printf("For this processor, CFI_type_int = %d\n", (int)CFI_type_int);
  printf("and CFI_type_int32_t = %d\n", (int)CFI_type_int32_t);
  return;
}
  • and for the Fortran processor
   use, intrinsic :: iso_c_binding, only : c_int, c_int32_t
   interface
      subroutine Cfunc( a, b ) bind(C, name="f")
         import :: c_int, c_int32_t
         integer(c_int), allocatable, intent(inout) :: a
         integer(c_int32_t), allocatable, intent(inout) :: b
      end subroutine
   end interface
   integer(c_int), allocatable :: x
   integer(c_int32_t), allocatable :: y
   call Cfunc( x, y ) 
end 
  • One processor gives a program response:
C:\temp>gfortran -c c.c

C:\temp>gfortran -c -ffree-form p.f

C:\temp>gfortran p.o c.o -o p.exe

C:\temp>p.exe
In C function f: a->type = 1025
b->type = 1025
For this processor, CFI_type_int = 1025
and CFI_type_int32_t = 1025

C:\temp>

which shows you that your wondering out aloud is effectively inaccurate: “How can it be, that an INTEGER(C_INT) declared in the Fortran side does not result in an CFI_type_int on the C side?,”

To borrow your turns of phrase, it is possible with a Fortran processor and its companion C processor

  1. for an “INTEGER(C_INT32_T) declared in the Fortran side” to also “result in an CFI_type_int on the C side” and
  2. an “INTEGER(C_INT) declared in the Fortran side” to also “result in an CFI_type_int32_t on the C side,”

but that is just how things are, for those on the Fortran standard committee, in their “infinite” wisdom, working on enhanced interoperability with C - as part of TS 29113 and Fortran 2018 - thought it to be alright.

Regardless, your assertion, " when you pass an c_int from Fortran to C is not equal to CFI_type_int" is incorrect with conforming processors.