ICON Community Interface 0.4.0
Loading...
Searching...
No Matches
mo_mpi_handshake.F90
Go to the documentation of this file.
1
3!
4! @authors 08/2021 :: ICON Community Interface <comin@icon-model.org>
5!
6! SPDX-License-Identifier: BSD-3-Clause
7!
8! Please see the file LICENSE in the root of the source tree for this code.
9! Where software is supplied by third parties, it is indicated in the
10! headers of the routines.
11!
13
15 INTEGER, PARAMETER :: max_groupname_len = 256
16
17CONTAINS
18
23 SUBROUTINE mpi_handshake ( comm, group_names, group_comms )
24 use, INTRINSIC :: iso_c_binding, only : c_ptr, c_char, c_null_char, c_loc
25
26 implicit none
27
28 interface
29 SUBROUTINE mpi_handshake_c2f (n, group_names, group_comms, comm) &
30 bind( c, name='mpi_handshake_c2f')
31 use, intrinsic :: iso_c_binding, only : c_ptr, c_int
32 implicit none
33 INTEGER(KIND=c_int), INTENT(in), VALUE :: n
34 TYPE (c_ptr) , INTENT(in) :: group_names(n)
35 INTEGER(KIND=c_int), INTENT(out) :: group_comms(n)
36 INTEGER(KIND=c_int), INTENT(in), VALUE :: comm
37 end subroutine mpi_handshake_c2f
38 end interface
39
40 integer, intent(in) :: comm
41 character(len=MAX_GROUPNAME_LEN), intent(in) :: group_names(:)
42 integer, intent(inout) :: group_comms(size(group_names))
43
44 CHARACTER (kind=c_char, len=MAX_GROUPNAME_LEN), TARGET :: group_names_cpy(size(group_names))
45 type( c_ptr ) :: group_name_ptr(size(group_names))
46 integer :: i
47 DO i=1,SIZE(group_names)
48 group_names_cpy(i) = trim(group_names(i)) // c_null_char
49 group_name_ptr(i) = c_loc(group_names_cpy(i))
50 END DO
51
52 CALL mpi_handshake_c2f(SIZE(group_names), group_name_ptr, group_comms, comm)
53
54 END SUBROUTINE mpi_handshake
55
56 !! @ingroup host_interface
57 SUBROUTINE mpi_handshake_dummy(comm)
58 INTEGER, INTENT(IN) :: comm
59 INTEGER :: empty_int_array(0)
60 CHARACTER(LEN=MAX_GROUPNAME_LEN) :: empty_char_array(0)
61
62 CALL mpi_handshake(comm, empty_char_array, empty_int_array)
63 END SUBROUTINE mpi_handshake_dummy
64
65END MODULE mo_mpi_handshake
subroutine, public mpi_handshake(comm, group_names, group_comms)
Procedure for the communicator splitting ("MPI handshake") that has been harmonized with the respecti...
void mpi_handshake_c2f(int n, char const **group_names, MPI_Fint *group_comms, MPI_Fint comm)
subroutine, public mpi_handshake_dummy(comm)
integer, parameter, public max_groupname_len