-fallow-argument-mismatch

If anyone seeks bit handling in Fortran with type punning in the most unfortunate absence of a full-featured bit string facility in the language, the broken-record-of-a- suggested-approach remains using the interoperable types and intrinsic module procedures in the standard:

   use iso_c_binding, only: int8 => c_int8_t, int16 => c_int16_t, &
                            int32 => c_int32_t, int64 => c_int64_t, &
                            c_loc, c_f_pointer
   logical, parameter :: IS_BIG_ENDIAN = iachar( c=transfer(source=1,mold="a") ) == 0

   integer( int8), pointer ::  i8(:)
   integer(int16), pointer :: i16(:)
   integer(int32), pointer :: i32(:)
   integer(int64), target  :: i64

   call c_f_pointer( cptr=c_loc(i64), fptr=i8, shape=[ storage_size(1_int64)/storage_size(1_int8) ] )
   call c_f_pointer( cptr=c_loc(i64), fptr=i16, shape=[ storage_size(1_int64)/storage_size(1_int16) ] )
   call c_f_pointer( cptr=c_loc(i64), fptr=i32, shape=[ storage_size(1_int64)/storage_size(1_int32) ] )

   i64 = 1
   print "(g0,*(b64.64))", "i64: ", i64
   if ( IS_BIG_ENDIAN ) then 
      print "(g0,*(b32.32))", "i32: ", (i32(i), i=1,size(i32),1)
      print "(g0,*(b16.16))", "i16: ", (i16(i), i=1,size(i16),1)
      print "(g0,*(b8.8))", "i8:  ", (i8(i), i=1,size(i8),1)
   else
      print "(g0,*(b32.32))", "i32: ", (i32(i), i=size(i32),1,-1)
      print "(g0,*(b16.16))", "i16: ", (i16(i), i=size(i16),1,-1)
      print "(g0,*(b8.8))", "i8:  ", (i8(i), i=size(i8),1,-1)
   end if
   print "(g0,z0)", "Address of i64: ", transfer(c_loc(i64), mold=1_int64)
   print "(g0,z0)", "Address of i32: ", transfer(c_loc(i32), mold=1_int64)
   print "(g0,z0)", "Address of i16: ", transfer(c_loc(i16), mold=1_int64)
   print "(g0,z0)", "Address of i8: ", transfer(c_loc(i8), mold=1_int64)

end
C:\temp>gfortran p.f90 -o p.exe

C:\temp>p.exe
i64: 0000000000000000000000000000000000000000000000000000000000000001
i32: 0000000000000000000000000000000000000000000000000000000000000001
i16: 0000000000000000000000000000000000000000000000000000000000000001
i8:  0000000000000000000000000000000000000000000000000000000000000001
Address of i64: C8CB1FF7C8
Address of i32: C8CB1FF7C8
Address of i16: C8CB1FF7C8
Address of i8: C8CB1FF7C8

I agree with this practical statement, but it is still unclear to me if this is standard conforming and how portable it is. Are there any compilers that would reject this kind of code? Do any print warnings, but then proceed to work correctly? Are there any fortran integer kinds that are not interoperable with some C type and should therefore be avoided?

It is still not standards conforming, as I indicated earlier in the thread. Re:

If the value of CPTR is the C address of an interoperable data entity, FPTR shall be a data pointer with type and type parameter values interoperable with the type of the entity.

An integer(int64) is not interoperable with an integer(int8).

It’s portability is entirely dependent on the endian-ness and representation strategy for integers on the systems in question (i.e. 1 or 2s compliment or signed magnitude). If one does not care about the integer value corresponding to the bits in question (i.e. just treating them as raw bits), then that probably isn’t of concern. But the values printed by the following example are not defined by the standard.

use iso_fortran_env

integer(int64) :: x
integer(int8) :: y(8)

x = 1234567890_int64
y = transfer(x, y)
print *, y
end

I am finding this discussion really very stupid.

