Mpif90 gfortran strange warning for mpi subroutines: 'Rank mismatch between actual argument...'

Dear all,

I have a strange Gfortran strange warning for my mpi subroutines, eg, a simple example of my module is,

  module mympi
  use mpi
  implicit none
  integer, private, parameter :: i4=selected_int_kind(9)
  integer, private, parameter :: i8=selected_int_kind(15)
  integer, private, parameter :: r8=selected_real_kind(15,9) 
  contains
   subroutine recvc1(c,idfrom,itag)
   integer :: mpi_comm_world,ierror
   integer :: mpi_double_complex,idfrom,itag,STATUS(MPI_STATUS_SIZE)  
   complex (kind=r8) :: c
   call mpi_recv(c,1,mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
   return
   end subroutine recvc1
   subroutine recvc1d(c,idfrom,itag)
   integer :: mpi_comm_world,ierror
   integer :: mpi_double_complex,idfrom,itag,STATUS(MPI_STATUS_SIZE)  
   complex(kind=r8) :: c(:)
   call mpi_recv(c,size(c),mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
   return
   end subroutine recvc1d   
  end module mympi

However, once I compile it using the mpif90 gfortran,

mpif90 -c mympi.f90

it gives warning below,

mympi.f90:13:17:

   13 |    call mpi_recv(c,1,mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
      |                 1
......
   20 |    call mpi_recv(c,size(c),mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
      |                 2
Warning: Rank mismatch between actual argument at (1) and actual argument at (2) (rank-1 and scalar)

However I am not able to identify what caused the warning.
Does anyone know what may caused the warning?
Thank you very much in advance!

PS.
In fact, if I include only one of the subroutine recvc1 or recvc1d in the module, it compile with no warning. So I am a little confused. Intel Fortran never give me any warning.
The complete version of my mpi module is here,

gfortran warns you because you call the same subroutine one with a scalar and once with a 1D array.

This means that your MPI library does not define an interface for MPI_Recv to overload it. You could see whether using mpi_f08 instead of mpi solves the issue.

1 Like

Thank you very much @MarDie !
Oh, now I see the problem! Thank you very much indeed! :+1: :100:
Yeah, uhm, I always think that by using use mpi or include 'mpif.h', all the internal mpi_xxx subroutines should have interface already. OK, I will check with mpi_f08. Cool!
By the way, do you have perhaps some suggestions on my mpi module here,

Thanks again :wink:

Oh, @MarDie, hmmm, however, do you know why if I simply have one such subroutine then the module does not have warning anymore? Like,
either

  module mympi
  use mpi
  implicit none
  integer, private, parameter :: i4=selected_int_kind(9)
  integer, private, parameter :: i8=selected_int_kind(15)
  integer, private, parameter :: r8=selected_real_kind(15,9) 
  contains
   subroutine recvc1(c,idfrom,itag)
   integer :: mpi_comm_world,ierror
   integer :: mpi_double_complex,idfrom,itag,STATUS(MPI_STATUS_SIZE)  
   complex (kind=r8) :: c
   call mpi_recv(c,1,mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
   return
   end subroutine recvc1
  end module mympi

Or

  module mympi
  use mpi
  implicit none
  integer, private, parameter :: i4=selected_int_kind(9)
  integer, private, parameter :: i8=selected_int_kind(15)
  integer, private, parameter :: r8=selected_real_kind(15,9) 
  contains
   subroutine recvc1d(c,idfrom,itag)
   integer :: mpi_comm_world,ierror
   integer :: mpi_double_complex,idfrom,itag,STATUS(MPI_STATUS_SIZE)  
   complex(kind=r8) :: c(:)
   call mpi_recv(c,size(c),mpi_double_complex,idfrom,itag,mpi_comm_world,status,ierror)
   return
   end subroutine recvc1d 

Just can compile without warning?
I mean if mpi_recv missing one of the interface then one of the module above should give me a warning right? But both can compile without warning. The warning only happens when I put these two subroutine in one module.
The internal mpi_xxxxx subroutines such as mpi_recv, eg,

in principle they seems should have many interface defined already, is it? So that they can be used to transfer all types of data right?

You are assuming that “use mpi” actually provides fortran interfaces for the subprograms you call. Try an “only” clause to check that. I think you will find that mpi module does not, but mpi_f08 module does.

1 Like

I think what is happening is that the compiler is generating interfaces to the called subrouitine internally, and using that interface to compare multiple calls to the subroutine. So whichever call it sees first effectively defines the interface, and then any subsequent calls are compared to that. In your case, one call has a scalar argument and the other call has an array argument. If only one call exists, then no problem, it is only when multiple calls are there that the inconsistency is detected. One solution is to change the scalar argument to an array with one element, c(1). Then the interface that is generated internally will be consistent. If the dummy argument is an array, which it almost certainly is, then that will also bring your code into conformance with the language. Your call with the scalar argument would also have been detected as an error if you had an explicit interface to that subroutine, either from an interface block or from a module procedure.

1 Like