Assumed-rank arrays

It’s nice that in Fortran 2018, a function can have an assumed-rank array argument that can be a scalar or an array of any rank, so that the program

module m_mod
implicit none
contains
function mean(x) result(y)
real, intent(in) :: x(..) ! assumed-rank array
real             :: y
select rank(x)
   rank(0) ; y = x
   rank(1) ; y = sum(x)/size(x)
   rank(2) ; y = sum(x)/size(x)
   rank default ; y = -huge(x) ! signal that rank not handled
end select
end function mean
end module m_mod

program main
use m_mod, only: mean
implicit none
real :: x,xvec(3),xmat(3,3),xtens(3,3,3)
x = 5.0
xvec = 5.0
xmat = 5.0
xtens = 5.0
print*,mean(x),mean(xvec),mean(xmat),mean(xtens)
end program main

gives output

5.00000000 5.00000000 5.00000000 -3.40282347E+38

To handle the case above where the same code is used for different ranks, the alternatives to manual copying would be to use INCLUDE or have a preprocessor generate the code? Analogous with SELECT CASE, it would be ideal if one could write

rank(1:7); y = sum(x)/size(x)

but using the assumed-rank feature is still more concise than having to define separate mean_scalar, mean_vector, mean_matrix functions as MODULE PROCEDUREs for the INTERFACE mean, as one would do in Fortran 95. Is there a way to have the program fail at compile time when an array of rank 3 or higher is passed to mean?

1 Like

My personal take has been there is no good way that is supported by the standard.

Note the assumed-rank facility, as it stands in Fortran 2018, has considerable limitations if it is pursued to achieve compact and convenient authoring of generic programs toward rank-agnostic procedures in Fortran-only codes.

When there are functions with the companion C processor that can accept parameters of any rank, the assumed-rank facility helps and that’s the bulk of the use case of this feature.

If you want the program to fail for rank > 3, just have the rank default branch execute a STOP statement.

For this particular case, and easier change to the standard than rank(1:7) would be to allow the SUM intrinsic to accept an assumed-rank argument. SIZE already allows this, so all of your cases would reduce to y = sum(x)/size(x).

Maybe extend the syntax of assumed-rank arrays declarations to allow the minimum and maximum rank of an array to be specified:

real, intent(in) :: x(..7) ! assumed-rank array of rank up to 7, or a scalar
real, intent(in) :: x(1..7) ! assumed-rank array of rank up to 7, excluding scalars
3 Likes

Which compiler did you use in the original post?

I was trying to compile the function:

  pure function flatten(x) result(y)
    real, intent(in) :: x(..)
    real :: y(size(x))
    y = reshape(x,shape=[size(x)])
  end function

but with gfortran v 10.1.0 on Ubuntu it fails with Error: Assumed-rank argument at (1) is only permitted as actual argument to intrinsic inquiry functions.

1 Like

I used, on Windows, GNU Fortran (GCC) 11.0.0 20200927 from equation.com and Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.1 Build 20201112_000000 . Neither compiler accepts the code above, but gfortran does compile

  pure function flatten(x) result(y)
    real, intent(in) :: x(..)
    real :: y(size(x))
  select rank(x)
    rank(1) ; y = reshape(x,shape=[size(x)])
    rank(2) ; y = reshape(x,shape=[size(x)])
  end select
  end function

while Intel says

flatten.f90(5): error #7617: This host associated object appears in a 'defining' context in a PURE procedure or in an internal procedure contained in a PURE procedure.   [Y]
    rank(1) ; y = reshape(x,shape=[size(x)])
--------------^
flatten.f90(6): error #7617: This host associated object appears in a 'defining' context in a PURE procedure or in an internal procedure contained in a PURE procedure.   [Y]
    rank(2) ; y = reshape(x,shape=[size(x)])
--------------^
compilation aborted for flatten.f90 (code 1)

but does compile it if the PURE designation is removed. The function does not modify x, so I don’t see why it cannot be PURE.

It’s a bug in Intel Fortran.

In the meantime, a workaround can be a subroutine option and which may be advantageous in certain circumstances:

module m
contains
   pure subroutine flatten(x, y)
       real, intent(in) :: x(..)
       real, intent(inout) :: y(size(x))
       select rank(x)
         rank(1) ; y = reshape(x,shape=[size(x)])
         rank(2) ; y = reshape(x,shape=[size(x)])
       end select
   end subroutine
   pure subroutine flatten2(x, y)
       real, intent(in) :: x(..)
       real, intent(out), allocatable :: y(:)
       select rank(x)
         rank(1) ; y = reshape(x+1.0,shape=[size(x)])
         rank(2) ; y = reshape(x+1.0,shape=[size(x)])
       end select
     end subroutine
end module
   use m
   real :: a(2,3)
   real, allocatable :: b(:)
   a = 1.0
   call flatten2(a, b)
   print *, "size(b): ", size(b), "; expected is ", size(a)
   print *, "b(2*3): ", b(2*3), "; expected is ", a(2,3)+1.0
   call flatten(a, b)
   print *, "b(2*3): ", b(2*3), "; expected in ", a(2,3)
 end

C:\temp>ifort /standard-semantics r.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

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

-out:r.exe
-subsystem:console
r.obj

C:\temp>r.exe
size(b): 6 ; expected in 6
b(23): 2.000000 ; expected is 2.000000
b(2
3): 1.000000 ; expected is 1.000000

C:\temp>

Or, a function result with an ALLOCATABLE attribute:

   pure function flatten(x) result(y)
      real, intent(in) :: x(..)
      real, allocatable :: y(:)
..
``