1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine MPI_Recv_f08ts(buf, count, datatype, source, tag, comm, status, ierror)
7    use, intrinsic :: iso_c_binding, only : c_loc, c_associated
8    use, intrinsic :: iso_c_binding, only : c_int, c_ptr
9    use :: mpi_f08, only : MPI_Datatype, MPI_Comm, MPI_Status
10    use :: mpi_f08, only : MPI_STATUS_IGNORE, MPIR_C_MPI_STATUS_IGNORE, assignment(=)
11    use :: mpi_c_interface, only : c_Datatype, c_Comm
12    use :: mpi_c_interface, only : c_Status
13    use :: mpi_c_interface, only : MPIR_Recv_cdesc
14
15    implicit none
16
17    type(*), dimension(..) :: buf
18    integer, intent(in) :: count
19    integer, intent(in) :: source
20    integer, intent(in) :: tag
21    type(MPI_Datatype), intent(in) :: datatype
22    type(MPI_Comm), intent(in) :: comm
23    type(MPI_Status), target :: status
24    integer, optional, intent(out) :: ierror
25
26    integer(c_int) :: count_c
27    integer(c_int) :: source_c
28    integer(c_int) :: tag_c
29    integer(c_Datatype) :: datatype_c
30    integer(c_Comm) :: comm_c
31    type(c_Status), target :: status_c
32    integer(c_int) :: ierror_c
33
34    if (c_int == kind(0)) then
35        if (c_associated(c_loc(status), c_loc(MPI_STATUS_IGNORE))) then
36            ierror_c = MPIR_Recv_cdesc(buf, count, datatype%MPI_VAL, source, tag, comm%MPI_VAL, MPIR_C_MPI_STATUS_IGNORE)
37        else
38            ierror_c = MPIR_Recv_cdesc(buf, count, datatype%MPI_VAL, source, tag, comm%MPI_VAL, c_loc(status))
39        end if
40    else
41        count_c = count
42        datatype_c = datatype%MPI_VAL
43        source_c = source
44        tag_c = tag
45        comm_c = comm%MPI_VAL
46        if (c_associated(c_loc(status), c_loc(MPI_STATUS_IGNORE))) then
47            ierror_c = MPIR_Recv_cdesc(buf, count_c, datatype_c, source_c, tag_c, comm_c, MPIR_C_MPI_STATUS_IGNORE)
48        else
49            ierror_c = MPIR_Recv_cdesc(buf, count_c, datatype_c, source_c, tag_c, comm_c, c_loc(status_c))
50            status = status_c
51        end if
52    end if
53
54    if (present(ierror)) ierror = ierror_c
55
56end subroutine MPI_Recv_f08ts
57