-fallow-argument-mismatch

I am attempting to emulate gfortran/ifort unformatted sequential file records using access=‘stream’
Unfortunately for records larger than 2^31-9 bytes, it generates a record sequence that are 2^31-9 bytes long, ie not a multiple of 4. To merge the sub records, I am converting the buffer “rec_data”, which is provided as 4-byte (default) integers to 1-byte integer vector so the sub-records can be easily merged.
I am attempting to do this in a module of contained routines.

  712 |          call write_ifort_stream_record ( stream_lunit, address, rec_data, rec_bytes )
      |                                                                                      1
Error: Type mismatch in argument 'rec_data' at (1); passed INTEGER(4) to INTEGER(1)
mslib_t6.f90:721:77:

  721 |          call write_record_bytes   ( stream_lunit, pos, rec_data, rec_bytes )
      |                                                                             1
Error: Type mismatch in argument 'rec_data' at (1); passed INTEGER(4) to INTEGER(1)
mslib_t6.f90:319:85:

Unfortunately the compile option “-fallow-argument-mismatch” appears to be ignored, perhaps as the routines are contained in a module ?

I am using gfortran 11.1.0 and also 10.2.0.
Has anyone overcome this problem ?

@kargl

Thanks for your helpful explanation of the interpretation of “-fallow-argument-mismatch”.

I know there is a long history of discussion on similar issues to this, but there should be an option that changes the “Error: Type mismatch in argument” to “Warning: Type mismatch in argument” for all cases.

This is especially the case where the argument is basically a memory address to the start of an I/O record.
Valid use of memory addresses has a long history in Fortran, typically described as F77 wrapper construction and the inability to implement this without significant changes to Fortran code is unreasonable.

I don’t 100% understand what you are trying to do, but it sounds like transfer does what you want (packing four 1-byte ints into one four-byte int) without having to coerce the compiler into accepting non-standard code.

This code is typing to pack a sequence of 4 x 1-byte buffers that are 2^31-9 bytes long into an 8-gigabyte integer*4 buffer. I don’t think TRANSFER would be an effective solution. Relabeling the Integer(4) buffer as Integer(1) is a much simpler and well proven approach. It should not be banned.

If long unformatted sequential file records in ifort and gfortran were converted into a sequence of 2^31 - 16 bytes, rather than 2^31-9 bytes, this would be a much simpler problem. A more detailed description of the problem is discussed in the following link.

Clearly, the ifort and gfortran compilers have addressed this issue, without being restricted by this gfortran defined "Type mismatch in argument” error.

Thanks,

I will stop using contained procedures in the module and go back to a library of routines.
This approach resolves the problem.

This leads me to wonder what are the advantages of
contained procedures in the module vs a library of routines

An advantage is that the implicit interface assists in using contained functions,
but what else is available ?

I think one option could be to use iso_c_binding to get a pointer to your data with another type:

program main
    use iso_c_binding 
    implicit none
    
    integer, allocatable, target :: i(:)
    logical, pointer :: l(:) 
    
    i = [0,1,2,3,4]
    call c_f_pointer(c_loc(i), l, shape=[size(i)])
    
    print *, i
    print *, l
end program 

sizeof can be used to determine the correct shape when the storage size of the data and the view differs.

I suspect that’s likely to work, but technically is not standards conforming, as the standard says this:

If the value of CPTR is the result of a reference to C_LOC with a noninter-operable effective argument X, FPTR shall be a nonpolymorphic pointer with the same type and type parameters as X.

Other than the obsolete equivalence I do not believe there is a standards conforming way for a Fortran program to interpret a single section of memory as two different types. The Fortran standard doesn’t define a memory model, and so there are lots of reasons (dope vectors, len type parameters, any other meta-data the processor wishes) that the memory layout of two different types of arrays might be different. Any circumvention of the type system could invalidate a processors assumptions about its own memory layout conventions.

True, but using different types for a dummy and actual argument in a procedure without an interface would have the same problem. With this approach it is possible to cheat, but have interface checking for the rest of the code.

For standard compliance, transfer is probably the best option. It might even be that the compiler optimisation is able to do copy elison which would solve performance concerns if it’s actually the case.

Yep. What OP is trying to do is go outside the standard. That’s understandable in this case. I’d suggest that in a way, using an implicit interface/external procedure kind of lets the compiler know that, making sure it really does use an internal representation that lets it just pass a pointer.

