@@ -17,6 +17,7 @@ module mpi
17
17
integer , parameter :: MPI_SUCCESS = 0
18
18
19
19
integer , parameter :: MPI_COMM_WORLD = - 1000
20
+ integer , parameter :: MPI_COMM_NULL = - 1001
20
21
real (8 ), parameter :: MPI_IN_PLACE = - 1002
21
22
integer , parameter :: MPI_SUM = - 2300
22
23
integer , parameter :: MPI_MAX = - 2301
@@ -49,6 +50,10 @@ module mpi
49
50
module procedure MPI_Comm_Group_proc
50
51
end interface MPI_Comm_Group
51
52
53
+ interface MPI_Comm_create
54
+ module procedure MPI_Comm_create_proc
55
+ end interface MPI_Comm_create
56
+
52
57
interface MPI_Group_free
53
58
module procedure MPI_Group_free_proc
54
59
end interface MPI_Group_free
@@ -57,6 +62,11 @@ module mpi
57
62
module procedure MPI_Group_size_proc
58
63
end interface MPI_Group_size
59
64
65
+ interface MPI_Group_range_incl
66
+ module procedure MPI_Group_range_incl_proc
67
+ end interface MPI_Group_range_incl
68
+
69
+
60
70
interface MPI_Comm_dup
61
71
module procedure MPI_Comm_dup_proc
62
72
end interface MPI_Comm_dup
@@ -175,6 +185,16 @@ integer(kind=MPI_HANDLE_KIND) function handle_mpi_comm_f2c(comm_f) result(c_comm
175
185
end if
176
186
end function handle_mpi_comm_f2c
177
187
188
+ integer (kind= MPI_HANDLE_KIND) function handle_mpi_comm_c2f(comm_c) result(f_comm)
189
+ use mpi_c_bindings, only: c_mpi_comm_c2f, c_mpi_comm_null
190
+ integer (kind= mpi_handle_kind), intent (in ) :: comm_c
191
+ if (comm_c == c_mpi_comm_null) then
192
+ f_comm = MPI_COMM_NULL
193
+ else
194
+ f_comm = c_mpi_comm_c2f(comm_c)
195
+ end if
196
+ end function handle_mpi_comm_c2f
197
+
178
198
integer (kind= MPI_HANDLE_KIND) function handle_mpi_info_f2c(info_f) result(c_info)
179
199
use mpi_c_bindings, only: c_mpi_info_f2c, c_mpi_info_null
180
200
integer , intent (in ) :: info_f
@@ -350,6 +370,51 @@ subroutine MPI_Group_free_proc(group, ierror)
350
370
end if
351
371
end subroutine MPI_Group_free_proc
352
372
373
+ subroutine MPI_Group_range_incl_proc (group , n , ranks , newgroup , ierror )
374
+ use mpi_c_bindings, only: c_mpi_group_range_incl, c_mpi_group_f2c, c_mpi_comm_c2f, c_mpi_group_c2f
375
+ use iso_c_binding, only: c_int, c_ptr
376
+ integer , intent (in ) :: group
377
+ integer , intent (in ) :: n
378
+ integer , dimension (:,:), intent (in ) :: ranks
379
+ integer , intent (out ) :: newgroup
380
+ integer , optional , intent (out ) :: ierror
381
+ integer (kind= MPI_HANDLE_KIND) :: c_group, c_newgroup
382
+ integer (c_int) :: local_ierr
383
+
384
+ c_group = c_mpi_group_f2c(group)
385
+ local_ierr = c_mpi_group_range_incl(c_group, n, ranks, c_newgroup)
386
+ newgroup = c_mpi_group_c2f(c_newgroup)
387
+
388
+ if (present (ierror)) then
389
+ ierror = local_ierr
390
+ else if (local_ierr /= MPI_SUCCESS) then
391
+ print * , " MPI_Group_incl failed with error code: " , local_ierr
392
+ end if
393
+ end subroutine MPI_Group_range_incl_proc
394
+
395
+ subroutine MPI_Comm_create_proc (comm , group , newcomm , ierror )
396
+ use mpi_c_bindings, only: c_mpi_comm_create, c_mpi_comm_f2c, c_mpi_comm_c2f, c_mpi_group_f2c, c_mpi_comm_null
397
+ use iso_c_binding, only: c_int, c_ptr
398
+ integer , intent (in ) :: comm
399
+ integer , intent (in ) :: group
400
+ integer , intent (out ) :: newcomm
401
+ integer , optional , intent (out ) :: ierror
402
+ integer (kind= MPI_HANDLE_KIND) :: c_comm, c_group, c_newcomm
403
+ integer (c_int) :: local_ierr
404
+
405
+ c_comm = handle_mpi_comm_f2c(comm)
406
+ c_group = c_mpi_group_f2c(group)
407
+ local_ierr = c_mpi_comm_create(c_comm, c_group, c_newcomm)
408
+
409
+ newcomm = handle_mpi_comm_c2f(c_newcomm)
410
+
411
+ if (present (ierror)) then
412
+ ierror = local_ierr
413
+ else if (local_ierr /= MPI_SUCCESS) then
414
+ print * , " MPI_Comm_create failed with error code: " , local_ierr
415
+ end if
416
+ end subroutine MPI_Comm_create_proc
417
+
353
418
subroutine MPI_Comm_dup_proc (comm , newcomm , ierror )
354
419
use mpi_c_bindings, only: c_mpi_comm_dup, c_mpi_comm_c2f
355
420
integer , intent (in ) :: comm
0 commit comments