SFEMaNS  version 4.1 (work in progress)
Reference documentation for SFEMaNS
 All Classes Files Functions Variables Groups Pages
create_communicators.f90
Go to the documentation of this file.
1 MODULE create_comm
2 PUBLIC :: create_cart_comm
3 PRIVATE
4 CONTAINS
5  SUBROUTINE create_cart_comm(ndim,comm_cart,comm_one_d,coord_cart)
6  IMPLICIT NONE
7  INTEGER, DIMENSION(:), INTENT(IN) :: ndim
8  INTEGER, INTENT(OUT) :: comm_cart
9  INTEGER, DIMENSION(:), POINTER :: comm_one_d, coord_cart
10  LOGICAL, DIMENSION(SIZE(ndim)) :: period, remain
11  LOGICAL :: reorder
12  INTEGER :: dim, nb_procs, code, n, i, rank
13 !Declare Petsc----------------------------------------------------------------
14 #include "petsc/finclude/petsc.h"
15 !-----------------------------------------------------------------------------
16  !==Verification of compatibility==!
17  CALL mpi_comm_size(petsc_comm_world, nb_procs, code)
18  dim = SIZE(ndim)
19  n= 1
20  DO i = 1, dim
21  n = n*ndim(i)
22  END DO
23  IF (nb_procs/=n) THEN
24  WRITE(*,*) ' CREATE_CART_COMM: Nb of procs not compatible with Cartesian decomposition'
25  stop
26  END IF
27 
28  !==Create Cartesian communication==!
29  ALLOCATE(comm_one_d(dim),coord_cart(dim))
30  period = .false.
31  reorder = .false.
32  CALL mpi_cart_create(petsc_comm_world, dim, ndim, period, reorder, comm_cart, code)
33  CALL mpi_comm_rank(comm_cart, rank, code)
34  CALL mpi_cart_coords(comm_cart, rank, dim, coord_cart, code)
35 
36  !==Create one D communication for each dimension==!
37  DO i = 1, dim
38  remain = .false.
39  remain(i) = .true.
40  CALL mpi_cart_sub(comm_cart, remain, comm_one_d(i), code)
41  END DO
42  END SUBROUTINE create_cart_comm
43 
44 END MODULE create_comm
subroutine, public create_cart_comm(ndim, comm_cart, comm_one_d, coord_cart)