SURFEX v8.1
General documentation of Surfex
mpl_locomm_create_mod.F90
Go to the documentation of this file.
2 
3 !**** MPL_LOCOMM_CREATE Create a new communicator
4 
5 ! Purpose.
6 ! --------
7 ! Create a new communicator from lowest N tasks in MPI_COMM_WORLD
8 ! and set as default
9 
10 !** Interface.
11 ! ----------
12 ! CALL MPL_LOCOMM_CREATE
13 
14 ! Input required arguments :
15 ! -------------------------
16 ! N - Number of tasks in New Communicator
17 
18 ! Input optional arguments :
19 ! -------------------------
20 
21 ! Output required arguments :
22 ! -------------------------
23 ! KCOMM - New Communicator
24 
25 ! Output optional arguments :
26 ! -------------------------
27 ! MPL_LOCOMM_CREATE aborts when an error is detected.
28 
29 ! Author.
30 ! -------
31 ! J.Hague
32 
33 ! Modifications.
34 ! --------------
35 ! Original: 21/07/2003
36 
37 ! ------------------------------------------------------------------
38 
39 USE parkind1 ,ONLY : jpim ,jprb
40 
41 USE mpl_mpif
44 
45 IMPLICIT NONE
46 
47 PRIVATE
48 PUBLIC mpl_locomm_create
49 
50 CONTAINS
51 
52 
53 SUBROUTINE mpl_locomm_create(N,KCOMM)
54 
55 
56 #ifdef USE_8_BYTE_WORDS
57  USE mpi4to8, ONLY : &
58  mpi_comm_group => mpi_comm_group8, mpi_group_incl => mpi_group_incl8, mpi_comm_create => mpi_comm_create8
59 #endif
60 
61 
62 INTEGER(KIND=JPIM),INTENT(OUT) :: KCOMM
63 INTEGER(KIND=JPIM),INTENT(IN) :: N
64 
65 INTEGER(KIND=JPIM) :: IRANK(n)
66 INTEGER(KIND=JPIM) :: J, IER, IGROUP, MPI_GROUP_WORLD
67 LOGICAL :: LLABORT=.true.
68 
69 DO j=1,n
70  irank(j)=j-1
71 ENDDO
72 
73 CALL mpi_comm_group(mpl_comm,mpi_group_world,ier)
74 IF (ier/=0) CALL mpl_message(ier,'MPL_LOCOMM_CREATE: MPI_COMM_GROUP',ldabort=llabort)
75 
76 CALL mpi_group_incl(mpi_group_world,n,irank,igroup,ier)
77 IF (ier/=0) CALL mpl_message(ier,'MPL_LOCOMM_CREATE: MPI_GROUP_INCL',ldabort=llabort)
78 
79 CALL mpi_comm_create(mpl_comm,igroup,kcomm,ier)
80 IF (ier/=0) CALL mpl_message(ier,'MPL_LOCOMM_CREATE: MPI_COMM_CREATE',ldabort=llabort)
81 
82 RETURN
83 
84 END SUBROUTINE mpl_locomm_create
85 
86 END MODULE mpl_locomm_create_mod
subroutine, public mpl_message(KERROR, CDMESSAGE, CDSTRING, LDABORT)
integer, parameter jpim
Definition: parkind1.F90:13
subroutine, public mpl_locomm_create(N, KCOMM)
integer, parameter jprb
Definition: parkind1.F90:32
integer(kind=jpim) mpl_comm