Why has the Fortran standard committee decided to make EQUIVALENCE obsolete ?

What is the justification ?

It is a way to manage memory addresses, which have been the basis of Fortran since it was first developed.

I look at code I have, as an example from Win API, function GlobalMemoryStatusEx, which uses equivalence.

It has a practical way to look at and manage memory, as a sequence of bytes. This is a basic approach to memory usage. Is Fortran trying to ban the concept of memory as a sequence of bytes; that all variables and arrays have a memory address ?

Look at how long it took for the function LOC to appear in the Fortran standard (assuming it has been included, as I don’t have a copy of the recent standard).
Should EQUIVALENCE have been extended and allow subroutine arguments; to recast arguments ?
Or perhaps on 32-bit OS, LOC be a 32-bit unsigned integer kind that has been required since 3-gbytes of addressable memory was available ?
Where is the support for Fortran users, rather than Fortran religious zealots ?

Up until this post, in 2022!, I did not even know of all these restrictions placed on EQUIVALENCE. My use of the standard has been to look for new features/improvements in the language, not these unnecessary restrictions.

Why should the Fortran committee decide this concept of memory location should not be used ?

It just amazes me that a language that has been in existence for over 60 years has a committee who can decide that a concept, as basic as memory address can be removed from the language, especially when the implementation of subroutine/function arguments are basically a series of memory addresses on the stack; something the Standard committee are trying to say we can no longer use.

If compilers start to implement these unnecessary restrictions, Fortran users will be forced to use other compilers that don’t religiously follow this committee. Will compilers like NAG become standard checkers and not be used for Fortran computation?

No, the above assertion by @everythingfunctional is inaccurate.

The example I showed upthread with integer(int64_t) target and a pointer of integer(int8_t) of appropriate shape falls under the combination of Fortran type and type parameters case mentioned in section 18.3.1 Interoperability of intrinsic types in the standard.

It is the combination that I showed which makes it interoperable.

In a way this is similar to the situation with the Fortran standard whereby the C type of unsigned char is indeed interoperable with an integer type with a kind type parameter of C_SIGNED_CHAR.

It was years ago when Intel Fortran had fully implemented TS 29113:2012 as part of what was then called Fortran 2015 that I had first explored facilities in Fortran similar to the union type in C and challenged the standard to determine this was both viable and not excluded by the standard.

It is that last statement that I was unsure about, namely exactly what is and isn’t “interoperable”.

Furthermore, in a statement like

call c_f_pointer( c_loc(i64), i8pt, [n] )

there really isn’t anything that is being executed in C. The arguments are all specified as if the information will be passed to a C function, but in the applications we are talking about here, everything is really done in 100% fortran. So what exactly does any “interoperable” limitations of the C coprocessor do to a statement like that? That statement could be generalized in the fortran standard to apply to any intrinsic type and kind that is supported by the fortran processor (maybe with numeric mixed with character types not included).

That there is a companion processor working with the Fortran processor, and which may be the Fortran processor itself or a gazillion minions doing all the work or an actual C compiler, and which importantly conforms to ISO/IEC 9899:2011 specifications toward the C standard.

As I wrote above, in the situation at hand, it is the combination of Fortran type and type parameters that comes into play with the Interoperability and therefore, what I showed upthread is kosher.

If a reader with access to NAG compiler can try out the code I showed, it will be useful to read a report here of the NAG response given its penchant for conformance. NAG Fortran compiler too can be expected to process the above code ok without any report of standard violations with the strictest checking enforced, just as gfortran and Intel Fortran both do now.

You’re going to have to explain this one to me. I don’t understand how a C int8_t is compatible with a C int64_t. Maybe it’s just my lack of experience in C?

A combination of Fortran type and type parameters that is interoperable with a C type listed in the table is also interoperable with any unqualified C type that is compatible with the listed C type.

Is the word “unqualified” doing some heavy lifting I’m not grasping?

