Some updates: Here is a regeneration of FortranFanâs example on the Intel Fortran forum (for simplicity, I have included the include-file in the code below):
module kinds_m
   use, intrinsic :: iso_fortran_env, only : I8 => int64
   implicit none
   integer, parameter :: R4 = selected_real_kind( p=6 )
   integer, parameter :: R8 = selected_real_kind( p=12 )
end module
module cpu_m
   use kinds_m, only : I8, R8
   implicit none
contains
   subroutine cpu_t( time )
      !.. Argument list
      real(R8), intent(inout) :: time
      !.. Local variables
      integer(I8) :: tick
      integer(I8) :: rate
      call system_clock (tick, rate)
      time = real(tick, kind=kind(time) ) / real(rate, kind=kind(time) )
      return
   end subroutine cpu_t
end module
module aux_m
   use kinds_m, only : R4, R8
   use cpu_m, only : cpu_t
   implicit none
   interface calc_aux
      module procedure calc_aux_R4
      module procedure calc_aux_R8
   end interface
   real(R8), protected, public :: calc_time = 0.0_r8
contains
   subroutine calc_aux_R8( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )
      ! Argument list
      real(kind=R8), contiguous, intent(inout) :: x(:)
      real(kind=R8), contiguous, intent(inout) :: y(:)
      real(kind=R8), contiguous, intent(inout) :: z(:)
      real(kind=R8), contiguous, intent(inout) :: xx(:)
      real(kind=R8), contiguous, intent(inout) :: yy(:)
      real(kind=R8), contiguous, intent(inout) :: zz(:)
      real(kind=R8), contiguous, intent(inout) :: xxx(:)
      real(kind=R8), contiguous, intent(inout) :: yyy(:)
      real(kind=R8), contiguous, intent(inout) :: zzz(:)
      real(kind=R8), intent(out)               :: aux
      !include 'calc_aux.f90'
      ! Local variables
      integer :: i
      real(R8) :: t1, t2
      call cpu_t( time=t1 )
      do concurrent ( i = 1:size(x) )
         x(i) = 56*real(i)-1000
         y(i) = 56*real(i)-1000*log(real(i))
         z(i) = 56*real(i)-1000*log(real(i+1))
         xx(i) = 56*real(i)-1000*log(real(i+10))
         yy(i) = 56*real(i)-1000*log(real(i+3))
         zz(i) = 56*real(i)-1000*log(real(i+2))
         xxx(i) = 56*real(i)-1000*log(real(i+5))
         yyy(i) = 56*real(i)-1000*log(real(i+4))
         zzz(i) = 56*real(i)-1000*log(real(i+9))
      end do      
      aux = sum(x) - sum(y) + sum(z) - sum(xx) + sum(yy) - sum(zz) + sum(xxx) - sum(yyy) - sum(zzz)
      call cpu_t( time=t2 )
      calc_time = t2 - t1
      return
   end subroutine
   subroutine calc_aux_R4( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )
      ! Argument list
      real(kind=R4), contiguous, intent(inout) :: x(:)
      real(kind=R4), contiguous, intent(inout) :: y(:)
      real(kind=R4), contiguous, intent(inout) :: z(:)
      real(kind=R4), contiguous, intent(inout) :: xx(:)
      real(kind=R4), contiguous, intent(inout) :: yy(:)
      real(kind=R4), contiguous, intent(inout) :: zz(:)
      real(kind=R4), contiguous, intent(inout) :: xxx(:)
      real(kind=R4), contiguous, intent(inout) :: yyy(:)
      real(kind=R4), contiguous, intent(inout) :: zzz(:)
      real(kind=R4), intent(out)               :: aux
      !include 'calc_aux.f90'
      ! Local variables
      integer :: i
      real(R8) :: t1, t2
      call cpu_t( time=t1 )
      do concurrent ( i = 1:size(x) )
         x(i) = 56*real(i)-1000
         y(i) = 56*real(i)-1000*log(real(i))
         z(i) = 56*real(i)-1000*log(real(i+1))
         xx(i) = 56*real(i)-1000*log(real(i+10))
         yy(i) = 56*real(i)-1000*log(real(i+3))
         zz(i) = 56*real(i)-1000*log(real(i+2))
         xxx(i) = 56*real(i)-1000*log(real(i+5))
         yyy(i) = 56*real(i)-1000*log(real(i+4))
         zzz(i) = 56*real(i)-1000*log(real(i+9))
      end do      
      aux = sum(x) - sum(y) + sum(z) - sum(xx) + sum(yy) - sum(zz) + sum(xxx) - sum(yyy) - sum(zzz)
      call cpu_t( time=t2 )
      calc_time = t2 - t1
      return
   end subroutine
end module aux_m
module pdt_m
   use kinds_m, only : R4, R8
   use cpu_m, only : cpu_t
   use aux_m, only : caux => calc_aux
   implicit none
   type :: pdt_t(K,N)
      integer, kind :: K = R4
      integer, len :: N = 1
      real(kind=K) :: x(N)
      real(kind=K) :: y(N)
      real(kind=K) :: z(N)
      real(kind=K) :: xx(N)
      real(kind=K) :: yy(N)
      real(kind=K) :: zz(N)
      real(kind=K) :: xxx(N)
      real(kind=K) :: yyy(N)
      real(kind=K) :: zzz(N)
   contains
      private
      procedure, pass(this) :: calc_aux_R4
      procedure, pass(this) :: calc_aux_R8
      generic, public :: calc_aux => calc_aux_R4, calc_aux_R8
   end type pdt_t
   real(R8), protected, public :: calc_time = 0.0_r8
