1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine MPI_Exscan_f08ts(sendbuf, recvbuf, count, datatype, op, comm, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_Datatype, MPI_Op, MPI_Comm
9    use :: mpi_c_interface, only : c_Datatype, c_Op, c_Comm
10    use :: mpi_c_interface, only : MPIR_Exscan_cdesc
11
12    implicit none
13
14    type(*), dimension(..), intent(in) :: sendbuf
15    type(*), dimension(..) :: recvbuf
16    integer, intent(in) :: count
17    type(MPI_Datatype), intent(in) :: datatype
18    type(MPI_Op), intent(in) :: op
19    type(MPI_Comm), intent(in) :: comm
20    integer, optional, intent(out) :: ierror
21
22    integer(c_int) :: count_c
23    integer(c_Datatype) :: datatype_c
24    integer(c_Op) :: op_c
25    integer(c_Comm) :: comm_c
26    integer(c_int) :: ierror_c
27
28    if (c_int == kind(0)) then
29        ierror_c = MPIR_Exscan_cdesc(sendbuf, recvbuf, count, datatype%MPI_VAL, op%MPI_VAL, comm%MPI_VAL)
30    else
31        count_c = count
32        datatype_c = datatype%MPI_VAL
33        op_c = op%MPI_VAL
34        comm_c = comm%MPI_VAL
35        ierror_c = MPIR_Exscan_cdesc(sendbuf, recvbuf, count_c, datatype_c, op_c, comm_c)
36    end if
37
38    if (present(ierror)) ierror = ierror_c
39
40end subroutine MPI_Exscan_f08ts
41