For example

subroutine foo(arr)
  ! assumed shape, comes with a Fortran descriptor attached
  ! for shape, possible dope vector for non-contiguous, etc.
  integer :: arr(:)

  ! because the interface is either implicit
  ! or explicit as shown below
  ! the compiler knows it better make sure
  ! the actual data is contiguous
  ! and pass a pointer to the start of it.
  call bar(arr)
end subroutine

subroutine bar(arr)
  ! assumed size, basically just passes a pointer
  integer :: arr(*)
end subroutine

But OP’s use case is toward two different KINDs of the same intrinsic type integer and here the approach shown by @plevold, provided the reference result provided by C_LOC and the FPTR are both integers, is alright.

Note this is what I had illustrated earlier in this thread with a simple container type. OP can pretty much take the container type example with the bitbucket_t derived type shown therein and do what is stated in the original post, “To merge the sub records, I am converting the buffer “rec_data”, which is provided as 4-byte (default) integers to 1-byte integer vector so the sub-records can be easily merged.”

Or, OP can also use EQUIVALENCE with “data” stored as a MODULE entity and achieve a perfomant solution that way. EQUIVALENCE, by the way, is forever going to be part of the standard even if it is labeled as obsolescent (a big mistake by the committee on this) in the official publication.

OP can pursue a couple of different standard-conforming options, as stated here, that can work well performance-wise and which can also allow OP to not run into the gfortran error, “Type mismatch in argument.”

In Fortran Standardese, yes they are the same type, but I was using the word in the colloquial sense to include kind, and note that the section I quoted actually addresses it, e.g. “same type and type parameters”.

But even with equivalence, does the standard sufficiently define the behavior of equivalenceing arrays of different kind? My understanding is that it probably doesn’t since it doesn’t define the byte size or layout of the types. E.g. given two arrays of integers

integer(selected_int_kind(9)) :: a(2)
integer(selected_int_kind(10)) :: b(2)

how many bytes does each take up? Even then, assuming the larger range kind does occupy an integer multiple number more bytes than the smaller, given a particular integer value for an element of the larger kind, are the values of the smaller unambiguously defined by the standard? My understanding is no. I.e.

use iso_fortran_env, only: int32, int64

integer(int32) :: a(2)
integer(int64) :: b(1)

equivalence (a, b)

b(1) = 1234567890_int64
print *, a(1), a(2)

Will this print the same values on all systems with all compilers? Given the answer is likely no, what does equivalence for entities with different type/kind get you besides undefined behavior? And if you restrict yourself to only equivalence entities of the same type and kind, what does it give you that pointers don’t? So why keep it in the standard (other than “compilers will continue supporting it anyway”)?

1 Like

In this example, the C_LOC reference is to an interoperable type effective argument, so the restriction on type and type parameters (meaning type and kind) would not apply, right?

+1 Excellent points re: EQUIVALENCE.

The standard makes certain allowances for equivalenceing “default integer, default real, double precision real, default complex, default logical, or of numeric sequence type,” but otherwise has a numbered constraint to disallow equivalenceing the same intrinsic type of different KIND parameters.

Looking more closely at the standard, I think the code you show with equivalence-objects of same intrinsic type but different KINDs of int32 with int64 does not conform and constraint C8113 requires the processor to detect and report the violation. Both Intel Fortran and gfortran need to be explicitly “requested” to follow standard compliance before they report it.

1 Like

I think the following is an option that conforms to the standard and which anyone with similar needs as OP can consider:

   use iso_c_binding, only: c_int8_t, c_int32_t, c_loc, c_f_pointer

   integer(c_int32_t), target :: x
   integer(c_int8_t), pointer :: y(:)

   x = int( b"10101010101010101010101010101010", kind=kind(x) )
   call c_f_pointer( cptr=c_loc(x), fptr=y, &
      shape= [ storage_size(1_c_int32_t)/storage_size(1_c_int8_t) ] )

   print "(b32)", x
   print "(4b8)", y
end
C:\temp>gfortran -Wall -std=f2018 p.f90 -o p.exe

C:\temp>p.exe
10101010101010101010101010101010
10101010101010101010101010101010

The use of “likely” is a convenience for your argument, but please give an example of an actual compiler that is still being used and supports a recent Fortran Standard.

My problem I am addressing is to recast Integer4 as Integer1, so that I can get byte addressing.
The Integer*4 memory buffer is supplied via a subroutine argument, so equivalence is not an option.

