LMDZ
yommp.F90
Go to the documentation of this file.
1 MODULE yommp
2 
3 USE parkind1 ,ONLY : jpim
4 
5 IMPLICIT NONE
6 
7 SAVE
8 
9 ! ----------------------------------------------------------------------
10 !* variables describing distributed memory parallelization
11 
12 ! ---------------------------------------
13 
14 ! mp_type : 1=blocked (MPI_SEND/RECV)
15 ! : 2=buffered (MPI_BSEND/MPI_BRECV)
16 ! : 3=immediate (MPI_ISEND/MPI_IRECV)
17 ! mbx_size : user-provided mailbox size
18 
19 ! myproc : logical processor id (is in the range 1 to nproc)
20 ! myseta : own processor set a (is in the range 1 to nprgpns)
21 ! mysetb : own processor set b (is in the range 1 to nprgpew)
22 ! my_region_ns: own processor set a (is in the range 1 to n_regions_ns)
23 ! my_region_ew: own processor set b (is in the range 1 to n_regions_ew)
24 ! mysetw : own processor set a in wave space (1..nprtrw)
25 ! mysetv : own processor set b in wave space (1..nprtrv)
26 ! mysetm : own processor set a in spectral space (1..nprtrm)
27 ! mysetn : own processor set b in spectral space (1..nprtrn)
28 ! mysetaf : own processor set a in Fourier space (is in the range
29 ! 1 to nprocc)
30 ! ngpset2pe : grid point space processor mapping array (n_regions_ns,n_regions_ew)
31 ! nslpad : number of pad words initialised to a huge number at either
32 ! of side of the sl halo, used to trap halo problems.
33 ! The default is 0.
34 ! nintype : type in input processing to be performed
35 ! : 1=pbio
36 ! : 2=mpi-io (future)
37 ! nouttype : type of output (post) processing to be performed
38 ! : 1=pbio
39 ! : 2=output to FDB
40 ! : 3=shared blocking MPI-I/O
41 ! : 4=shared blocking collective MPI-I/O
42 ! : 5=shared non-blocking MPI_I/O
43 ! : 6=shared non-blocking collective MPI_I/O
44 ! nstrin : number of processors required to perform input processing
45 ! nstrout : number of processors required to perform output processing
46 ! ngathout : to be described
47 ! nwrtout : to be described
48 ! nblkout : to be described
49 ! nfldin : number of input fields to be buffered during distribution
50 ! nfldout : number of output fields to be buffered during gathering
51 ! nprcids(nproc) : array containing the process ids. It is the mapping
52 ! between the process numbering in the application
53 ! (from 1 to NPROC) and the numbering used by the
54 ! underlying communication library.
55 
56 ! lockio : io to be done in locked regions (.true.)
57 
58 ! lsplit : true - latitudes are shared between a-sets
59 ! false - a latitude belongs to only one a-set
60 ! leq_regions : true - use new eq_regions partitioning
61 ! false - use old NPRGPNS x NPRGPEW partitioning
62 ! lsplitout : output data provided in sequential files (.true.) or
63 ! in directories (.false.)
64 ! limp : true: immediate message passing in transposition routines
65 ! limp_noolap : true: isend/irecv with no overlap of message passing and
66 ! packing of buffers
67 
68 INTEGER(KIND=JPIM),ALLOCATABLE:: nprcids(:)
69 INTEGER(KIND=JPIM),ALLOCATABLE:: ngpset2pe(:,:)
70 LOGICAL :: lsplit
71 LOGICAL :: leq_regions
72 LOGICAL :: lsplitout
73 LOGICAL :: lockio
74 LOGICAL :: limp
75 LOGICAL :: limp_noolap
76 
77 INTEGER(KIND=JPIM) :: mp_type
78 INTEGER(KIND=JPIM) :: mbx_size
79 INTEGER(KIND=JPIM) :: myproc
80 INTEGER(KIND=JPIM) :: myseta
81 INTEGER(KIND=JPIM) :: mysetb
82 INTEGER(KIND=JPIM) :: mysetw
83 INTEGER(KIND=JPIM) :: mysetv
84 INTEGER(KIND=JPIM) :: mysetm
85 INTEGER(KIND=JPIM) :: mysetn
86 INTEGER(KIND=JPIM) :: my_region_ns
87 INTEGER(KIND=JPIM) :: my_region_ew
88 INTEGER(KIND=JPIM) :: nstrin
89 INTEGER(KIND=JPIM) :: nstrout
90 INTEGER(KIND=JPIM) :: nfldin
91 INTEGER(KIND=JPIM) :: nfldout
92 INTEGER(KIND=JPIM) :: nslpad
93 INTEGER(KIND=JPIM) :: nintype
94 INTEGER(KIND=JPIM) :: nouttype
95 INTEGER(KIND=JPIM) :: ngathout
96 INTEGER(KIND=JPIM) :: nwrtout
97 INTEGER(KIND=JPIM) :: nblkout
98 
99 ! ----------------------------------------------------------------------
100 
101 !* common block describing the partitioning of data
102 
103 ! ----------------------------------------------------
104 
105 ! nprocm(0:ncmax) : gives process which is responsible for Legendre
106 ! transforms, nmi, and spectral space calculations for a
107 ! certain wave number m
108 ! numprocfp(nfprgpg) : gives process which is responsible for FULL-POS
109 ! horizontal interpolation point. This is only used in
110 ! FULL-POS.
111 ! numpp(n_regions_ns) : the number of wave numbers each a-set is responsible
112 ! for. As aspecial case NUMP = NUMPP(MYSETA).
113 ! numxpp(n_regions_ns) : Similar to NUMPP() but for NXMAX.
114 ! nallms(0:max(nsmax,nmsmax)) : wave numbers for all a-set concate-
115 ! nated together to give all wave numbers in a-set order.
116 ! Used when global spectral norms have to be gathered.
117 ! nptrms(n_regions_ns) : pointer to the first wave number of a given a-set
118 ! in nallms array.
119 ! mylats(1:ndgenl) if LMESSP else mylats(ndgsag:ndgeng) : mapping
120 ! between physical latitude number and local latitude number
121 ! in grid point space on this process. This is identical
122 ! for all processes within an a-set
123 ! nptrls(n_regions_ns) : pointer to first global latitude of each a-set
124 ! for which it performs the Fourier calculations
125 ! nptrlsf(n_regions_ns) : pointer to first global latitude of each a-set
126 ! for which it performs the Fourier calculations
127 ! nfrstlat(n_regions_ns) : first lat of each a-set in grid-point space
128 ! nfrstloff: offset for first lat of own a-set in grid-point space,
129 ! i.e. nfrstloff=nfrstlat(my_region_ns)-1
130 ! nlstlat(n_regions_ns) : last lat of each a-set in grid-point space
131 ! nptrfrstlat(n_regions_ns) : pointer to the first latitude of each a-set in
132 ! NSTA and NONL arrays
133 ! nptrlstlat(n_regions_ns) : pointer to the last latitude of each a-set in
134 ! NSTA and NONL arrays
135 ! nptrfloff : offset for pointer to the first latitude of own a-set
136 ! NSTA and NONL arrays, i.e. nptrfrstlatf(my_region_ns)-1
137 ! nptrlat : pointer to start of latitude in grid-point space
138 ! lsplitlat(ndglg) : true if latitude is split in grid point space
139 ! over two a-sets
140 ! myfrstactlat : first actual lat on this PE in grid-point space,
141 ! it is nfrstlat(my_region_ns)
142 ! mylstactlat : last actual lat on this PE in grid-point space,
143 ! it is nlstlat(my_region_ns)
144 ! ------------------------------------------------------------------
145 ! nptrsv(nprtrw+1) : pointer to first spectral wave column to be
146 ! handled by each b-set. Used for semi-implicit calculations
147 ! and Jb vertical transforms, and only really if nprtrv>1.
148 ! nptrcv(nprtrv+1) : As nptrsv but for ncmax arrays
149 ! nptrtv(nprtrv+1) : As nptrsv but for ntmax arrays
150 ! nptrsvf(nprtrv+1) : As nptrsv but for the case where full m-columns
151 ! have to be treated by one processor for the vertical
152 ! spectral calculations. This is the case if implicit
153 ! treatment of Coriolis terms is used and in other cases.
154 ! nptrmf(nprtrv+1) : Distribution of m-columns among b-sets used for
155 ! the full m-column cases where nptrsvf() is used.
156 ! nspstaf(0:nsmax) : pointer to where each m-column starts (used for
157 ! the full m-column cases where nptrsvf() is used.
158 ! numll(nprtrv+1) : distribution of levels among b-sets for Legendre
159 ! transforms, FFT and horizontal diffusion.
160 ! To simplify coding numll(nprtrv+1) is defined to zero.
161 ! numvmo(nprtrv) : number of vertical normal modes on each b-set
162 ! numvmojb(nprtrv) : number of vertical normal modes on each b-set for
163 ! Jb computations
164 ! nptrll(nprtrv+1) : defines the first level treated on each b-set
165 ! To simplify coding nptrll(nprtrv+1)=nptrll(nprtrv)
166 ! npsp : =1 if surface pressure is handled by this processor for
167 ! the Legendre Trasforms and FFT calculations. npsp is
168 ! the same for all processors within a b-set.
169 ! npsurf(nprtrv) : contains the npsp-values for each b-set
170 ! nbsetlev(nflevg) : the b-set on which a level belongs. Please use
171 ! global indexing.
172 ! nbsetsp : the b-set on which the surface pressure belongs.
173 ! mylevs(nflevl) : mapping between local and global numbering for the
174 ! levels handled by this process.
175 ! nvmodist(nvmodmxpp,nprtrv) : normal modes mapped to the different
176 ! b-sets. The same distribution strategy is used for NMI and
177 ! Jb calculations. The number of modes is usually larger
178 ! for Jb caluclations.
179 ! nspec2v : number of spectral columns treated by this process for
180 ! semi-implicit calculations and other vertical transforms
181 ! ncpec2v : like nspec2v for NCMAX arrays
182 ! ntpec2v : like nspec2v for NTMAX arrays
183 ! nspec2vf: number of spectral columns treated by this process for
184 ! semi-implicit calculations for the full m-column cases.
185 ! See nptrsvf().
186 ! nsta(ndgsag:ndgeng+n_regions_ns-1,n_regions_ew) : Position of first grid column
187 ! for the latitudes on a processor. The information is
188 ! available for all processors. The b-sets are distinguished
189 ! by the last dimension of nsta(). The latitude band for
190 ! each a-set is addressed by nptrfrstlat(jaset),
191 ! nptrlstlat(jaset), and nptrfloff=nptrfrstlat(my_region_ns) on
192 ! this processors a-set. Each split latitude has two entries
193 ! in nsta(,:) which necessitates the rather complex
194 ! addressing of nsta(,:) and the overdimensioning of nsta by
195 ! n_regions_ns.
196 ! nonl(ndgsag:ndgeng+n_regions_ns-1,n_regions_ew) : number of grid columns for
197 ! the latitudes on a processor. Similar to nsta() in data
198 ! structure.
199 ! belong to it in fourier space. Available for all n_regions_ew
200 ! processors within this processors a-set.
201 ! napsets : number of apple sets at the poles. Default is zero.
202 ! nglobalindex : mapping of local grid points to global grid points
203 ! : used for debugging
204 ! nglobalproc : global data structure containing proc distribution
205 ! an ngptotg array that maps owning proc
206 ! nlocalindex : global data structure containing local index
207 ! an ngptotg array that maps the local index into a
208 ! ngptot array for the owning proc
209 
210 ! -- SLCSET and SLRSET variables (based on NSLWIDE).
211 ! naslb1 : local inner dimension of semi-Lagrangian buffer. It is
212 ! the number of columns in the core+halo region on this
213 ! processor.
214 ! nslprocs : semi-Lagrangian communication : number of processors
215 ! this processor needs to communicate with.
216 ! nslrpt : the number of columns received from other PE's when
217 ! computing the halo for interpolations.
218 ! nslspt : the number of columns sent to other PE's when
219 ! computing the halo for interpolations.
220 ! nslmpbufsz : size of semi-Lagrangian communication buffer in
221 ! slcomm.F. It is sized so the total requirement is kept
222 ! below ncombflen.
223 ! nslsta(ndgsal-nslwide:ndgenl+nslwide) : Start position in semi-
224 ! Lagrangian buffer ZSLBUF1 of grid columns for each local
225 ! and halo latitude.
226 ! nslonl(ndgsal-nslwide:ndgenl+nslwide) : number of grid columns on
227 ! each local and halo latitude in the semi-Lagrangian
228 ! buffer ZSLBUF1. Only used in dm version.
229 ! nsloff(ndgsal-nslwide:ndgenl+nslwide) : offset to the start of each
230 ! local and halo latitude in the semi-Lagrangian buffer
231 ! ZSLBUF1. Only used in dm version.
232 ! nslext(1-ndlon:ndlon+ndlon,1-nslwide:ndgenl+nslwide) in dm version
233 ! and nslext(nslext(0:ndlon+2,ndgsag:ndgeng) in sm version : pointer
234 ! that makes sure addressing of points in the east-west
235 ! extension zone is correct. It also handles the half
236 ! latitude shift of extension latitudes at the poles.
237 ! In the sm version this array is just the identity, but
238 ! used in order to keep sm and dm code in common.
239 ! nslsendpos: the addresses within the semi-Lagrangian buffer of point sent
240 ! from this PE.
241 ! nslrecvpos: the addresses within the semi-Lagrangian buffer of point
242 ! received on this PE.
243 ! nsendptr : pointer to the first point for each of the PE's that has to
244 ! receive semi-Lagrangian halo-data from this.
245 ! Used for addressing nslsendpos().
246 ! nrecvptr : pointer to the first point for each of the PE's that are sending
247 ! semi-Lagrangian halo-data to this PE.
248 ! Used for addressing nslrecvpos().
249 ! nsendnum(nproc+1) : Pointing at the first semi-Lagrangian
250 ! halo data entry this processor is sending to each of the
251 ! other processors. The number of columns sent is equal to
252 ! nsendnum(irecver+1)-nsendnum(irecver), and might be zero.
253 ! nrecvnum(nproc+1) : Pointing at the first semi-Lagrangian
254 ! halo data entry this processor is receiving from each of
255 ! the other processors. The number of columns received is
256 ! equal to nrecvnum(isender+1)-nrecvnum(isender), it might
257 ! be zero.
258 ! nslcore(ngptot) : Pointer to this processors core region points
259 ! within the semi-Lagrangian buffer
260 ! nslcomm(nslprocs) : semi-Lagrangian communication : list of the
261 ! processors this proceesor has to communicate with.
262 
263 ! -- SUFPCSET and SUFPRSET variables (based on NFPWIDE).
264 ! nafpb1 : FULL-POS version of naslb1
265 ! nfpprocs : FULL-POS version of nslprocs
266 ! nfpmpbufsz : FULL-POS version of nslmpbufsz
267 ! nfprpt : FULL-POS version of nslrpt
268 ! nfpspt : FULL-POS version of nslspt
269 ! nfpsta : FULL-POS version of nslsta
270 ! nfponl : FULL-POS version of nslonl
271 ! nfpoff : FULL-POS version of nsloff
272 ! nfpext : FULL-POS version of nslext
273 ! nfpsendpos : FULL-POS version of nslsendpos
274 ! nfprecvpos : FULL-POS version of nslrecvpos
275 ! nfpsendptr : FULL-POS version of nsendptr
276 ! nfprecvptr : FULL-POS version of nrecvptr
277 ! nfpcore : FULL-POS version of nslcore
278 ! nfpcomm : FULL-POS version of nslcomm
279 
280 ! -- SLCSET variables (based on NOBWIDE)
281 ! nobsta : observation version of nslsta
282 ! nobonl : observation version of nslonl
283 ! noboff : observation version of nsloff
284 
285 ! -- SLCSET variables (based on NRIWIDE - model grid).
286 ! narib1 : Radiation input version of naslb1
287 ! nriprocs : Radiation input version of nslprocs
288 ! nrimpbufsz : Radiation input version of nslmpbufsz
289 ! nrirpt : Radiation input version of nslrpt
290 ! nrispt : Radiation input version of nslspt
291 ! nrista : Radiation input version of nslsta
292 ! nrionl : Radiation input version of nslonl
293 ! nrioff : Radiation input version of nsloff
294 ! nriext : Radiation input version of nslext
295 ! nrisendpos : Radiation input version of nslsendpos
296 ! nrirecvpos : Radiation input version of nslrecvpos
297 ! nrisendptr : Radiation input version of nsendptr
298 ! nrirecvptr : Radiation input version of nrecvptr
299 ! nricore : Radiation input version of nslcore
300 ! nricomm : Radiation input version of nslcomm
301 
302 ! -- SLCSET variables (based on NROWIDE - radiation grid).
303 ! narob1 : Radiation input version of naslb1
304 ! nroprocs : Radiation input version of nslprocs
305 ! nrompbufsz : Radiation input version of nslmpbufsz
306 ! nrorpt : Radiation input version of nslrpt
307 ! nrospt : Radiation input version of nslspt
308 ! nrosta : Radiation input version of nslsta
309 ! nroonl : Radiation input version of nslonl
310 ! nrooff : Radiation input version of nsloff
311 ! nroext : Radiation input version of nslext
312 ! nrosendpos : Radiation input version of nslsendpos
313 ! nrorecvpos : Radiation input version of nslrecvpos
314 ! nrosendptr : Radiation input version of nsendptr
315 ! nrorecvptr : Radiation input version of nrecvptr
316 ! nrocore : Radiation input version of nslcore
317 ! nrocomm : Radiation input version of nslcomm
318 
319 ! ------------------------------------------------------------------
320 
321 ! ncombflen : Size of communication buffer. This is the maximum per
322 ! processor buffer space (in words) that the IFS should use
323 ! for one or more sends before receives are issued from
324 ! destination processors.
325 
326 INTEGER(KIND=JPIM),ALLOCATABLE:: numpp(:)
327 INTEGER(KIND=JPIM),ALLOCATABLE:: numxpp(:)
328 INTEGER(KIND=JPIM),ALLOCATABLE:: nprocm(:)
329 INTEGER(KIND=JPIM),ALLOCATABLE:: numprocfp(:)
330 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrms(:)
331 INTEGER(KIND=JPIM),ALLOCATABLE:: nallms(:)
332 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrls(:)
333 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrsv(:)
334 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrcv(:)
335 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrtv(:)
336 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrsvf(:)
337 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrmf(:)
338 INTEGER(KIND=JPIM),ALLOCATABLE:: nspstaf(:)
339 INTEGER(KIND=JPIM),ALLOCATABLE:: numll(:)
340 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrll(:)
341 INTEGER(KIND=JPIM),ALLOCATABLE:: numvmo(:)
342 INTEGER(KIND=JPIM),ALLOCATABLE:: numvmojb(:)
343 INTEGER(KIND=JPIM),ALLOCATABLE:: mylevs(:)
344 INTEGER(KIND=JPIM),ALLOCATABLE:: npsurf(:)
345 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nsta(:,:)
346 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nonl(:,:)
347 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nptrfrstlat(:)
348 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrlstlat(:)
349 INTEGER(KIND=JPIM),ALLOCATABLE:: nptrlat(:)
350 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nfrstlat(:)
351 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nlstlat(:)
352 INTEGER(KIND=JPIM),ALLOCATABLE:: nbsetlev(:)
353 INTEGER(KIND=JPIM),ALLOCATABLE:: nglobalindex(:)
354 INTEGER(KIND=JPIM),ALLOCATABLE:: nglobalproc(:)
355 INTEGER(KIND=JPIM),ALLOCATABLE:: nlocalindex(:)
356 
357 LOGICAL,ALLOCATABLE:: lsplitlat(:)
358 
359 INTEGER(KIND=JPIM),ALLOCATABLE:: mylats(:)
360 INTEGER(KIND=JPIM),ALLOCATABLE:: nvmodist(:,:)
361 
362 ! -- SLCSET and SLRSET variables (based on NSLWIDE).
363 
364 INTEGER(KIND=JPIM),ALLOCATABLE:: nslsta(:)
365 INTEGER(KIND=JPIM),ALLOCATABLE:: nslonl(:)
366 INTEGER(KIND=JPIM),ALLOCATABLE:: nsloff(:)
367 INTEGER(KIND=JPIM),ALLOCATABLE:: nslext(:,:)
368 INTEGER(KIND=JPIM),ALLOCATABLE:: nslsendpos(:)
369 INTEGER(KIND=JPIM),ALLOCATABLE:: nslrecvpos(:)
370 INTEGER(KIND=JPIM),ALLOCATABLE:: nsendptr(:)
371 INTEGER(KIND=JPIM),ALLOCATABLE:: nrecvptr(:)
372 INTEGER(KIND=JPIM),ALLOCATABLE:: nslcore(:)
373 INTEGER(KIND=JPIM),ALLOCATABLE:: nslcomm(:)
374 
375 ! -- SUFPCSET and SUFPRSET variables (based on NFPWIDE).
376 
377 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpsta(:)
378 INTEGER(KIND=JPIM),ALLOCATABLE:: nfponl(:)
379 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpoff(:)
380 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpext(:,:)
381 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpsendpos(:)
382 INTEGER(KIND=JPIM),ALLOCATABLE:: nfprecvpos(:)
383 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpsendptr(:)
384 INTEGER(KIND=JPIM),ALLOCATABLE:: nfprecvptr(:)
385 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpcore(:)
386 INTEGER(KIND=JPIM),ALLOCATABLE:: nfpcomm(:)
387 
388 ! -- SLCSET variables (based on NOBWIDE)
389 
390 INTEGER(KIND=JPIM),ALLOCATABLE:: nobsta(:)
391 INTEGER(KIND=JPIM),ALLOCATABLE:: nobonl(:)
392 INTEGER(KIND=JPIM),ALLOCATABLE:: noboff(:)
393 
394 ! -- SLCSET variables (based on NRIWIDE).
395 
396 INTEGER(KIND=JPIM),ALLOCATABLE:: nrista(:)
397 INTEGER(KIND=JPIM),ALLOCATABLE:: nrionl(:)
398 INTEGER(KIND=JPIM),ALLOCATABLE:: nrioff(:)
399 INTEGER(KIND=JPIM),ALLOCATABLE:: nriext(:,:)
400 INTEGER(KIND=JPIM),ALLOCATABLE:: nrisendpos(:)
401 INTEGER(KIND=JPIM),ALLOCATABLE:: nrirecvpos(:)
402 INTEGER(KIND=JPIM),ALLOCATABLE:: nrisendptr(:)
403 INTEGER(KIND=JPIM),ALLOCATABLE:: nrirecvptr(:)
404 INTEGER(KIND=JPIM),ALLOCATABLE:: nricore(:)
405 INTEGER(KIND=JPIM),ALLOCATABLE:: nricomm(:)
406 
407 ! -- SLCSET variables (based on NROWIDE).
408 
409 INTEGER(KIND=JPIM),ALLOCATABLE:: nrosta(:)
410 INTEGER(KIND=JPIM),ALLOCATABLE:: nroonl(:)
411 INTEGER(KIND=JPIM),ALLOCATABLE:: nrooff(:)
412 INTEGER(KIND=JPIM),ALLOCATABLE:: nroext(:,:)
413 INTEGER(KIND=JPIM),ALLOCATABLE:: nrosendpos(:)
414 INTEGER(KIND=JPIM),ALLOCATABLE:: nrorecvpos(:)
415 INTEGER(KIND=JPIM),ALLOCATABLE:: nrosendptr(:)
416 INTEGER(KIND=JPIM),ALLOCATABLE:: nrorecvptr(:)
417 INTEGER(KIND=JPIM),ALLOCATABLE:: nrocore(:)
418 INTEGER(KIND=JPIM),ALLOCATABLE:: nrocomm(:)
419 
420 INTEGER(KIND=JPIM) :: numxp
421 INTEGER(KIND=JPIM) :: npsp
422 INTEGER(KIND=JPIM) :: nspec2v
423 INTEGER(KIND=JPIM) :: ncpec2v
424 INTEGER(KIND=JPIM) :: ntpec2v
425 INTEGER(KIND=JPIM) :: nspec2vf
426 INTEGER(KIND=JPIM) :: nbsetsp
427 INTEGER(KIND=JPIM) :: nfrstloff
428 INTEGER(KIND=JPIM) :: myfrstactlat
429 INTEGER(KIND=JPIM) :: mylstactlat
430 INTEGER(KIND=JPIM) :: napsets
431 INTEGER(KIND=JPIM) :: nptrfloff
432 INTEGER(KIND=JPIM) :: ncombflen
433 
434 ! -- scalar integers depending on NSLWIDE.
435 
436 INTEGER(KIND=JPIM) :: naslb1
437 INTEGER(KIND=JPIM) :: nslprocs
438 INTEGER(KIND=JPIM) :: nslmpbufsz
439 INTEGER(KIND=JPIM) :: nslrpt
440 INTEGER(KIND=JPIM) :: nslspt
441 
442 ! -- scalar integers depending on NFPWIDE.
443 
444 INTEGER(KIND=JPIM) :: nafpb1
445 INTEGER(KIND=JPIM) :: nfpprocs
446 INTEGER(KIND=JPIM) :: nfpmpbufsz
447 INTEGER(KIND=JPIM) :: nfprpt
448 INTEGER(KIND=JPIM) :: nfpspt
449 
450 ! -- scalar integers depending on NRIWIDE.
451 
452 INTEGER(KIND=JPIM) :: narib1
453 INTEGER(KIND=JPIM) :: nriprocs
454 INTEGER(KIND=JPIM) :: nrimpbufsz
455 INTEGER(KIND=JPIM) :: nrirpt
456 INTEGER(KIND=JPIM) :: nrispt
457 
458 ! -- scalar integers depending on NROWIDE.
459 
460 INTEGER(KIND=JPIM) :: narob1
461 INTEGER(KIND=JPIM) :: nroprocs
462 INTEGER(KIND=JPIM) :: nrompbufsz
463 INTEGER(KIND=JPIM) :: nrorpt
464 INTEGER(KIND=JPIM) :: nrospt
465 
466 ! ----------------------------------------------------------------------
467 
468 !$OMP THREADPRIVATE(leq_regions,limp,limp_noolap,lockio,lsplit,lsplitout,mbx_size,mp_type,my_region_ew,my_region_ns)
469 !$OMP THREADPRIVATE(myfrstactlat,mylstactlat,myproc,myseta,mysetb,mysetm,mysetn,mysetv,mysetw,nafpb1,napsets,narib1)
470 !$OMP THREADPRIVATE(narob1,naslb1,nblkout,nbsetsp,ncombflen,ncpec2v,nfldin,nfldout,nfpmpbufsz,nfpprocs,nfprpt,nfpspt)
471 !$OMP THREADPRIVATE(nfrstloff,ngathout,nintype,nouttype,npsp,nptrfloff,nrimpbufsz,nriprocs,nrirpt,nrispt,nrompbufsz)
472 !$OMP THREADPRIVATE(nroprocs,nrorpt,nrospt,nslmpbufsz,nslpad,nslprocs,nslrpt,nslspt,nspec2v,nspec2vf,nstrin,nstrout)
473 !$OMP THREADPRIVATE(ntpec2v,numxp,nwrtout)
474 !$OMP THREADPRIVATE(lsplitlat,mylats,mylevs,nallms,nbsetlev,nfpcomm,nfpcore,nfpext,nfpoff,nfponl,nfprecvpos,nfprecvptr)
475 !$OMP THREADPRIVATE(nfpsendpos,nfpsendptr,nfpsta,nfrstlat,nglobalindex,nglobalproc,ngpset2pe,nlocalindex,nlstlat,noboff)
476 !$OMP THREADPRIVATE(nobonl,nobsta,nonl,nprcids,nprocm,npsurf,nptrcv,nptrfrstlat,nptrlat,nptrll,nptrls,nptrlstlat,nptrmf)
477 !$OMP THREADPRIVATE(nptrms,nptrsv,nptrsvf,nptrtv,nrecvptr,nricomm,nricore,nriext,nrioff,nrionl,nrirecvpos,nrirecvptr)
478 !$OMP THREADPRIVATE(nrisendpos,nrisendptr,nrista,nrocomm,nrocore,nroext,nrooff,nroonl,nrorecvpos,nrorecvptr,nrosendpos)
479 !$OMP THREADPRIVATE(nrosendptr,nrosta,nsendptr,nslcomm,nslcore,nslext,nsloff,nslonl,nslrecvpos,nslsendpos,nslsta)
480 !$OMP THREADPRIVATE(nspstaf,nsta,numll,numpp,numprocfp,numvmo,numvmojb,numxpp,nvmodist)
481 END MODULE yommp
logical lockio
Definition: yommp.F90:73
integer(kind=jpim) nrimpbufsz
Definition: yommp.F90:454
integer(kind=jpim) mp_type
Definition: yommp.F90:77
integer(kind=jpim), dimension(:), allocatable nricore
Definition: yommp.F90:404
integer(kind=jpim) ncpec2v
Definition: yommp.F90:423
integer(kind=jpim), dimension(:), allocatable nptrsv
Definition: yommp.F90:333
integer(kind=jpim), dimension(:), allocatable nricomm
Definition: yommp.F90:405
integer(kind=jpim) nrirpt
Definition: yommp.F90:455
integer(kind=jpim), dimension(:), allocatable nobonl
Definition: yommp.F90:391
integer(kind=jpim), dimension(:), allocatable mylats
Definition: yommp.F90:359
integer(kind=jpim), dimension(:), allocatable nslonl
Definition: yommp.F90:365
integer(kind=jpim), dimension(:), allocatable nrioff
Definition: yommp.F90:398
integer(kind=jpim) mysetv
Definition: yommp.F90:83
integer(kind=jpim) narob1
Definition: yommp.F90:460
logical lsplitout
Definition: yommp.F90:72
integer(kind=jpim) nroprocs
Definition: yommp.F90:461
integer(kind=jpim), dimension(:), allocatable numvmojb
Definition: yommp.F90:342
integer(kind=jpim) myproc
Definition: yommp.F90:79
integer(kind=jpim), dimension(:), allocatable nfprecvpos
Definition: yommp.F90:382
integer(kind=jpim), dimension(:), allocatable, target nlstlat
Definition: yommp.F90:351
integer(kind=jpim), dimension(:), allocatable numvmo
Definition: yommp.F90:341
integer(kind=jpim) nblkout
Definition: yommp.F90:97
integer(kind=jpim), dimension(:), allocatable nptrms
Definition: yommp.F90:330
integer(kind=jpim), dimension(:), allocatable nglobalindex
Definition: yommp.F90:353
integer(kind=jpim), dimension(:), allocatable nrisendpos
Definition: yommp.F90:400
integer(kind=jpim), dimension(:), allocatable numxpp
Definition: yommp.F90:327
integer(kind=jpim), dimension(:,:), allocatable nvmodist
Definition: yommp.F90:360
integer(kind=jpim) nptrfloff
Definition: yommp.F90:431
integer(kind=jpim) nfpspt
Definition: yommp.F90:448
integer(kind=jpim) mysetn
Definition: yommp.F90:85
integer(kind=jpim) ntpec2v
Definition: yommp.F90:424
integer(kind=jpim), dimension(:), allocatable nrisendptr
Definition: yommp.F90:402
integer(kind=jpim), dimension(:), allocatable mylevs
Definition: yommp.F90:343
integer(kind=jpim) nfrstloff
Definition: yommp.F90:427
integer(kind=jpim) nwrtout
Definition: yommp.F90:96
integer(kind=jpim), dimension(:), allocatable nprocm
Definition: yommp.F90:328
integer(kind=jpim) nrompbufsz
Definition: yommp.F90:462
integer(kind=jpim) nafpb1
Definition: yommp.F90:444
integer(kind=jpim), dimension(:), allocatable nptrsvf
Definition: yommp.F90:336
integer(kind=jpim), dimension(:), allocatable nrocomm
Definition: yommp.F90:418
integer(kind=jpim), dimension(:), allocatable nrorecvptr
Definition: yommp.F90:416
integer(kind=jpim), dimension(:), allocatable nptrll
Definition: yommp.F90:340
logical, dimension(:), allocatable lsplitlat
Definition: yommp.F90:357
integer(kind=jpim) narib1
Definition: yommp.F90:452
integer(kind=jpim), dimension(:), allocatable npsurf
Definition: yommp.F90:344
integer(kind=jpim) numxp
Definition: yommp.F90:420
logical limp_noolap
Definition: yommp.F90:75
integer(kind=jpim) nrispt
Definition: yommp.F90:456
integer(kind=jpim), dimension(:), allocatable nfpoff
Definition: yommp.F90:379
logical leq_regions
Definition: yommp.F90:71
integer(kind=jpim), dimension(:), allocatable nslsendpos
Definition: yommp.F90:368
integer(kind=jpim) ncombflen
Definition: yommp.F90:432
integer(kind=jpim) mysetb
Definition: yommp.F90:81
integer(kind=jpim), dimension(:), allocatable nrosta
Definition: yommp.F90:409
integer(kind=jpim), dimension(:), allocatable nroonl
Definition: yommp.F90:410
integer(kind=jpim), dimension(:), allocatable nslrecvpos
Definition: yommp.F90:369
integer(kind=jpim), dimension(:), allocatable nptrls
Definition: yommp.F90:332
integer(kind=jpim), dimension(:), allocatable nslcomm
Definition: yommp.F90:373
integer(kind=jpim) nfldout
Definition: yommp.F90:91
integer(kind=jpim) nspec2v
Definition: yommp.F90:422
integer(kind=jpim), dimension(:), allocatable numll
Definition: yommp.F90:339
integer(kind=jpim), dimension(:), allocatable nrecvptr
Definition: yommp.F90:371
integer(kind=jpim), dimension(:), allocatable nrocore
Definition: yommp.F90:417
integer(kind=jpim), dimension(:), allocatable nglobalproc
Definition: yommp.F90:354
integer(kind=jpim), dimension(:), allocatable nfpcore
Definition: yommp.F90:385
integer(kind=jpim) myfrstactlat
Definition: yommp.F90:428
integer(kind=jpim) mylstactlat
Definition: yommp.F90:429
integer(kind=jpim) mysetm
Definition: yommp.F90:84
integer(kind=jpim), dimension(:), allocatable numpp
Definition: yommp.F90:326
integer(kind=jpim), dimension(:), allocatable nrosendpos
Definition: yommp.F90:413
integer(kind=jpim), dimension(:), allocatable nfponl
Definition: yommp.F90:378
integer(kind=jpim), dimension(:), allocatable nrirecvpos
Definition: yommp.F90:401
integer(kind=jpim), dimension(:), allocatable nptrmf
Definition: yommp.F90:337
integer(kind=jpim), dimension(:), allocatable nfpsendptr
Definition: yommp.F90:383
integer(kind=jpim), dimension(:), allocatable nfpcomm
Definition: yommp.F90:386
integer(kind=jpim) ngathout
Definition: yommp.F90:95
integer(kind=jpim), dimension(:), allocatable nptrtv
Definition: yommp.F90:335
integer(kind=jpim) mysetw
Definition: yommp.F90:82
integer(kind=jpim) nslspt
Definition: yommp.F90:440
integer(kind=jpim), dimension(:), allocatable nfpsendpos
Definition: yommp.F90:381
integer(kind=jpim) nslprocs
Definition: yommp.F90:437
integer(kind=jpim) my_region_ns
Definition: yommp.F90:86
integer(kind=jpim) nintype
Definition: yommp.F90:93
Definition: yommp.F90:1
integer(kind=jpim) nrospt
Definition: yommp.F90:464
integer(kind=jpim) nfpmpbufsz
Definition: yommp.F90:446
integer(kind=jpim) nfpprocs
Definition: yommp.F90:445
integer(kind=jpim), dimension(:), allocatable nsendptr
Definition: yommp.F90:370
integer(kind=jpim), dimension(:), allocatable nobsta
Definition: yommp.F90:390
integer(kind=jpim), dimension(:), allocatable nptrcv
Definition: yommp.F90:334
integer(kind=jpim) myseta
Definition: yommp.F90:80
integer(kind=jpim), dimension(:,:), allocatable, target nsta
Definition: yommp.F90:345
integer(kind=jpim), dimension(:), allocatable nptrlstlat
Definition: yommp.F90:348
logical limp
Definition: yommp.F90:74
integer(kind=jpim) nfldin
Definition: yommp.F90:90
integer(kind=jpim), dimension(:,:), allocatable, target nonl
Definition: yommp.F90:346
integer(kind=jpim) napsets
Definition: yommp.F90:430
integer(kind=jpim), dimension(:), allocatable nrirecvptr
Definition: yommp.F90:403
integer(kind=jpim) nslrpt
Definition: yommp.F90:439
integer(kind=jpim), dimension(:), allocatable nslcore
Definition: yommp.F90:372
integer(kind=jpim), dimension(:), allocatable nrionl
Definition: yommp.F90:397
integer(kind=jpim), dimension(:,:), allocatable ngpset2pe
Definition: yommp.F90:69
integer(kind=jpim) nbsetsp
Definition: yommp.F90:426
integer(kind=jpim) mbx_size
Definition: yommp.F90:78
integer(kind=jpim) nriprocs
Definition: yommp.F90:453
integer(kind=jpim) nslmpbufsz
Definition: yommp.F90:438
integer(kind=jpim) nstrout
Definition: yommp.F90:89
integer(kind=jpim), dimension(:,:), allocatable nslext
Definition: yommp.F90:367
integer(kind=jpim), dimension(:), allocatable nptrlat
Definition: yommp.F90:349
integer(kind=jpim), dimension(:), allocatable nallms
Definition: yommp.F90:331
integer(kind=jpim), dimension(:), allocatable nfprecvptr
Definition: yommp.F90:384
integer(kind=jpim), dimension(:), allocatable noboff
Definition: yommp.F90:392
integer(kind=jpim), dimension(:), allocatable nrorecvpos
Definition: yommp.F90:414
integer(kind=jpim), dimension(:), allocatable nspstaf
Definition: yommp.F90:338
integer(kind=jpim), dimension(:), allocatable, target nptrfrstlat
Definition: yommp.F90:347
integer(kind=jpim), dimension(:), allocatable nfpsta
Definition: yommp.F90:377
integer(kind=jpim) nrorpt
Definition: yommp.F90:463
integer(kind=jpim) nspec2vf
Definition: yommp.F90:425
integer(kind=jpim), dimension(:), allocatable nrooff
Definition: yommp.F90:411
integer, parameter jpim
Definition: parkind1.F90:13
integer(kind=jpim), dimension(:), allocatable nsloff
Definition: yommp.F90:366
integer(kind=jpim), dimension(:,:), allocatable nriext
Definition: yommp.F90:399
logical lsplit
Definition: yommp.F90:70
integer(kind=jpim), dimension(:,:), allocatable nfpext
Definition: yommp.F90:380
integer(kind=jpim), dimension(:), allocatable nprcids
Definition: yommp.F90:68
integer(kind=jpim) nslpad
Definition: yommp.F90:92
integer(kind=jpim) nstrin
Definition: yommp.F90:88
integer(kind=jpim) my_region_ew
Definition: yommp.F90:87
integer(kind=jpim), dimension(:), allocatable nrista
Definition: yommp.F90:396
integer(kind=jpim), dimension(:), allocatable numprocfp
Definition: yommp.F90:329
integer(kind=jpim), dimension(:), allocatable nbsetlev
Definition: yommp.F90:352
integer(kind=jpim), dimension(:), allocatable, target nfrstlat
Definition: yommp.F90:350
integer(kind=jpim), dimension(:), allocatable nslsta
Definition: yommp.F90:364
integer(kind=jpim) nfprpt
Definition: yommp.F90:447
integer(kind=jpim), dimension(:), allocatable nrosendptr
Definition: yommp.F90:415
integer(kind=jpim), dimension(:,:), allocatable nroext
Definition: yommp.F90:412
integer(kind=jpim), dimension(:), allocatable nlocalindex
Definition: yommp.F90:355
integer(kind=jpim) naslb1
Definition: yommp.F90:436
integer(kind=jpim) npsp
Definition: yommp.F90:421
integer(kind=jpim) nouttype
Definition: yommp.F90:94