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