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