Interesting output from gfortran when using parameterized derived types

Dear all,

Nice to see how dynamic this discourse and the community have become!

EDIT
Here is a self-contained reproducer of what I describe later:

module m_test
implicit none
type pdt_t(n)
  integer, len :: n
  integer, dimension(n) :: counts
end type pdt_t
contains
subroutine create_pdt(dims,pdt)
  integer, intent(in), dimension(3) :: dims
  type(pdt_t(product(dims(:)))), intent(out), dimension(2) :: pdt
  pdt(1)%counts(:) = 1
end subroutine create_pdt
end module m_test
$ gfortran -c -Wall reproducer.f90                                                                                                                                                                   [1]
reproducer.f90:12:0:

   12 | end subroutine create_pdt
      |
Warning: ‘val.2’ may be used uninitialized in this function [-Wmaybe-uninitialized]
reproducer.f90:12:0:

   12 | end subroutine create_pdt
      |
note: ‘val.2’ was declared here

END EDIT

I have a derived type, declared as follows:

   type alltoallw(n)
     integer, len :: n
     integer           , dimension(n) :: counts
     integer           , dimension(n) :: disps
     type(MPI_DATATYPE), dimension(n) :: types
   end type alltoallw

and in a subroutine I declare an array of derived types like this:

  integer, intent(in), dimension(3) :: dims,n_p,n_s
  type(alltoallw(product(dims))), dimension(2), intent(out) :: transpose_params

Then, as soon as I touch this array of derived types, e.g.:

     transpose_params(1)%counts(:) = 1

and compile with gfortran -g -O0 -Wall -Wextra (version 10.2.0), I get among other things the following strange output:

Warning: ‘val.48’ may be used uninitialized in this function [-Wmaybe-uninitialized]
(...)
note: ‘val.48’ was declared here

where val.48 has not been explicitly declared in the code.

This warning and note disappear if I pass a single integer nrank (instead of product(dims)) as the len parameter. Is the compiler creating a variable because of the way I declare the array of derived types? Do you know what is going on?

Thank you!