Procedure pointers and assumed-size arrays

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.

1 Like

@arjen, nvfortran doesn’t give an error so I’m guessing its a bug in gfortran. I tried several mods to your code including adding an abstract interface for the procedure pointer but gfortran 13 always returned with your error. My abstract interface mod looks like

   abstract interface
      subroutine pf(array)
        real, intent(in) :: array(*)
      end subroutine pf
    end interface
    type proc
        procedure(pf), pointer, nopass :: p=>NULL()
    end type proc

The NAG compiler accepts it as well. I believe it is standards conforming. It looks like gfortran has the characteristic of an argument to a procedure with an implicit interface backwards. If a procedure does not have an explicit interface it is assumed that an array argument is an assumed size array, not assumed shape. An assumed shape argument would need to know the upper bound but assumed size does not. That’s why gfortran accepts it when you change the interface of callit.

That is what I assumed as well. The code I am working with stems from way back and I recently converted it to use procedure pointers, As most if not all routines are contained in a module, changing callit to use assumed-shape is not a big problem, but it was puzzling.

Thanks everyone for the confirmation.