C-Fortran interoperabilty: passing logical(kind=4) to Fortran

While passing logical variables to the subroutine from c, I found that by default logical(kind=1) is passed to the Fortran subroutine. However, the my subroutine accepts logical (kind=4).

Is it possible to pass logical(kind=4) from c or how to define logical(kind=4) in c? I don’t want to change the logical kind from the Fortran side, as there are many logical variables dispersed in many calling routines.

Would it be okay if you convert the logical value to an integer before passing it?

The integer interoperability works very well, and will not create compatibility issues in future.

Since logical values can be basically 0 or 1, you can use an integer in this case.

Maybe the C compiler has some command-line option to force the bool type to occupy 4 bytes instead of one, but I wouldn’t recommend his solution. In the Fortran code you can mix logical(kind=1) and logical(kind=4) without any problem. Most of time the casting will be implicit, only sometimes you will need explicit casting.

You may also write wrapper routines for the calls from C, and make all the casts in these routines.

2 Likes

you could also do something like

subroutine mysub( c_somebool ) bind(c)
        logical(c_bool), intent(in) :: c_somebool !> C boolean
        logical :: f_somebool !> fortran boolean
       
        f_somebool = logical( c_somebool  )
...
end subroutine
1 Like

I think that even passing logical(kind=1) is not guaranteed to work/standard conforming. ISO_C_BINDING defines only C_BOOL, which is, however, probably equivalent to logical(kind=1) in all compilers.

I see two options:

  1. If you have access to the code and there is no reason besides “don’t want to change the code”, familiarize yourself with regex or use search and replace and change the code. Avoid code changes because they require work is IMHO a indication of an non-working toolset.
  2. As mentioned in the other posts that appeared while I was typing, write a wrapper. At the Fortran side, you can even define an interface to have an overloaded routine that branches to your original function and the wrapper.
1 Like

@hkvzjal @MarDie @PierU @aerosayan; thank you all for the advice.

So it seems that writing a wrapper is the best option. Also, I can change the code using regex, etc but I don’t want to change it at the moment.

We are talking about the following difference:

! print_bool.f90
use iso_c_binding, only: c_bool
print *, storage_size(.true._4), storage_size(.true._c_bool)
end
$ gfortran -Wall print_bool.f90 
$ ./a.out
          32           8

In C the size of the type _Bool (C99) or bool (since C23) is implementation-specific, but appears to be one byte in most compilers, just like the one above. In Fortran, the standard requires the default logical has the same storage size as the default integer and real types.

I couldn’t find anything like this in gcc or clang (unless you modify the compiler yourself…) at least, which leaves only the wrapper option. You can choose between bool or an integer type:

subroutine print_bool(b)
    logical, intent(in) :: b
    print *, b
end subroutine

! Pass C _Bool as logical
subroutine f_print_bool_v1(b) bind(c)
   use, intrinsic :: iso_c_binding, only: c_bool
   integer, parameter :: lk = kind(.true.)
   logical(c_bool), value :: b
   call print_bool(logical(b,kind=lk))
end subroutine

! Use integer as logical
subroutine f_print_bool_v2(b) bind(c)
   use, intrinsic :: iso_c_binding, only: c_int
   integer, parameter :: FBOOL = c_int
   integer(FBOOL), value :: b
   logical :: fb
   fb = b /= 0    ! 0 is false, anything else is true
   call print_bool(fb)
end subroutine

The C binding would then look like this:

// f_binding.h
#include <stdbool.h>

typedef int FBOOL;
#ifndef FALSE
#define FALSE               0
#endif
#ifndef TRUE
#define TRUE                1
#endif

extern void f_print_bool_v1(bool b);
extern void f_print_bool_v2(FBOOL b);

The integer approach has the downside it can be misused:

FBOOL myFunc(int a)
{
    if (a < 3) {
       return FALSE;
    } else if (a > 3) { 
       return TRUE; 
    } else {
       return 2; // !???
    }
}

Nonetheless some API’s such as Win32 rely heavily on this approach. The difference between the Windows-specific BOOL and the standard C/C++ bool is a known source of problems according to this answer: windows - When should BOOL and bool be used in C++? - Stack Overflow

Trying to pass a 4-byte logical from C to Fortran, without using bind(c) is difficult. Compilers are allowed to use different internal representations for .true. and .false., meaning your C library would be tied to a particular Fortran compiler:

#if defined(GFORTRAN)
typedef int_fast32_t logical;
// We cast the `bool` to the wider integer type
#define logical(b) ((logical) b)
#elif defined(IFORT)
typedef int32_t logical;
// Convert to representation used in Compaq Visual Fortran
#define logical(b) ((b) ? -1 : 0)
#else
#error "Unsupported Fortran compiler"
#endif

#define FNAME(name) name##_
#define print_bool FNAME(print_bool)

// Compiler-specific (!) function prototype
extern void print_bool(logical *b);

void f_print_bool(bool b) {
    print_bool(logical(b));
}

To make things worse, the width of the default logical can change depending on compiler flags:

  • gfortran: -fdefault-integer-8
  • ifort: -integer-size 16|32|64, -i2|4|8
  • nagfor: -double, -i8

With the Intel Compiler, the representation can change depending upon the flags -fpscomp [no]logicals and -standard-semantics.

Even if you manage to do the preprocessor logic, account for flag-dependent behaviour and name-mangling, you are still left to deal with other dummy arguments (e.g. character variables).

thank you @ivanpribec for the illustrative example of handling logical variables. I spent some time exploring these data types. Yes, so far my experience with passing logical and character data types from C or Python has been not good enough.

As you mentioned, the character data is more intricate (in another post passing character and logical data from Python to Fortran, I mentioned this issue - any suggestion or link to some online/offline resources will be great ).

