@@ -45,6 +45,18 @@ module mpi
4545 module procedure MPI_Comm_size_proc
4646 end interface MPI_Comm_size
4747
48+ interface MPI_Comm_Group
49+ module procedure MPI_Comm_Group_proc
50+ end interface MPI_Comm_Group
51+
52+ interface MPI_Group_free
53+ module procedure MPI_Group_free_proc
54+ end interface MPI_Group_free
55+
56+ interface MPI_Group_size
57+ module procedure MPI_Group_size_proc
58+ end interface MPI_Group_size
59+
4860 interface MPI_Comm_dup
4961 module procedure MPI_Comm_dup_proc
5062 end interface MPI_Comm_dup
@@ -274,6 +286,70 @@ subroutine MPI_Comm_size_proc(comm, size, ierror)
274286 end if
275287 end subroutine
276288
289+ subroutine MPI_Comm_Group_proc (comm , group , ierror )
290+ use mpi_c_bindings, only: c_mpi_comm_group, c_mpi_group_f2c, c_mpi_group_c2f
291+ use iso_c_binding, only: c_int, c_ptr
292+ integer , intent (in ) :: comm
293+ integer , intent (out ) :: group
294+ integer , optional , intent (out ) :: ierror
295+ integer (kind= MPI_HANDLE_KIND) :: c_comm, c_group
296+ integer :: local_ierr
297+
298+ c_comm = handle_mpi_comm_f2c(comm)
299+ c_group = c_mpi_group_f2c(group)
300+ local_ierr = c_mpi_comm_group(c_comm, c_group)
301+ group = c_mpi_group_c2f(c_group)
302+
303+ if (present (ierror)) then
304+ ierror = local_ierr
305+ else
306+ if (local_ierr /= 0 ) then
307+ print * , " MPI_Comm_Group failed with error code: " , local_ierr
308+ end if
309+ end if
310+ end subroutine MPI_Comm_Group_proc
311+
312+ subroutine MPI_Group_size_proc (group , size , ierror )
313+ use mpi_c_bindings, only: c_mpi_group_size, c_mpi_group_f2c
314+ use iso_c_binding, only: c_int, c_ptr
315+ integer , intent (in ) :: group
316+ integer , intent (out ) :: size
317+ integer , optional , intent (out ) :: ierror
318+ integer (kind= MPI_HANDLE_KIND) :: c_group
319+ integer :: local_ierr
320+
321+ c_group = c_mpi_group_f2c(group)
322+ local_ierr = c_mpi_group_size(c_group, size)
323+
324+ if (present (ierror)) then
325+ ierror = local_ierr
326+ else
327+ if (local_ierr /= 0 ) then
328+ print * , " MPI_Group_size failed with error code: " , local_ierr
329+ end if
330+ end if
331+ end subroutine MPI_Group_size_proc
332+
333+ subroutine MPI_Group_free_proc (group , ierror )
334+ use mpi_c_bindings, only: c_mpi_group_free, c_mpi_group_f2c
335+ use iso_c_binding, only: c_int, c_ptr
336+ integer , intent (in ) :: group
337+ integer , optional , intent (out ) :: ierror
338+ integer (kind= MPI_HANDLE_KIND) :: c_group
339+ integer :: local_ierr
340+
341+ c_group = c_mpi_group_f2c(group)
342+ local_ierr = c_mpi_group_free(c_group)
343+
344+ if (present (ierror)) then
345+ ierror = local_ierr
346+ else
347+ if (local_ierr /= 0 ) then
348+ print * , " MPI_Group_free failed with error code: " , local_ierr
349+ end if
350+ end if
351+ end subroutine MPI_Group_free_proc
352+
277353 subroutine MPI_Comm_dup_proc (comm , newcomm , ierror )
278354 use mpi_c_bindings, only: c_mpi_comm_dup, c_mpi_comm_c2f
279355 integer , intent (in ) :: comm
0 commit comments