1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Alltoall_f08ts(sendbuf, sendcount, sendtype, recvbuf, recvcount, recvtype, &
7    comm, ierror)
8    use, intrinsic :: iso_c_binding, only : c_int
9    use :: mpi_f08, only : MPI_Datatype, MPI_Comm
10    use :: mpi_c_interface, only : c_Datatype, c_Comm
11    use :: mpi_c_interface, only : MPIR_Alltoall_cdesc
12
13    implicit none
14
15    type(*), dimension(..), intent(in) :: sendbuf
16    type(*), dimension(..) :: recvbuf
17    integer, intent(in) :: sendcount
18    integer, intent(in) :: recvcount
19    type(MPI_Datatype), intent(in) :: sendtype
20    type(MPI_Datatype), intent(in) :: recvtype
21    type(MPI_Comm), intent(in) :: comm
22    integer, optional, intent(out) :: ierror
23
24    integer(c_int) :: sendcount_c
25    integer(c_int) :: recvcount_c
26    integer(c_Datatype) :: sendtype_c
27    integer(c_Datatype) :: recvtype_c
28    integer(c_Comm) :: comm_c
29    integer(c_int) :: ierror_c
30
31    if (c_int == kind(0)) then
32        ierror_c = MPIR_Alltoall_cdesc(sendbuf, sendcount, sendtype%MPI_VAL, recvbuf, recvcount, recvtype%MPI_VAL, &
33            comm%MPI_VAL)
34    else
35        sendcount_c = sendcount
36        sendtype_c = sendtype%MPI_VAL
37        recvcount_c = recvcount
38        recvtype_c = recvtype%MPI_VAL
39        comm_c = comm%MPI_VAL
40        ierror_c = MPIR_Alltoall_cdesc(sendbuf, sendcount_c, sendtype_c, recvbuf, recvcount_c, recvtype_c, &
41            comm_c)
42    end if
43
44    if (present(ierror)) ierror = ierror_c
45
46end subroutine PMPIR_Alltoall_f08ts
47