Explicit-shape and assumed-size arrays, and sequence association

At FortranTip I focus on modern Fortran, but Fortranners will sometimes need a reading knowledge of older features. I have already discussed the preferred assumed-shape arrays but think explicit-shape and assumed-size arrays should be mentioned. Here are a few tweets I intend to post. Since I am rusty with these features I would appreciate corrections.

Tweet 1: Explicit-shape arrays

For explicit-shape arrays, the dimensions are passed as dummy
arguments. This should be avoided when possible in new code, in favor
of assumed-shape arrays, since the dimensions may be passed incorrectly.

Code:

! Code illustrates explicit-shape arrays and sequence association,
! discussed at Dr Fortran "I've Come Here For An Argument" and
! https://michaelgoerz.net/notes/advanced-array-passing-in-fortran.html

module explicit_shape_mod
implicit none
contains
subroutine print_vec(n, r)
integer, intent(in) :: n
integer, intent(in) :: r(n) ! explicit shape-array
print "(*(i3))",r
end subroutine print_vec
end module explicit_shape_mod
!
program test_explicit_shape
use explicit_shape_mod
implicit none
integer, parameter :: m = 2, n = m**2
integer :: v(n) = [10,20,30,40], imat(m,m)
imat = reshape(v,[2,2])
call print_vec(n,v)    ! pass v(1:4)
call print_vec(n,v(1)) ! pass v(1:4) -- equivalent
call print_vec(2,v)    ! pass v(1:2)
call print_vec(2,v(3)) ! pass v(3:4)
call print_vec(n,imat) ! passed imat as 1D array
call print_vec(2,imat(2,1)) ! passed [imat(2,1),imat(1,2)]
call print_vec(2,v(4)) ! invalid since v(5) does not exist
end program test_explicit_shape
! Intel Fortran output:
!  10 20 30 40
!  10 20 30 40
!  10 20
!  30 40
!  10 20 30 40
!  20 30
!  40 54 -- nonsense, but code is invalid

Tweet 2: Sequence association

With “sequence association” for explicit-shape and assumed-size arrays, you
can pass a single array element to an array dummy argument, which amounts
to passing a pointer to a location in the array, as shown in the previous code.

Tweet 3: Assumed-size arrays

An assumed-size array argument has a * as the upper bound of the last
dimension, meaning that it is unknown. Other dimension bounds must be
provided. Such arguments should be avoided in new code. Sequence
association applies as with explicit-shape arrays

Code:

subroutine print_vec(n,v)
implicit none
integer n
integer v(*)
integer i
print "(*(1x,i0))",(v(i),i=1,n)
! print "(*(1x,i0))",v -- invalid since array size unknown
end subroutine print_vec
!
subroutine print_mat_3_rows(ncol,v)
implicit none
integer ncol
integer v(3,*)
! whatever is passed as v is coerced to a matrix with 3 rows
integer i,j
do i=1,3
   print "(*(i3))",(v(i,j),j=1,ncol)   
end do
end subroutine print_mat_3_rows
!
module print_mat_mod
implicit none
contains
subroutine print_mat(mat)
integer, intent(in) :: mat(:,:)
integer             :: i
do i=1,size(mat,1)
   print "(*(i3))", mat(i,:)
end do
end subroutine print_mat
end module print_mat_mod
!
program test_assumed_size
use print_mat_mod
implicit none
integer, parameter :: m = 2, n = m**2
integer :: i, v(n) = [10,20,30,40], mat(m,m+1)
! set mat to v, padded by column [0,0]
mat = reshape(v,[m,m+1],pad=[0,0])
call print_vec(n,v)    ! 10 20 30 40
call print_vec(n,v(1)) ! 10 20 30 40
call print_vec(2,v(3)) ! 30 40
call print_vec(size(mat),mat)! 10 20 30 40 0 0
call print_vec(n,mat)  ! 10 20 30 40
call print_vec(3,mat(2,1)) ! 20 30 40
call print_mat(mat) ! output:
!  10 30  0
!  20 40  0
call print_mat_3_rows(2,mat) ! output:
! mat has shape [2,3] but is coerced to [3,2]
! 10 40
! 20  0
! 30  0
call print_mat_3_rows(2,[(i,i=1,6)]) ! output:
! 6-element 1-D array coerced to shape [3,2]
!   1  4
!   2  5
!   3  6
end program test_assumed_size
2 Likes

How about the very dated but not entirely forgotten practice of passing an array and declaring the associated dummy argument as array(1)? This was before the advent of the asterisk.

2 Likes

That was never standard Fortran, but it was done, as the post by Goerz discusses. Covering it occurred to me, but one aim of FortranTip is to promote the language, and I worry that if I post too much about the dark corners people will flee. But yes it probably should be mentioned eventually, along with deleted FORTRAN features.

3 Likes

My 2¢: the nomenclature had changed with the advent of modern Fortran (90/95). In F77 dummy array arguments with the shape defined by variable expressions (variables had to be either passed as dummy args or globally accessible through common blocks) were called adjustable arrays.
In modern Fortran they are treated as explicit shape arrays but that is a broader category, as in

