A strange warning raised by `gfortran -Wconversion-extra`

gfortran -Wconversion-extra raises a strange warning when I am testing a function that manipulates strings. It seems to be caused by the len instrinsic function, though I am not sure.

Here is a minimal working example.

! teststr.f90

!!!!!!! A module that defines COPY !!!!!!!!!!!!!!!!!!!!!!!!
module string_mod

implicit none
private
public :: copy

contains

pure function copy(x) result(y)
! A function that does nothing but copying X to Y.

implicit none
character(len=*), intent(in) :: x
character(len=len(x)) :: y
! The following line will not cause the warning.
!!character(len=10) :: y

y = x
end function copy

end module string_mod
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

!!!!!!! The main program !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program teststr
! A simple test of COPY.
use, non_intrinsic :: string_mod, only : copy
implicit none

write (*, *) copy('a')//''

! The following line will not cause the warning.
!!write (*, *) copy('a')
end program teststr
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

Name this snippet as teststr.f90. Then compile it with gfortran -Wconversion-extra. Here is what happened on my computer with GNU Fortran (Ubuntu 9.3.0-17ubuntu1~20.04) 9.3.0.

$ gfortran -Wconversion-extra teststr.f90
teststr.f90:28:21:

   28 | use, non_intrinsic :: string_mod, only : copy
      |                     1
Warning: Conversion from INTEGER(4) to INTEGER(8) at (1) [-Wconversion-extra]

Note that a conversion warning is associated with the use statement of the string_mod module, which seems strange to me.

In addition, I observed the following.

  1. The warning will disappear if we replace
character(len=len(x)) :: y

with

character(len=10) :: y

in the function copy.

  1. The warning will disappear if we replace
write (*, *) copy('a')//''

with

write (*, *) copy('a')

in the program teststr.

Question:

  1. What is the reason for this warning?
  2. How to get rid of the warning except for the two above-mentioned possibilities?

Thanks for your attention.

1 Like

Looks funny to me. Below is what I get for the parse tree of the copy function declaration, obtained with -fdump-tree-original. You can see a few places where integer(kind=8) shows up. I don’t know the syntax of this intermediate representation that well, but my guess is that gfortran is using integer(8) to represent some metadata related to the function result y. I can only speculate why that might trigger a conversion warning when using copy in a concatenation result with a character literal.

As further evidence for this, I found that copy('a')//copy('b') does not trigger the conversion warning, nor does trim(copy('a'))//''. I wonder if this is some peculiarity of how gfortran handles dummy arguments with assumed lengths that are not known until runtime.

copy (character(kind=1)[1:..__result] & __result, integer(kind=8) .__result, character(kind=1)[1:_x] & restrict x, integer(kind=8) _x)
{
  integer(kind=8) ..__result;
  bitsizetype D.3866;
  sizetype D.3867;
  bitsizetype D.3868;
  sizetype D.3869;

  D.3868 = (bitsizetype) (sizetype) NON_LVALUE_EXPR <_x> * 8;
  D.3869 = (sizetype) NON_LVALUE_EXPR <_x>;
  ..__result = MAX_EXPR <(integer(kind=8)) (integer(kind=4)) _x, 0>;
  D.3866 = (bitsizetype) (sizetype) NON_LVALUE_EXPR <..__result> * 8;
  D.3867 = (sizetype) NON_LVALUE_EXPR <..__result>;
  {
    integer(kind=8) D.3864;
    integer(kind=8) D.3865;

    D.3864 = _x;
    D.3865 = ..__result;
    if (D.3865 > 0)
      {
        if (NON_LVALUE_EXPR <D.3864> < NON_LVALUE_EXPR <D.3865>)
          {
            __builtin_memmove ((void *) __result, (void *) x, (unsigned long long) NON_LVALUE_EXPR <D.3864>);
            __builtin_memset ((void *) __result + (sizetype) NON_LVALUE_EXPR <D.3864>, 32, (unsigned long long) (NON_LVALUE_EXPR <D.3865> - NON_LVALUE_EXPR <D.3864>));
          }
        else
          {
            __builtin_memmove ((void *) __result, (void *) x, (unsigned long long) NON_LVALUE_EXPR <D.3865>);
          }
      }
  }
}
2 Likes

Thank you, @nshaffer , for the effort!

It sounds that it is the compiler itself (rather than the Fortran code) who makes some conversion internally when compiling the code, and then this warning is triggered. If that is the case, then I guess the warning should not be emitted. Metaphorically, a policeman finds a gun in a car and files a report, but the report is unnecessary if it is his gun in his car and he himself puts the gun there consciously, even if he is told to be extraordinarily vigilant about suspicious guns (-Wconversion-exra). Do I get it correctly?

Thanks!