In the quoted phrase, “the entity” is not required to be a C entity. But it is an entity that is interoperable between C and Fortran (i.e. it has a defined type in both C and Fortran), but could be a value produced by either side. Thus the statement can still apply in a Fortran only situation.

nagfor operates as one would expect:

$ nagfor main.f90 -o main && ./main
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7116
[NAG Fortran Compiler normal termination]
i64: 0000000000000000000000000000000000000000000000000000000000000001
i32: 0000000000000000000000000000000000000000000000000000000000000001
i16: 0000000000000000000000000000000000000000000000000000000000000001
i8:  0000000000000000000000000000000000000000000000000000000000000001
Address of i64: 55689ED01760
Address of i32: 55689ED01760
Address of i16: 55689ED01760
Address of i8: 55689ED01760

HOWEVER, this is not a situation in one which can check for conformance generally. I.e.

use iso_c_binding
use iso_fortran_env
type(c_ptr) :: p
integer(int64), target :: x
real(real32), pointer :: y

x = 42_int64
p = c_loc(x)
call c_f_pointer(p, y)
print *, y
end

produces

$ nagfor main.f90 -o main && ./main
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7116
[NAG Fortran Compiler normal termination]
   5.8854536E-44

but I’m pretty sure that’s not standards conforming. The reason is once an entity is type(c_ptr), the processor cannot determine what it’s actual type is, and so it can’t be determined at compile time whether the CPTR argument is compatible with the FPTR argument, and there’s probably no special cases to try and do so when the CPTR happens to be produced inline with a call to c_loc.

Yes, I agree that it applies to the fortran-only situation. My other point was that the fortran standard could be extended so that that statement (or something equivalent to that statement with different syntax) could be allowed to operate on any intrinsic fortran type, not just those that happen to be interoperable with a companion C compiler.

I know that C has void pointers, and I know that any pointer in C can be converted to a void pointer and back again. What exactly, if any, are the limitations on the C side about type punning variables by converting their pointers in this way?

@JohnCampbell , my reading is that actually Fortran has never had any explicit concept of memory addresses. One might argue that the recent type(c_ptr) does this to a degree, but it is still just a kind of black box nod to the idea that C has an explicit concept of memory addresses. That programmers have made assumptions and treated certain constructs that way does not necessarily mean that it has ever been portable or standards conforming.

My interpretation (which I’ll admit may be somewhat subjective and not be exactly historically accurate) is that Fortran was invented specifically to avoid machine dependence and enable portability. Memory addressing and bit representations are specifically machine dependent and so Fortran intentionally avoids saying much of anything about them. Also, type systems were invented specifically to avoid accidentally interpreting bit representations in different, incompatible ways. That EQUIVALENCE allowed for this (intentionally or not), is now seen as a mistake, hence it being marked as obsolete. The new TRANSFER still enables the reinterpretation of a bit pattern, but forces it to be explicit at the point that it happens.

I’m sympathetic to those who wish that Fortran did have an explicit concept of memory addresses, and perhaps it would be feasible to add a new intrinsic type to the standard, a la address (or something similar). But even still, it seems your specific problem in the original post would be more suitably solved by a new bit_string intrinsic (which I’d also be sympathetic to). My guess though is that it will always be considered non-conforming to interpret the bit pattern for a value of one type as a value of a different type, because it is demonstrably not portable. There’s lots of nuance there though, because something like the following would be non-conforming:

integer :: x
real :: y
x = 42 
print *, transfer(x, y)

but the following would be conforming,

integer :: x
real :: y
x = 42
print *, transfer(transfer(x, y), x)
1 Like

Just that it’s undefined behavior (if I’m not mistaken).

Does anyone know of, and can provide evidence to the effect, a language where re-interpreting a bit pattern as a value of a different type than it was originally created is not undefined behavior? I’m not saying you can’t write programs that “do it correctly” by taking machine/environment dependencies into consideration, but that it’s not strictly defined by the language.

