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