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,