contains
   subroutine calc_aux_R4( this, aux )
      ! Argument list
      class(pdt_t(K=R4,N=*)), intent(inout) :: this
      real(kind=R4), intent(out)            :: aux
      ! Local variables
      real(R8) :: t1, t2
      call cpu_t( time=t1 )
      aux = 0.0_R4
      call caux( this%x, this%y, this%z, this%xx, this%yy, this%zz, this%xxx, this%yyy, this%zzz, aux )
      call cpu_t( time=t2 )
      return
   end subroutine
   subroutine calc_aux_R8( this, aux )
      ! Argument list
      class(pdt_t(K=R8,N=*)), intent(inout) :: this
      real(kind=R8), intent(out)            :: aux
      ! Local variables
      real(R8) :: t1, t2
      call cpu_t( time=t1 )
      aux = 0.0_R8
      call caux( this%x, this%y, this%z, this%xx, this%yy, this%zz, this%xxx, this%yyy, this%zzz, aux )
      call cpu_t( time=t2 )
      calc_time = t2 - t1
      return
   end subroutine
end module pdt_m
module dt_m
   use kinds_m, only : R8
   use cpu_m, only : cpu_t
   implicit none
   type :: dt_t
      real(kind=R8) :: x
      real(kind=R8) :: y
      real(kind=R8) :: z
      real(kind=R8) :: xx
      real(kind=R8) :: yy
      real(kind=R8) :: zz
      real(kind=R8) :: xxx
      real(kind=R8) :: yyy
      real(kind=R8) :: zzz
   end type dt_t
   real(R8), protected, public :: calc_time = 0.0_r8
contains
   subroutine calc_aux( this, aux )
      ! Argument list
      type(dt_t), intent(inout)  :: this(:)
      real(kind=R8), intent(out) :: aux
      ! Local variables
      integer :: i
      real(R8) :: t1, t2
      call cpu_t( time=t1 )
      aux = 0.0_R8
      do i = 1, size(this)
         this(i)%x = 56*real(i)-1000
         aux = aux  + this(i)%x
         this(i)%y = 56*real(i)-1000*log(real(i))
         aux = aux  - this(i)%y
         this(i)%z = 56*real(i)-1000*log(real(i+1))
         aux = aux  + this(i)%z
         this(i)%xx = 56*real(i)-1000*log(real(i+10))
         aux = aux  - this(i)%xx
         this(i)%yy = 56*real(i)-1000*log(real(i+3))
         aux = aux  + this(i)%yy
         this(i)%zz = 56*real(i)-1000*log(real(i+2))
         aux = aux  - this(i)%zz
         this(i)%xxx = 56*real(i)-1000*log(real(i+5))
         aux = aux  + this(i)%xxx
         this(i)%yyy = 56*real(i)-1000*log(real(i+4))
         aux = aux  - this(i)%yyy
         this(i)%zzz = 56*real(i)-1000*log(real(i+9))
         aux = aux  - this(i)%zzz
      end do
      call cpu_t( time=t2 )
      calc_time = t2 - t1
      return
   end subroutine
end module dt_m
program p
   !dir$ if defined (rbytes)
   !dir$ else
      !dir$ define rbytes = 64
   !dir$ end if
   !dir$ if (rbytes == 32)
   use kinds_m, only : WP => R4
   !dir$ else
   use kinds_m, only : WP => R8
   !dir$ end if
   implicit none
   integer, parameter :: N = 50000000
   blk1: block
      use pdt_m, only : pdt_t, calc_time
      type(pdt_t(K=WP,N=:)), allocatable :: pdt
      real(WP) :: aux
      allocate( pdt_t(K=WP,N=N) :: pdt )
      call pdt%calc_aux( aux )
      print *, "Block 1: PDT"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
      print *
   end block blk1
   blk2: block
      use dt_m, only : dt_t, calc_aux, calc_time
      type(dt_t), allocatable :: dt(:)
      real(WP) :: aux
      allocate( dt(N) )
      call calc_aux( dt, aux )
      print *, "Block 2: Derived Type"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
      print *
   end block blk2
   blk3: block
      use aux_m, only : calc_aux, calc_time
      real(WP), allocatable :: x(:), y(:), z(:), xx(:), yy(:), zz(:), xxx(:), yyy(:), zzz(:)
      real(WP) :: aux
      allocate( x(N), y(N), z(N), xx(N), yy(N), zz(N), xxx(N), yyy(N), zzz(N) )
      call calc_aux( x, y, z, xx, yy, zz, xxx, yyy, zzz, aux )
      print *, "Block 3: Arrays"
      print *, "aux = ", aux
      print "(g0,g10.3,g0)", "Calc time = ", calc_time, " seconds"
   end block blk3
   stop
end program
The above compiles and runs fine with the Intel Fortran compiler 2021, but it does not compile with Gfortran. Here is the error message:
main.f90:146:15:
146 |       procedure, pass(this) :: calc_aux_R4
    |               1
Error: Argument âthisâ of âcalc_aux_r4â with PASS(this) at (1) must be of the derived-type âpdt_tâ
main.f90:147:15:
147 |       procedure, pass(this) :: calc_aux_R8
|               1
Error: Argument âthisâ of âcalc_aux_r8â with PASS(this) at (1) must be of the derived-type âpdt_tâ
main.f90:287:10:
287 |       use pdt_m, only : pdt_t, calc_time
|          1
Fatal Error: Cannot open module file âpdt_m.modâ for reading at (1): No such file or directory
compilation terminated.
Does anyone know if this is a gfortran bug or it can be somehow fixed to work? Thanks again in advance.