1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Put_f08ts(origin_addr, origin_count, origin_datatype, target_rank, &
7    target_disp, target_count, target_datatype, win, ierror)
8    use, intrinsic :: iso_c_binding, only : c_int
9    use :: mpi_f08, only : MPI_Datatype, MPI_Win
10    use :: mpi_f08, only : MPI_ADDRESS_KIND
11    use :: mpi_c_interface, only : c_Datatype, c_Win
12    use :: mpi_c_interface, only : MPIR_Put_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    integer(MPI_ADDRESS_KIND), intent(in) :: target_disp
22    type(MPI_Datatype), intent(in) :: target_datatype
23    type(MPI_Win), intent(in) :: win
24    integer, optional, intent(out) :: ierror
25
26    integer(c_int) :: origin_count_c
27    integer(c_int) :: target_rank_c
28    integer(c_int) :: target_count_c
29    integer(c_Datatype) :: origin_datatype_c
30    integer(MPI_ADDRESS_KIND) :: target_disp_c
31    integer(c_Datatype) :: target_datatype_c
32    integer(c_Win) :: win_c
33    integer(c_int) :: ierror_c
34
35    if (c_int == kind(0)) then
36        ierror_c = MPIR_Put_cdesc(origin_addr, origin_count, origin_datatype%MPI_VAL, target_rank, target_disp, &
37            target_count, target_datatype%MPI_VAL, win%MPI_VAL)
38    else
39        origin_count_c = origin_count
40        origin_datatype_c = origin_datatype%MPI_VAL
41        target_rank_c = target_rank
42        target_disp_c = target_disp
43        target_count_c = target_count
44        target_datatype_c = target_datatype%MPI_VAL
45        win_c = win%MPI_VAL
46        ierror_c = MPIR_Put_cdesc(origin_addr, origin_count_c, origin_datatype_c, target_rank_c, target_disp_c, &
47            target_count_c, target_datatype_c, win_c)
48    end if
49
50    if (present(ierror)) ierror = ierror_c
51
52end subroutine PMPIR_Put_f08ts
53