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!

Probably not solving your problem, but why do you write

transpose_params(1)%counts(:) = 1

instead of just

transpose_params(1)%counts = 1

I think I read on comp.lang.fortran that writing x(:) = foo can be slower than just x = foo

In general, gfortran -Wall -Wextra produces some false warnings, which I am used to ignoring. (I may be missing some real warnings.) For example, gfortran -Wall -Wextra for

program main
implicit none
integer, parameter :: n = 3
real :: x(n),y(n)
integer :: i
call random_number(x)
do i=1,n
   if (i == 1) then
      y(i) = 0.0
   else
      y(i) = x(i) - x(i-1)
   end if
end do
print*,y
end program main

gives a spurious warning

xwarn.f90:11:22:

    7 | do i=1,n
      |        2              
......
   11 |       y(i) = x(i) - x(i-1)
      |                      1
Warning: Array reference at (1) out of bounds (0 < 1) in loop beginning at (2) [-Wdo-subscript]

for GNU Fortran (GCC) 11.0.0 20200927 from equation.com on Windows.

1 Like

@pcosta ,

Without you providing a reproducer one can try, it’s difficult to gage the issue. However do note the parameterized derived type (PDT) facility from way back in Fortran 2003 is effectively not supported in gfortran yet, particularly the length-type parameter you have attempted. Meaning, the number of bug scenarios far exceed the few cases where the feature works with gfortran.

On the other hand, IFORT compiler is in far better shape with PDTs. It is not without problems.
However if you are not using type-bound procedures, then the chances of success with using PDTs in IFORT are reasonably good. Over the years, I’ve submitted many, many bug reports (I’ve lost count actually) with Intel and a vast majority of the cases have been fixed by Intel.

I suggest you either try IFORT compiler in free Intel oneAPI or use a non-parametrized derived type with gfortran.

1 Like

@kargl, a gfortran developer, has written that he

turn[s] off a few warnings that are too noisy with false-positives:

FFLAGS+= -Wno-maybe-uninitialized -Wno-conversion -Wno-integer-division

I have also noticed spurious gfortran warnings about uninitialized variables.

Thank you! Indeed, I do not get this warning when compiling ifort nor nvfortran. I feel that to be safe I should just avoid using parameterized derived types for now.

I edited the original post with a small reproducer, which I also add here:

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

Thank you!

Probably not solving your problem, but why do you write

transpose_params(1)%counts(:) = 1

instead of just

transpose_params(1)%counts = 1

I think I read on comp.lang.fortran that writing x(:) = foo can be slower than just x = foo

This is a small array that will be initialized once at the beginning of the code. So, for readability, my notation makes it clear that params(1)%counts(:) is an array. It seems strange that there would be a difference in performance between the two… It seems like something easy to optimize.

1 Like

@pcosta,

Separately note the Fortran language standard provides guardrails in terms of type-kind-rank (TKR) compatibility via explicit interfaces but when it comes to length-type parameters, the onus is largely on the programmer(s) to write standard-conforming code.

As such, considerable vulnerability comes into play when the length-type parameter of a dummy argument is a non-constant specification expression in conjunction with INTENT(OUT) and the consequences are often felt harshly at run-time by the caller.

Should you consider PDTs with length-type parameters in such a context, I recommend assumed length and INTENT(INOUT) with an error handling mechanism (say additional dummy argument (s) for a status code (and a status message)):

subroutine create_pdt( dims, pdt, stat, [smsg] )
   integer, intent(in), dimension(:) :: dims
   type(pdt_t(n=*)), intent(inout), dimension(:) :: pdt
   integer, intent(inout) :: stat
   [ character(len=*), intent(inout) :: smsg ]
   ..
   ! set suitable stat value if pdt%n is less than or different from product(dims(:))
2 Likes

Compiles OK for me with other compilers. Note that “warnings” are not “errors” and the code might work anyway. The text of the warning is bogus in this case. Also, variables mentioned that are not visibly part of your program, such as “val.48” are probably names on internally generated temporary variables that the compiler uses. They can sometimes be useful if you can get an dump of the intermediate compiler state, but are generally unhelpful to the normal programmer who is not involved with the compiler internals. But can be helpful to the compiler folks as part of a bug submission. As noted by others, the ifort that is part of Intel’s oneAPI is free to download, install, and use. Might be worth a try.

1 Like

Thank you for the suggestion! I guess that if I pass to the original subroutine an array of derived types exactly as declared, the code should work as expected? (I changed my implementation to avoid a PDR, but I will test your suggestion once my application is working).

Would it be a bad practice to use assumed length together with INTENT(OUT) for this specific case? Because that would be its true intent.

Somewhat off-topic, but what does the “len” do in the “integer, len :: n” construct? Never seen that before.

It specifies that n is a length parameter of the derived type, and thus can be used as such in other declarations for components of the type. You can’t then say real :: x(n) without it.

2 Likes