I have a question about the rules for matching the rank of explicit-shape arrays when the interface for the subroutine is known. Consider the following code
program flattening_test
use iso_fortran_env, only : int32
implicit none
type mytype
integer(int32) :: k
end type mytype
class(mytype), allocatable :: multidim_array(:,:)
integer(int32), parameter :: num = 4
integer(int32) :: i
allocate(mytype :: multidim_array(num,num))
call reinterpret_1d(multidim_array,num*num)
contains
subroutine reinterpret_1d(array, n)
integer(int32), intent(in) :: n
type(mytype), intent(inout) :: array(n)
integer(int32):: j
do j = 1, n
array(j)%k = j
enddo
end subroutine reinterpret_1d
end program flattening_test
GFortran accepts this without complaint. It’s unclear to me if this ends up being a GNU extension or if this is valid. However, the interface is known and the compiler is matching a 2D array to the 1D explicit-shape dummy argument. Does the Fortran standard clarify if this rank mismatch being allowed or disallowed? When you put this subroutine in a different compilation unit and do not provide an interface then there is no opportunity for the compiler to complain.