real function f(arr,m)
  integer, intent(in) :: m
  real, intent(inout) :: arr(m)
  real                :: temp(20)

both arr and temp are explicit shape arrays.
Your tweet narrows the meaning of this category just to old adjustables

2 Likes

Sequence association has some restrictions. I discuss this in detail in Doctor Fortran in “I’ve Come Here For An Argument” - Doctor Fortran (stevelionel.com) In particular, you don’t get sequence association if the actual argument is assumed-shape or is an array with a “vector subscript”. This gets people into trouble when they are “updating” old code.

1 Like

I tried to write a program that violates the constraint you mention, and gfortran rejects it but ifort, flang, and g95 do not:

subroutine print_vec(n,v)
implicit none
integer n
integer v(*)
integer i
print "(100(1x,i0))",(v(i),i=1,n)
end subroutine print_vec
!
program test_assumed_size
implicit none
integer, parameter :: n = 4
integer :: v(n) = [10,20,30,40]
call call_print_vec(v)
contains
!
subroutine call_print_vec(w)
integer, intent(in) :: w(:)
call print_vec(size(w),w(1))
end subroutine call_print_vec
!
end program test_assumed_size
c:\fortran\tweets\unposted>gfortran sequence_assoc.f90
sequence_assoc.f90:18:23:

   18 | call print_vec(size(w),w(1))
      |                       1
Error: Element of assumed-shape or pointer array passed to array dummy argument 'v' at (1)
c:\fortran\tweets\unposted>ifort -stand:f18 sequence_assoc.f90 && sequence_assoc.exe
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.16.27027.1
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:sequence_assoc.exe 
-subsystem:console 
sequence_assoc.obj 
 10 20 30 40

I like the new color syntax highlighting :slight_smile:

You have implicit interface for print_vec, so unless the compiler does additional checking it may not catch this.

D:\Projects>ifort /warn:interface t.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

t.f90(18): error #8284: If the actual argument is scalar, the dummy argument shall be scalar unless the actual argument is of type character or is an element of an array that is not assumed shape, pointer, or polymorphic.   [V]
call print_vec(size(w),w(1))
-----^
compilation aborted for t.f90 (code 1)
1 Like
D:\Projects>nagfor -c t.f90
NAG Fortran Compiler Release 7.0(Yurakucho) Build 7048
Error: t.f90: Argument V (no. 2) in reference to PRINT_VEC from CALL_PRINT_VEC is not an array
[NAG Fortran Compiler error termination, 1 error]
1 Like

But the restriction, as described in the cited article, applies to a scalar being actual argument and array dummy, right? Apparently if the actual argument is an assumed-shape or vector-subscripted array, it works fine. I guess the compiler make a contiguous copy of the argument? The following snippet compiles and executes fine and with expected results, even if print_vec is in its own, separately compiled file.

subroutine print_vec(n,v)
  implicit none
  integer n
  integer v(*)
  integer i
  print "(100(1x,i0))",(v(i),i=1,n)
end subroutine print_vec

program test_assumed_size
  implicit none
  integer, parameter :: n = 4
  integer :: v(n) = [10,20,30,40]
  call call_print_vec(v([1,3]))
contains
  !
  subroutine call_print_vec(w)
    integer, intent(in) :: w(:)
    integer :: ivec(5) = [1,2,3,4,5]
    call print_vec(size(w),w)        !  10 30
    call print_vec(3,ivec([1,3,5]))  !  1 3 5 
  end subroutine call_print_vec

end program test_assumed_size

No. A scalar variable isn’t allowed to be passed to an array, period.

You’ll also get this error (as error #8299) if you are passing a scalar that isn’t an array element, such as a constant 1 or a scalar variable, to an array dummy argument. In some cases you can use an array constructor to turn the scalar into an array, such as [1], but you will lose sequence association benefits.

The article refers to an array element, for example, A(1), passed to an explicit shape or assumed-size array. This is allowed, and gets you sequence association, as long as the array isn’t assumed-shape or a pointer.

OK, although an array element is a scalar, isn’t it? I agree fully that the very idea of sequence association is based on “contiguous” objects, typically (in old days especiually), arrays. So passing an array element resulted in giving the point in the actual array for the association.

Still, could you comment on the code snippet I included? Or, maybe, you meant the element of an assumed-shape or vector-subscript array that is restricted to be passed, not the array.

Yes, that’s what I meant and think that’s what I wrote. Yes, an array element is a scalar, but there is a “carve out” for that case in the language, assuming the other requirements are met.

No mention of array element here, that’s why I got confused. Now it is clear in that part, thank you @sblionel

Still I would be happy to hear comments on passing non-contiguous arrays as actual args to a procedure using sequence association. As I wrote above, it seems that this works. Does the Standard guarantee that (e.g. requiring a copy being made) or it just happens which some specific implementation.
Interestingly, an attempt to change values in v array in print_vec subroutine is quietly ignored for ivec. Changing the intent of w dummy in call_print_vec to inout results in error
Array-section actual argument with vector subscripts at (1) is incompatible with INTENT(OUT), INTENT(INOUT)…
So it seems that one can pass vector-subscript arrays only to INTENT(IN) dummy args. That I was not aware of.