There has been a lot of discussion about standard compliance, but as pointed out, the standard does not even consider the concept of a byte. Perhaps there is some recent concession in Stream IO definition?

A possible problem with my approach is the possibility of non-contiguous memory for the supplied buffer, but the buffer is typically defined by ALLOCATE.

@kargl , your reference to equivalence is also interesting, as I use the following (excuse non-standard for brievity):
integer1 :: bytes(8)
integer
4 :: words(2)
integer*8 :: eight_bytes
equivalence ( eight_bytes, words, bytes )

A historical construct for simplicity, but now non-conforming equivalence !

Yet the Fortran committee suggests this is to remove error prone coding approaches, but still supports explicit interface duplication.

I have solved the problem by removing the routines from being contained in a module so using -fallow-argument-mismatch now reports a warning. If only Intel had defined the maximum sequential record size as 2^31-16, this would have been much simpler.

( and why is 2^31-16 not an alternative syntax ( and 2**31 also being a problem in Fortran) not very user friendly. )

@FortranFan

Is the following code a bit simpler and more straight forward ?

   integer*4 :: x
   integer*1 :: y(4)
   equivalence (x,y)

   y = z"AA"

   print "(b32)", x
   print "(4b8)", y
end

You may presently view it as “a bit simpler and more straight forward” given your background and experience.

But if you think more broadly about all the practitioners, especially who started with Fortran some time after the Fortran 95 standard revision and the compilers which implemented said standard and other standard extensions subsequently, and if you study the current modern Fortran semantics in a more open-minded manner about all the possibilities and their standardization, you will start to see that no, what you show is neither simple nor straightforward across all the processors now and into the future.

And that is besides the fact what you showed does not conform to the standard in at least 3 aspects. If you consider a variant that goes with your use of EQUIVALENCE:

   use, intrinsic :: iso_fortran_env, only : int8, int32

   integer(kind=int32) :: x
   integer(kind=int8) :: y(4)

   equivalence (x,y)

   y = int( z"AA", kind=kind(y) )

   print "(b32)", x
   print "(4b8)", y
end
C:\temp>gfortran -c -Wall -std=f2018 p.f90
p.f90:4:20:

    4 |    equivalence (x,y)
      |                    1
Warning: Fortran 2018 obsolescent feature: EQUIVALENCE statement at (1)
eq.f90:4:18:

    4 |    equivalence (x,y)
      |                  1
Error: GNU Extension: Non-default type object or sequence y in EQUIVALENCE statement at (1) with objects of different type
C:\temp>ifort /c /standard-semantics /stand p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.7.0 Build 20220726_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

p.f90(6): warning #8873: EQUIVALENCE statements are obsolescent in Fortran 2018.
   equivalence (x,y)
---^
p.f90(6): warning #7162: If an equiv-object is of type default integer, default real, double precision, default complex, default logical, or numeric sequence type, all of the objects in the equiv set must be of these types.   [Y]
   equivalence (x,y)
------------------^

I have gone back to Lahey/Fujitsu Fortran 95 Language Reference for LF95 Ver 5.55.
As well as the “constraint” you have provided, it also states:

Remarks
If the equivalenced objects have different types or kinds, the EQUIVALENCE statement
does not cause any type conversion or imply mathematical equivalence.

If an equivalence-object is of an intrinsic type other than default INTEGER, default REAL,
double precision REAL, default COMPLEX, default LOGICAL, or default CHARACTER,
all of the objects in equivalence-set must be of the same type with the same kind value.

What are we to make of this inconsistency ?

LF95 was a more friendly programming environment and did not enforce this requirement you suggest.

My reading of that means that you can’t equivalence objects of different types or kinds, which is what I initially thought I remembered, but I looked it up in the draft of the next revision where it says:

C8114 (R875) If an equivalence-object is default integer, default real, double precision real, default complex, default logical, or of numeric sequence type, all of the objects in the equivalence set shall be of these types and kinds.

Which seems to indicate that you can equivalence different types/kinds so long as they’re all those specific intrinsic types and kinds. Although I suppose it does limit integers to default integer, so no equivalence to a different kind of integer.

You’re right. I grabbed the language from the wrong case.

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.

So, since integer(int32) is not interoperable with integer(int64) (or whatever different kinds OP is actually using), it’s still not standards conforming.