We encountered a curious problem with procedure pointers and assumed-size arrays. The following code is accepted by Intel Fortran oneAPI but not by gfortran. Question is: is the code conforming or not?
! proc_assumed_size.f90 --
! Check problem with assumed size arrays in procedure pointer
!
module proc_pnt
implicit none
type proc
procedure(), pointer, nopass :: p
end type proc
contains
subroutine callit( p, array )
type(proc), intent(in) :: p
real, dimension(*), intent(in) :: array
!real, dimension(:), intent(in) :: array <-- this is accepted by gfortran
call p%p( array )
end subroutine callit
end module proc_pnt
module simple_proc
implicit none
contains
subroutine mysub( array )
real, dimension(*), intent(in) :: array
write(*,*) array(1)
end subroutine mysub
end module simple_proc
program proc_assumed_size
use proc_pnt
use simple_proc
implicit none
type(proc) :: pp
real :: array(10)
call random_number( array )
pp%p => mysub
call pp%p( array )
end program proc_assumed_size
The error message from gfortran is:
proc_assumed_size.f90:17:14:
17 | call p%p( array )
| 1
Error: The upper bound in the last dimension must appear in the reference to the assumed size array 'array' at (1)
If I change the dummy argument in callit to be an assumed-shape array, both compilers are happy with the code.