1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Raccumulate_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
7    target_disp, target_count, target_datatype, op, win, request, ierror)
8    use, intrinsic :: iso_c_binding, only : c_int
9    use :: mpi_f08, only : MPI_Datatype, MPI_Op, MPI_Win, MPI_Request
10    use :: mpi_f08_compile_constants, only : MPI_ADDRESS_KIND
11    use :: mpi_c_interface, only : c_Datatype, c_Op, c_Win, c_Request
12    use :: mpi_c_interface, only : MPIR_Raccumulate_cdesc
13
14    implicit none
15
16    type(*), dimension(..), intent(in), asynchronous :: origin_addr
17    integer, intent(in) :: origin_count
18    integer, intent(in) :: target_rank
19    integer, intent(in) :: target_count
20    type(MPI_Datatype), intent(in) :: origin_datatype
21    type(MPI_Datatype), intent(in) :: target_datatype
22    integer(kind=MPI_ADDRESS_KIND), intent(in) :: target_disp
23    type(MPI_Op), intent(in) :: op
24    type(MPI_Win), intent(in) :: win
25    type(MPI_Request), intent(out) :: request
26    integer, optional, intent(out) :: ierror
27
28    integer :: origin_count_c
29    integer :: target_rank_c
30    integer :: target_count_c
31    integer(c_Datatype) :: origin_datatype_c
32    integer(c_Datatype) :: target_datatype_c
33    integer(c_Op) :: op_c
34    integer(c_Win) :: win_c
35    integer(c_Request) :: request_c
36    integer(c_int) :: ierror_c
37
38    if (c_int == kind(0)) then
39        ierror_c = MPIR_Raccumulate_cdesc(origin_addr, origin_count, origin_datatype%MPI_VAL, target_rank, &
40            target_disp, target_count, target_datatype%MPI_VAL, op%MPI_VAL, win%MPI_VAL, request%MPI_VAL)
41    else
42        origin_count_c = origin_count
43        origin_datatype_c = origin_datatype%MPI_VAL
44        target_rank_c = target_rank
45        target_count_c = target_count
46        target_datatype_c = target_datatype%MPI_VAL
47        op_c = op%MPI_VAL
48        win_c = win%MPI_VAL
49        ierror_c = MPIR_Raccumulate_cdesc(origin_addr, origin_count_c, origin_datatype_c, target_rank_c, &
50            target_disp, target_count_c, target_datatype_c, op_c, win_c, request_c)
51        request%MPI_VAL = request_c
52    end if
53
54    if (present(ierror)) ierror = ierror_c
55
56end subroutine PMPIR_Raccumulate_f08ts
57