LMDZ
tpm_distr.F90
Go to the documentation of this file.
1 MODULE tpm_distr
2 
3 USE parkind1 ,ONLY : jpim ,jprb
4 
5 IMPLICIT NONE
6 
7 SAVE
8 
9 !* Variables describing distributed memory parallelization
10 
11 INTEGER(KIND=JPIM) :: nproc ! Number of processors (NPRGPNS*NPRGPEW)
12 INTEGER(KIND=JPIM) :: nprgpns ! No. of sets in N-S direction (grid-point space)
13 INTEGER(KIND=JPIM) :: nprgpew ! No. of sets in E-W direction (grid-point space)
14 INTEGER(KIND=JPIM) :: nprtrw ! No. of sets in wave direction (spectral space)
15 INTEGER(KIND=JPIM) :: nprtrv ! NPROC/NPRTRW
16 INTEGER(KIND=JPIM) :: nprtrns ! No. of sets in N-S direction (Fourier space)
17  ! (always equal to NPRTRW)
18 LOGICAL :: leq_regions ! TRUE - Use new eq_regions partitioning
19  ! FALSE- Use old NPRGPNS x NPRGPEW partitioning
20 INTEGER(KIND=JPIM) :: myproc ! My processor number
21 INTEGER(KIND=JPIM) :: mysetw ! My set number in wave direction (spectral space)
22 INTEGER(KIND=JPIM) :: mysetv ! My set number in field direction(S.S and F.S)
23 INTEGER(KIND=JPIM) :: ncombflen ! Size of communication buffer
24 
25 INTEGER(KIND=JPIM) :: mtagletr ! Tag
26 INTEGER(KIND=JPIM) :: mtagml ! Tag
27 INTEGER(KIND=JPIM) :: mtaglg ! Tag
28 INTEGER(KIND=JPIM) :: mtaggl ! Tag
29 INTEGER(KIND=JPIM) :: mtagpart ! Tag
30 INTEGER(KIND=JPIM) :: mtagdistsp ! Tag
31 INTEGER(KIND=JPIM) :: mtaglm ! Tag
32 INTEGER(KIND=JPIM) :: mtagdistgp ! Tag
33 
34 INTEGER(KIND=JPIM) ,ALLOCATABLE :: nprcids(:) ! Array containing the process ids
35 
37 LOGICAL :: lsplit ! TRUE - latitudes are shared between a-sets
38 INTEGER(KIND=JPIM) :: napsets ! Number of apple sets at the poles. Default is zero.
39 
40 ! SPECTRAL SPACE
41 
42 INTEGER(KIND=JPIM) :: nump ! No. of spectral waves handled by this processor
43 INTEGER(KIND=JPIM) :: nspec ! No. of complex spectral coefficients (on this PE)
44 INTEGER(KIND=JPIM) :: nspec2 ! 2*NSPEC
45 INTEGER(KIND=JPIM) :: nspec2mx ! maximun NSPEC2 among all PEs
46 INTEGER(KIND=JPIM) :: ntpec2
47 INTEGER(KIND=JPIM) :: numtp
48 
49 
50 
51 INTEGER(KIND=JPIM) :: nspolegl ! No. of legendre polynomials on this PE
52 INTEGER(KIND=JPIM) :: nlei3d ! (NLEI3-1)/NPRTRW+1
53 
54 INTEGER(KIND=JPIM) ,POINTER :: myms(:) ! Wave numbers handled by this PE
55 INTEGER(KIND=JPIM) ,POINTER :: numpp(:) ! No. of wave numbers each wave set is
56  ! responsible for
57 INTEGER(KIND=JPIM) ,POINTER :: npossp(:) ! Not needed in transform?
58 INTEGER(KIND=JPIM) ,POINTER :: nprocm(:) ! Process that does the calc. for certain
59  ! wavenumber M
60 INTEGER(KIND=JPIM) ,POINTER :: ndim0g(:) ! Defines partitioning of global spectral
61  ! fields among PEs
62 
63 INTEGER(KIND=JPIM) ,POINTER :: nasm0(:) ! Address in a spectral array of (m, n=m)
64 INTEGER(KIND=JPIM) ,POINTER :: natm0(:) ! Same as NASM0 but for NTMAX
65 INTEGER(KIND=JPIM) ,POINTER :: nallms(:) ! Wave numbers for all a-set concatenated
66  ! together to give all wave numbers in a-set
67  ! order. Used when global spectral norms
68  ! have to be gathered.
69 INTEGER(KIND=JPIM) ,POINTER :: nptrms(:) ! Pointer to the first wave number of a given
70  ! a-set in nallms array.
71 
72 
73 ! Legendre polynomials
74 
75 INTEGER(KIND=JPIM) ,POINTER :: nlatls(:) ! First latitude for which each a-set calcul.
76 INTEGER(KIND=JPIM) ,POINTER :: nlatle(:) ! Last latitude for which each a-set calcul.
77 
78 INTEGER(KIND=JPIM) ,POINTER :: npmt(:) ! Adress for legendre polynomial for
79  ! given M (NTMAX)
80 INTEGER(KIND=JPIM) ,POINTER :: npms(:) ! Adress for legendre polynomial for
81  ! given M (NSMAX)
82 INTEGER(KIND=JPIM) ,POINTER :: npmg(:) ! Global version of NPMS
83 
84 ! FOURIER SPACE
85 
86 INTEGER(KIND=JPIM) :: ndgl_fs ! Number of rows of latitudes for which this process is
87  ! performing Fourier Space calculations
88 
89 INTEGER(KIND=JPIM) ,POINTER :: nstagtf(:) ! Offset for specific latitude in
90  ! Fourier/gridpoint buffer
91 INTEGER(KIND=JPIM) :: nlengtf ! Second dimension of Fourier/gridpoint buffer
92  ! (sum of (NLOEN+3) over local latitudes)
93 
94 INTEGER(KIND=JPIM) ,POINTER :: nultpp(:) ! No of lats. for each wave_set (F.S)
95 INTEGER(KIND=JPIM) ,POINTER :: nprocl(:) ! Process responsible for each lat. (F.S)
96 INTEGER(KIND=JPIM) ,POINTER :: nptrls(:) ! Pointer to first lat. (F.S)
97 
98 INTEGER(KIND=JPIM) ,POINTER :: nstagt0b(:) ! Start adresses for segments within buffer
99  ! (according to processors to whom data
100  ! is going to be sent)
101 INTEGER(KIND=JPIM) ,POINTER :: nstagt1b(:)
102 INTEGER(KIND=JPIM) ,POINTER :: npntgtb0(:,:)
103 INTEGER(KIND=JPIM) ,POINTER :: npntgtb1(:,:)
104 INTEGER(KIND=JPIM) ,POINTER :: nltsftb(:)
105 
106 INTEGER(KIND=JPIM) ,POINTER :: nltsgtb(:)
107 INTEGER(KIND=JPIM) ,POINTER :: mstabf(:)
108 
109 INTEGER(KIND=JPIM) :: nlengt0b
110 INTEGER(KIND=JPIM) :: nlengt1b
111 
112 ! GRIDPOINT SPACE
113 
114 INTEGER(KIND=JPIM) :: ndgl_gp ! D%NLSTLAT(MY_REGION_NS)-D%NFRSTLOFF
115 INTEGER(KIND=JPIM) ,POINTER :: nfrstlat(:) ! First lat of each a-set
116 INTEGER(KIND=JPIM) ,POINTER :: nlstlat(:) ! Last lat of each a-set
117 INTEGER(KIND=JPIM) :: nfrstloff ! Offset for first lat of own a-set
118  ! i.e. NFRSTLOFF=NFRSTLAT(MYSETA)-1
119 INTEGER(KIND=JPIM) ,POINTER :: nptrlat(:) ! Pointer to start of latitude
120 INTEGER(KIND=JPIM) ,POINTER :: nptrfrstlat(:) ! Pointer to the first latitude of each
121  ! a-set in NSTA and NONL arrays
122 INTEGER(KIND=JPIM) ,POINTER :: nptrlstlat(:) ! Pointer to the last latitude of each
123  ! a-set in NSTA and NONL arrays
124 INTEGER(KIND=JPIM) :: nptrfloff ! Offset for pointer to the first latitude of own a-set
125  ! NSTA and NONL arrays, i.e. NPTRFRSTLAT(MYSETA)-1
126 LOGICAL ,POINTER :: lsplitlat(:) ! True if latitude is split over 2 a-sets
127 
128 ! NSTA(R%NDGL+NPRGPNS-1,NPRGPEW) : Position of first grid column
129 ! for the latitudes on a processor. The information is
130 ! available for all processors. The b-sets are distinguished
131 ! by the last dimension of NSTA(). The latitude band for
132 ! each a-set is addressed by NPTRFRSTLAT(JASET),
133 ! NPTRLSTLAT(JASET), and NPTRFLOFF=NPTRFRSTLAT(MYSETA) on
134 ! this processors a-set. Each split latitude has two entries
135 ! in NSTA(,:) which necessitates the rather complex
136 ! addressing of NSTA(,:) and the overdimensioning of NSTA by
137 ! NPRGPNS.
138 ! NONL(R%NDGL+NPRGPNS-1,NPRGPEW) : Number of grid columns for
139 ! the latitudes on a processor. Similar to NSTA() in data
140 ! structure.
141 INTEGER(KIND=JPIM) ,POINTER :: nsta(:,:)
142 INTEGER(KIND=JPIM) ,POINTER :: nonl(:,:)
143 
144 INTEGER(KIND=JPIM) :: ngptot ! Total number of grid columns on this PE
145 INTEGER(KIND=JPIM) :: ngptotg ! Total number of grid columns on the Globe
146 INTEGER(KIND=JPIM) :: ngptotmx ! Maximum number of grid columns on any of the PEs
147 INTEGER(KIND=JPIM) ,POINTER :: ngptotl(:,:) ! Number of grid columns on each PE.
148 
149 END TYPE distr_type
150 
151 TYPE(distr_type),ALLOCATABLE,TARGET :: distr_resol(:)
152 TYPE(distr_type),POINTER :: d
153 
154 !$OMP THREADPRIVATE(d,leq_regions,mtagdistgp,mtagdistsp,mtaggl,mtagletr)
155 !$OMP THREADPRIVATE(mtaglg,mtaglm,mtagml,mtagpart,myproc,mysetv,mysetw)
156 !$OMP THREADPRIVATE(ncombflen,nprgpew,nprgpns,nproc,nprtrns,nprtrv,nprtrw)
157 
158 !$OMP THREADPRIVATE(distr_resol)
159 
160 END MODULE tpm_distr
161 
162 
163 
164 
165 
166 
167 
integer(kind=jpim) mtagpart
Definition: tpm_distr.F90:29
integer(kind=jpim), dimension(:), allocatable nprcids
Definition: tpm_distr.F90:34
integer(kind=jpim) ncombflen
Definition: tpm_distr.F90:23
type(distr_type), pointer d
Definition: tpm_distr.F90:152
integer(kind=jpim) myproc
Definition: tpm_distr.F90:20
integer(kind=jpim) mtaggl
Definition: tpm_distr.F90:28
integer(kind=jpim) mtagletr
Definition: tpm_distr.F90:25
integer, parameter jprb
Definition: parkind1.F90:31
integer(kind=jpim) nproc
Definition: tpm_distr.F90:11
integer(kind=jpim) nprgpns
Definition: tpm_distr.F90:12
integer(kind=jpim) mysetw
Definition: tpm_distr.F90:21
integer(kind=jpim) mysetv
Definition: tpm_distr.F90:22
integer(kind=jpim) nprtrv
Definition: tpm_distr.F90:15
integer(kind=jpim) mtagdistgp
Definition: tpm_distr.F90:32
integer(kind=jpim) nprtrw
Definition: tpm_distr.F90:14
integer(kind=jpim) nprgpew
Definition: tpm_distr.F90:13
integer(kind=jpim) mtagml
Definition: tpm_distr.F90:26
integer(kind=jpim) nprtrns
Definition: tpm_distr.F90:16
type(distr_type), dimension(:), allocatable, target distr_resol
Definition: tpm_distr.F90:151
integer, parameter jpim
Definition: parkind1.F90:13
integer(kind=jpim) mtaglg
Definition: tpm_distr.F90:27
logical leq_regions
Definition: tpm_distr.F90:18
integer(kind=jpim) mtaglm
Definition: tpm_distr.F90:31
integer(kind=jpim) mtagdistsp
Definition: tpm_distr.F90:30