Select kind of assumed rank array

Dear all,

I was wondering if the following program is conforming to the latest standard? It compiles with nvfortran and produces the results I aimed at getting, but not with ifort or gfortran.

Thank you!

program test
  implicit none
  integer, parameter :: n = 150
  real, allocatable :: p1d(:),p(:,:,:)
  integer :: i,j,k
  allocate(p1d(n))
  allocate(p(n,n,n))
  call print_size(p)
  call print_size(p1d)
contains 
  subroutine print_size(var)
  class(*), intent(in) :: var(..)
  select type(var)
  type is (real)
    print*, 'Size is:', size(var)
  end select
  end subroutine
end
2 Likes

No, the current standard does not allow a reference to an assumed-rank dummy object in a select type construct.

The practical workaround to the approach, which I do not recommend, is a cascaded select rank with enclosed select type in order to achieve what is presumably the use of unlimited polymorphism as a substitute for generics.

For the case shown in the original post, select rank will suffice where in each rank statement, the associate-name is of that rank i.e., it’s not assumed rank. But again it is rather silly; generic interfaces generally work better with current processors and can provide more readable code albeit with all the code duplication.

You can try this:

   integer :: x, y(1), z(2,3)
   call sub( x )
   call sub( y )
   call sub( z )
contains
   subroutine sub( a )
      class(*), intent(in) :: a(..)
      select rank ( v => a )
         rank ( 0 )
            print *, "arg is rank-0"
         rank ( 1 )
            print *, "arg is rank-1 of size ", size(v)
         rank ( 2 )
            print *, "arg is rank-2 of size ", size(v)
         rank default
            print *, "arg is of rank other than 0 thru' 2"
      end select
   end subroutine
end 
2 Likes

Thank you!

Funny… The non-conforming example compiled with nvfortran but not with gfortran and ifort. This conforming workaround one compiles with gfortran and ifort but not with nvfortran (because it does not support yet select rank).

The conforming example:

 program test
   implicit none
   integer, parameter :: n = 150
   real, allocatable :: p1d(:),p(:,:,:)
   integer :: i,j,k
   allocate(p1d(n))
   allocate(p(n,n,n))
   call print_size(p)
   call print_size(p1d)
 contains
   subroutine print_size(var)
   class(*), intent(in) :: var(..)
   select rank(var)
   rank (1)
     select type(var)
     type is (real)
       print*,'Size is:',size(var)
     end select
   rank (2)
     select type(var)
     type is (real)
       print*,'Size is:',size(var)
     end select
   rank (3)
     select type(var)
     type is (real)
       print*,'Size is:',size(var)
     end select
   end select
   end subroutine
 end
1 Like

I’ve never used assumed-rank arrays up to now, but isn’t it possible (in principle) to get the number of the total array elements via size(arr) because it is independent of the rank? Or, is the restriction related to the case where the dummy argument is possibly a scalar (i.e. not an array)?

Thanks!

I think my example is not very illustrative. In addition to getting the array size, I wanted to do some other operations which depend on the type (actually, on the kind), of the argument.

Ah… sorry, I was not writing about the “code design” (of your actual code), but simply interested in why the Fortran standard forbids us to use size(arr) on an assumed-rank dummy array (when there is no dim keyword).

I imagined that the assumed-rank array is implemented in a way similar to the usual array (with internal metadata for ranks, bounds, strides, etc), so I thought size(arr) can be used because the total element size should be independent of “how the user accesses (views) the actual data”.

Anyway, just a minor question for someone interested… :beach_umbrella:

1 Like

Ah! Sorry, I misread your comment. I have the same curiosity… I guess there has to be some strong reason for this not to be allowed, as it would seem like a really neat thing to be able to write…

1 Like

@septc, there is no prohibition in the standard against the use of an assumed-rank object with the SIZE intrinsic. In fact, the SIZE intrinsic description in the standard starting with Fortran 2018 states that the first parameter “shall be assumed-rank or an array.”

Note the prohibition that comes into play with OP’s code in the original post is with the use in a SELECT TYPE construct where OP was intending to include other instructions.

2 Likes

Thank you. Exactly… Do you know the reason why this is not allowed?

Thanks! I see… I completely misunderstood that the error comes from the use of size :face_with_spiral_eyes:

Now I’ve tried this code, which works as I expected (with Gfortran-10).

program test
    implicit none
    real :: x
    real, allocatable :: A(:,:), B(:,:,:)
    allocate( A(2,3), B(4,5,6) )
    call print_size( A )
    call print_size( B )
    call print_size( x )
contains 

subroutine print_size( arr )
    class(*), intent(in) :: arr(..)
    integer :: d
    print *, "rank =",  rank(arr), &
             "size =",  size(arr), &
             "shape =", shape(arr)
    print *, all( shape(arr) == [( size(arr,d), d = 1, rank(arr) )] )
end subroutine
end program

$ gfortran-10 test.f90 && ./a.out
 rank =           2 size =           6 shape =           2           3
 T
 rank =           3 size =         120 shape =           4           5           6
 T
 rank =           0 size =           1 shape =
 T
2 Likes