One exception that comes to mind is the storage sequence association of real and complex variables. That association can be either through common blocks or with equivalence. As a practical matter, programmers also do it through type punnng with dummy arguments, but I don’t think that last situation is defined in the standard and would therefore be undefined behavior.

That’s an interesting edge case/exception, but I think the way it’s expressed isn’t actually interpreting them as different types. I.e.

The values of a complex type are ordered pairs of real values.

Yes, I would agree that it is exceptional within fortran. Do you agree that it is undefined behavior to type pun real and complex arrays through dummy argument association? If so, then I would say that feature makes real and complex arrays a different type. Also, the association that is defined (for common block storage association and for equivalence) is not done at the bit level but rather at the level of pairs of real values as you point out. In modern fortran, there is also the z%re and z%im notation in which a complex variable is treated as if it were an intrinsic derived type with two real components. That also suggests that a complex type is distinct from a real type as far as TKR considerations are concerned.

It’s very nuanced. I would say that it is not standards conforming, but in the particular case of real vs complex arrays, the storage sequence and correspondence of the types is such that it isn’t undefined behavior. I.e.

call foo((42.0, 3.14))
end

subroutine foo(a)
  real, intent(in) :: a(2)

  print *, a
end subroutine

It is well defined by the standard what will be output there, but the call to foo is not standards conforming because the implicit interface does not match the actual procedure, because yes, complex is distinct from real as far as TKR is concerned. It really is a weird edge case.

TL;DR is the C standard has well-defined semantics with compatible types, ranks of integer types, exact-width integer types in <stdint.h>, contiguous memory alignment of its array types, and casting operations with the pointer types of compatible targets that there isn’t anything undefined per se in the bit-field representation of casting something like so:

#include <stdint.h>

..
   int64_t i64;
   i64 = ..;
   .. 
   int8_t* i8 = (int8_t*)&i64;
   ..

Sure the representation is processor-dependent (endian-ness specific) and thus the coder has to take extra steps to handle that.

The above cast is essentially what is done in the Fortran snippet upthread with facilities in the iso_c_binding intrinsic module.

So what I am trying to convey is with suitably chosen types as shown above, one is doing supported casting operation as opposed to any undefined, nonstandard type punning.

Just to make sure I understand the argument here, what you’re saying is that because C allows this casting/type-punning, it should be considered valid Fortran to use c_f_pointer to do the same casting as C allows provided the Fortran types are interoperable with C types that are allowed to do that. It’s kind of a roundabout explanation, but I suppose I don’t see a step in the logic that is invalid. I.e.

use iso_c_binding

interface
  subroutine pun_ints(x, y) bind(C)
    integer(c_int_64), intent(in) :: x
    integer(c_int_32), intent(out) :: y(2)
  end subroutine
end interface

integer(c_int_64) :: x
integer(c_int_32) :: y(2)

x = 1234567890_c_int_64
call pun_ints(x, y)
print *, y
end
#include <stdint.h>

extern void pun_ints(int64_t * x, int32_t * y) {
  *y = (int32_t)*x;
}

you see nothing that isn’t standards conforming in that example, and so why require the middle-man? I’m not sure I’m 100% convinced yet. Could you write an example that manually does something like what your previous example with c_f_pointer does? I couldn’t work out how to manipulate Fortran pointers from C off the top of my head.

If I’m reading that sentence correctly, you are saying that it is defined by the fortran standard. I think it is for common block storage sequence and for equivalence (of real and complex) but I don’t think it is for type punning through dummy arguments. I don’t know why the standard did not include that case, but I don’t think it does (or ever did). This is despite decades of use where fortran programmers did exactly that because with 1960s era compilers, programmers could program the complex arithmetic by hand better than the compilers could. I think by the 1980s, compilers had caught up, but there was still tons of legacy code by that time that did the type punning approach instead.

complex z(n)
...
call sub(n,z)
...
subroutine sub(n,z)
real z(2,n)
...