@@ -128,6 +128,10 @@ module mpi
128128 module procedure MPI_Recv_StatusIgnore_proc
129129 end interface
130130
131+ interface MPI_Sendrecv
132+ module procedure MPI_Sendrecv_proc
133+ end interface
134+
131135 interface MPI_Waitall
132136 module procedure MPI_Waitall_proc
133137 end interface
@@ -668,7 +672,49 @@ subroutine MPI_Irecv_proc(buf, count, datatype, source, tag, comm, request, ierr
668672 print * , " MPI_Irecv failed with error code: " , local_ierr
669673 end if
670674 end if
671- end subroutine
675+ end subroutine MPI_Irecv_proc
676+
677+ subroutine MPI_Sendrecv_proc (sendbuf , sendcount , sendtype , dest , sendtag , &
678+ recvbuf , recvcount , recvtype , source , recvtag , comm , status , ierror )
679+ use iso_c_binding, only: c_int, c_ptr, c_loc
680+ use mpi_c_bindings, only: c_mpi_sendrecv, c_mpi_status_c2f
681+ real (8 ), dimension (:,:), target , intent (in ) :: sendbuf
682+ integer , intent (in ) :: sendcount, dest, sendtag
683+ real (8 ), dimension (:,:), target , intent (out ) :: recvbuf
684+ integer , intent (in ) :: recvcount, source, recvtag
685+ integer , intent (in ) :: comm
686+ integer , intent (in ) :: sendtype, recvtype
687+ integer (kind= MPI_HANDLE_KIND) :: c_comm
688+ integer , intent (out ) :: status (MPI_STATUS_SIZE)
689+ integer , optional , intent (out ) :: ierror
690+ integer (c_int) :: local_ierr, status_ierr
691+ integer (kind= MPI_HANDLE_KIND) :: c_sendtype, c_recvtype
692+ type (c_ptr) :: sendbuf_ptr, recvbuf_ptr, c_status
693+ integer (c_int), dimension (MPI_STATUS_SIZE), target :: tmp_status
694+
695+ c_comm = handle_mpi_comm_f2c(comm)
696+
697+ c_sendtype = handle_mpi_datatype_f2c(sendtype)
698+ c_recvtype = handle_mpi_datatype_f2c(recvtype)
699+ sendbuf_ptr = c_loc(sendbuf)
700+ recvbuf_ptr = c_loc(recvbuf)
701+ c_status = c_loc(tmp_status)
702+
703+ local_ierr = c_mpi_sendrecv(sendbuf_ptr, sendcount, c_sendtype, dest, sendtag, &
704+ recvbuf_ptr, recvcount, c_recvtype, source, recvtag, &
705+ c_comm, c_status)
706+
707+ if (local_ierr == MPI_SUCCESS) then
708+ ! status_ierr = c_mpi_status_c2f(c_status, status)
709+ end if
710+
711+ if (local_ierr /= MPI_SUCCESS) then
712+ print * , " MPI_Sendrecv failed with error code: " , local_ierr
713+ if (present (ierror)) then
714+ ierror = local_ierr
715+ end if
716+ end if
717+ end subroutine MPI_Sendrecv_proc
672718
673719 subroutine MPI_Allreduce_scalar (sendbuf , recvbuf , count , datatype , op , comm , ierror )
674720 use iso_c_binding, only: c_int, c_ptr, c_loc
0 commit comments