Reshaping arrays via explicit length arguments

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.

I think it is standard. This is based on storage sequence association, which has been defined for the intrinsic types since before f77, and was extended for user defined types starting with f90. It only works for explicit shape and assumed size arrays, which were the only types of array dummy arguments in f77. It does not work for assumed shape arrays, where the ranks of the actual and dummy arguments must match. This aliasing is also allowed for common block arrays of different ranks, again dating back to before f77.

Also, if the actual argument is not contiguous, then copy-in/copy-out association must be done for the dummy argument, which has performance implications, so the programmer must be careful with using this feature.

There is a related feature involving storage sequence association of character strings and character arrays.

Pointer assignment of a high-rank pointer to a rank-1 target array is also allowed and is another way to alias arrays of different ranks.

According to my reading of the F2023 interpretation document J3/24-007, this case falls under sequence association (page 331, section 15.5.2.12, paragraph 1):

Sequence association only applies when the dummy argument is an explicit-shape or assumed-size array. The rest of this subclause only applies in that case

Paragraph 6 of the same section states,

An actual argument that represents an element sequence and corresponds to a dummy argument that is an array is sequence associated with the dummy argument. The rank and shape of the actual argument need not agree with the rank and shape of the dummy argument (emphasis added), but the number of elements in the dummy argument shall not exceed the number of elements in the element sequence of the actual argument. If the dummy argument is assumed-size, the number of elements in the dummy argument is exactly the number of elements in the element sequence.

The fact that this is an internal procedure appears irrelevant. It’s the explicit-shape dummy argument which permits sequence association. To get rank checking, rewrite the procedure as follows,

subroutine mustbe_1d(array)
    type(mytype), intent(inout) :: array(:)
    integer(int32):: j
    do j = 1, size(array)
      array(j)%k = j
    enddo
  end subroutine

In this case the rules state (page 237, paragraph 16),

If a dummy argument is an assumed-shape array, the rank of the actual argument shall be the same as the rank of the dummy argument, and the actual argument shall not be an assumed-size array.

So in this case the ranks must be the same.


The LAPACK procedures rely heavily on sequence association. For example if you look at the procedure DGESV, the B argument is 2-d array, however it is very common to solve a problem with a single right-hand side vector:

real(kind(1.0d0)) :: a(3,3), b(3)
integer :: ipiv(3), info
external :: dgesv
! ... fill a and b 
call dgesv(3,1,a,3,ipiv,b,3,info)

Before Fortran 90 introduced dynamic memory allocation, it was common to use fixed-size work buffers (i.e. memory pools) and designate areas for different purposes,

       integer ipiv(10), info
C work area for matrix A and vector b
       double precision work(10,10)
C solve a 3-by-3 system with 1 right-hand side
       call dgesv(3,1,work(1,1),10,ipiv,work(1,4),10,info)

LAPACK also uses storage sequence association heavily internally, for instance if you look at the DGETRF2 procedure.