1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine MPI_Cart_rank_f08(comm, coords, rank, 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_Cart_rank_c, MPIR_Cartdim_get_c
11
12    implicit none
13
14    type(MPI_Comm), intent(in) :: comm
15    integer, intent(in) :: coords(*)
16    integer, intent(out) :: rank
17    integer, optional, intent(out) :: ierror
18
19    integer(c_Comm) :: comm_c
20    integer(c_int), allocatable :: coords_c(:)
21    integer(c_int) :: rank_c
22    integer(c_int) :: ierror_c
23    integer(c_int) :: err, ndims ! To get length of assumed-size arrays
24
25    if (c_int == kind(0)) then
26        ierror_c = MPIR_Cart_rank_c(comm%MPI_VAL, coords, rank)
27    else
28        comm_c = comm%MPI_VAL
29        err = MPIR_Cartdim_get_c(comm_c, ndims)
30        coords_c = coords(1:ndims)
31        ierror_c = MPIR_Cart_rank_c(comm_c, coords_c, rank_c)
32        rank = rank_c
33    end if
34
35    if(present(ierror)) ierror = ierror_c
36
37end subroutine MPI_Cart_rank_f08
38