This thread leaves me wondering, why can’t the Fortran standardization committee lobby the C committee to include a Fortran-compatible logical type, or at least introduce such a type in the ISO Fortran binding source file.

Until C23, true and false (defined in stdbool.h) were just macros for integers:

#define bool    _Bool
#define true    1
#define false   0

By default an integer literal is of type int, and hence 4 bytes on most compilers. So if Fortran defined it’s own typedef:

typedef c_int32_t   CFI_logical;

The conversion from true and false would happen to work correctly, as long as the Fortran compiler uses the same internal 0 for .false. and 1 for .true.. Even if the default integer literal type in C was different, the implicit promotion to a shorter or wider type would take care of it.

Since C23, bool, true and false are not macros anymore. The type is now bool (instead of _Bool), and the true and false values are predefined constants (just like they are in Fortran). They also define the following default integral conversion:

If the source type is bool, the value false is converted to zero and the value true is converted to the value one of the destination type (note that if the destination type is int, this is an integer promotion, not an integer conversion).

So this would still happen to work.

The changes needed to the Fortran standard, would be

  • introduction of new logical kind constant

    F_LOGICAL is an integer scalar constant of the kind type parameter that specifies a LOGICAL type whose storage size matches the default logical kind kind(.false.) and is represented internally as an integer variable of default kind with the permissible values 1 for .true. and 0 for .false.. If the processor supports no such kind, the constant should be -1.

  • introduction of a typedef in ISO_Fortran_binding.h

    CFI_logical_t is typedef name for a standard signed integer type capable of representing the C values true and false. If supported, it is interoperable with the Fortran logical type with of kind F_LOGICAL.

  • introduction of an interoperable intrinsic type to the interoperability table

    Fortran type Named constant C Type
    LOGICAL C_BOOL _Bool (until C23), bool (since C23)
    LOGICAL F_LOGICAL CFI_logical_t (defined in ISO_Fortran_binding.h)

In gfortran, the value of F_LOGICAL would be 4, just like the current default integer and logical kinds.

In Intel Fortran this would also work, assuming the option -fpscomp logicals is enabled:

Specifies that integers with a non-zero value are treated as true, integers with a zero value are treated as false. The literal constant .TRUE. has an integer value of 1, and the literal constant .FALSE. has an integer value of 0. This representation is used by Intel Fortran releases before Version 8.0 and by Fortran PowerStation

(It may be necessary to make this stricter, as the above definition states that a non-zero value is true. Nevertheless, part of the behavior is already there).

In LFortran, I’m not entirely sure, but at least in the x86 backend, they use this representation: https://github.com/lfortran/lfortran/blob/2b99cd9e6e08e30088cfd5872137a6296b63409a/src/libasr/codegen/asr_to_x86.cpp#L251

LLVM Flang also appears use the C-like representation by default: https://github.com/llvm/llvm-project/blob/87dac9f1682c389c9feee6358263b049f1ad27d9/flang/include/flang/Evaluate/logical.h#L17

Just to reiterate the motivation for this, currently one is forced to write wrappers to convert Fortran logicals from or to the c_bool, despite the fact the true and false constants in C (or logical expressions for that matter) are of type int by default, and share this interpretation with most Fortran compilers.

1 Like

Here’s a sketch of how the C code should look like:

#include <stdbool.h>

typedef int32_t CFI_logical_t;

#define CFI_LOGICAL(predicate) ((predicate) ? true : false)

/*
 * subroutine pass_logical(b) bind(c)
 *   logical(f_logical), value :: b
 * end subroutine
 */
extern void pass_logical(CFI_logical_t b);

void test() {
  pass_logical(true);  // Works
  pass_logical(false); // Works
  pass_logical(5 > 4); // Works
  
  pass_logical(true || false); // Works

  pass_logical((bool) -1); // Works (true)
  pass_logical((bool)  0); // Works (false)

  pass_logical(42);                 // Error, violates permissible values
  pass_logical((CFI_logical_t) 42); // Error, as well

  pass_logical(CFI_LOGICAL(42)); // Works, but confusing
}

The biggest problem is there is no safety-net against mistakenly passing an integer. Arguably, this is no worse than the dozen of other implicit casting rules that exist in C. In principle the compilers could insert a runtime check in the Fortran routines annotated with bind(c).

With C11 generic selection, one could cook up something like this to detect wrong values when using the type macro:

// logical.c --
//      Example of using integers to represent 32-bit wide
//      Fortran-like logicals and C booleans.
//
//      Requires C11 standard.

#include <stdbool.h>
#include <stdint.h>
#include <stdio.h>
#include <assert.h>

typedef int32_t CFI_logical_t;

inline static CFI_logical_t _CFI_logical(CFI_logical_t L) { 
    assert(L == 1 || L == 0);
    return (L) ? true : false;
}

// Return type is CFI_logical_t
#define CFI_LOGICAL(X) _Generic((X),\
                _Bool: (CFI_logical_t)((X) ? true : false),\
              default: _CFI_logical(X))
 

int main(void) {

#define LCHAR(X) CFI_LOGICAL(X) ? 'T' : 'F'

    bool t = true;
    printf("%c\n", LCHAR(t));

    CFI_logical_t f = 3 > 4;
    printf("%c\n", LCHAR(f));

    printf("%c\n", LCHAR(3)); // Error!

    return 0;
}
$ gcc -Wall -std=c11 logical.c 
$ ./a.out
T
F
a.out: logical.c:12: _CFI_logical: Assertion `L == 1 || L == 0' failed.
Aborted (core dumped)

Unfortunately, this doesn’t give the desired line number.