1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Win_post_f08(group, assert, win, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_Group, MPI_Win
9    use :: mpi_c_interface, only : c_Win, c_Group
10    use :: mpi_c_interface, only : MPIR_Win_post_c
11
12    implicit none
13
14    type(MPI_Group), intent(in) :: group
15    integer, intent(in) :: assert
16    type(MPI_Win), intent(in) :: win
17    integer, optional, intent(out) :: ierror
18
19    integer(c_Group) :: group_c
20    integer(c_int) :: assert_c
21    integer(c_Win) :: win_c
22    integer(c_int) :: ierror_c
23
24    if (c_int == kind(0)) then
25        ierror_c = MPIR_Win_post_c(group%MPI_VAL, assert, win%MPI_VAL)
26    else
27        group_c = group%MPI_VAL
28        assert_c = assert
29        win_c = win%MPI_VAL
30        ierror_c = MPIR_Win_post_c(group_c, assert_c, win_c)
31    end if
32
33    if (present(ierror)) ierror = ierror_c
34
35end subroutine PMPIR_Win_post_f08
36