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