1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Ibarrier_f08(comm, request, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_Comm, MPI_Request
9    use :: mpi_c_interface, only : c_Comm, c_Request
10    use :: mpi_c_interface, only : MPIR_Ibarrier_c
11
12    implicit none
13
14    type(MPI_Comm), intent(in) :: comm
15    type(MPI_Request), intent(out) :: request
16    integer, optional, intent(out) :: ierror
17
18    integer(c_Comm) :: comm_c
19    integer(c_Request) :: request_c
20    integer(c_int) :: ierror_c
21
22    if (c_int == kind(0)) then
23        ierror_c = MPIR_Ibarrier_c(comm%MPI_VAL, request%MPI_VAL)
24    else
25        comm_c = comm%MPI_VAL
26        ierror_c = MPIR_Ibarrier_c(comm_c, request_c)
27        request%MPI_VAL = request_c
28    end if
29
30    if (present(ierror)) ierror = ierror_c
31
32end subroutine PMPIR_Ibarrier_f08
33