source: palm/trunk/SOURCE/init_pegrid.f90 @ 217

Last change on this file since 217 was 206, checked in by raasch, 15 years ago

ocean-atmosphere coupling realized with MPI-1, adjustments in mrun, mbuild, subjob for lcxt4

  • Property svn:keywords set to Id
File size: 33.6 KB
Line 
1 SUBROUTINE init_pegrid
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Implementation of a MPI-1 coupling: added __parallel within the __mpi2 part
7! 2d-decomposition is default on SGI-ICE systems
8! ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
9! TEST OUTPUT (TO BE REMOVED) logging mpi2 ierr values
10!
11! Former revisions:
12! -----------------
13! $Id: init_pegrid.f90 206 2008-10-13 14:59:11Z letzel $
14!
15! 197 2008-09-16 15:29:03Z raasch
16! multigrid levels are limited by subdomains if mg_switch_to_pe0_level = -1,
17! nz is used instead nnz for calculating mg-levels
18! Collect on PE0 horizontal index bounds from all other PEs,
19! broadcast the id of the inflow PE (using the respective communicator)
20!
21! 114 2007-10-10 00:03:15Z raasch
22! Allocation of wall flag arrays for multigrid solver
23!
24! 108 2007-08-24 15:10:38Z letzel
25! Intercommunicator (comm_inter) and derived data type (type_xy) for
26! coupled model runs created, assign coupling_mode_remote,
27! indices nxlu and nysv are calculated (needed for non-cyclic boundary
28! conditions)
29!
30! 82 2007-04-16 15:40:52Z raasch
31! Cpp-directive lcmuk changed to intel_openmp_bug, setting of host on lcmuk by
32! cpp-directive removed
33!
34! 75 2007-03-22 09:54:05Z raasch
35! uxrp, vynp eliminated,
36! dirichlet/neumann changed to dirichlet/radiation, etc.,
37! poisfft_init is only called if fft-solver is switched on
38!
39! RCS Log replace by Id keyword, revision history cleaned up
40!
41! Revision 1.28  2006/04/26 13:23:32  raasch
42! lcmuk does not understand the !$ comment so a cpp-directive is required
43!
44! Revision 1.1  1997/07/24 11:15:09  raasch
45! Initial revision
46!
47!
48! Description:
49! ------------
50! Determination of the virtual processor topology (if not prescribed by the
51! user)and computation of the grid point number and array bounds of the local
52! domains.
53!------------------------------------------------------------------------------!
54
55    USE control_parameters
56    USE fft_xy
57    USE grid_variables
58    USE indices
59    USE pegrid
60    USE poisfft_mod
61    USE poisfft_hybrid_mod
62    USE statistics
63    USE transpose_indices
64
65
66    IMPLICIT NONE
67
68    INTEGER ::  gathered_size, i, id_inflow_l, id_recycling_l, ind(5), j, k, &
69                maximum_grid_level_l, mg_switch_to_pe0_level_l, mg_levels_x, &
70                mg_levels_y, mg_levels_z, nnx_y, nnx_z, nny_x, nny_z, nnz_x, &
71                nnz_y, numproc_sqr, nx_total, nxl_l, nxr_l, nyn_l, nys_l,    &
72                nzb_l, nzt_l, omp_get_num_threads, subdomain_size
73
74    INTEGER, DIMENSION(:), ALLOCATABLE ::  ind_all, nxlf, nxrf, nynf, nysf
75
76    LOGICAL ::  found
77
78!
79!-- Get the number of OpenMP threads
80    !$OMP PARALLEL
81#if defined( __intel_openmp_bug )
82    threads_per_task = omp_get_num_threads()
83#else
84!$  threads_per_task = omp_get_num_threads()
85#endif
86    !$OMP END PARALLEL
87
88
89#if defined( __parallel )
90!
91!-- Determine the processor topology or check it, if prescribed by the user
92    IF ( npex == -1  .AND.  npey == -1 )  THEN
93
94!
95!--    Automatic determination of the topology
96!--    The default on SMP- and cluster-hosts is a 1d-decomposition along x
97       IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'      .OR. &
98            ( host(1:2) == 'lc'  .AND.  host(3:5) /= 'sgi' )  .OR. &
99             host(1:3) == 'dec' )  THEN
100
101          pdims(1) = numprocs
102          pdims(2) = 1
103
104       ELSE
105
106          numproc_sqr = SQRT( REAL( numprocs ) )
107          pdims(1)    = MAX( numproc_sqr , 1 )
108          DO  WHILE ( MOD( numprocs , pdims(1) ) /= 0 )
109             pdims(1) = pdims(1) - 1
110          ENDDO
111          pdims(2) = numprocs / pdims(1)
112
113       ENDIF
114
115    ELSEIF ( npex /= -1  .AND.  npey /= -1 )  THEN
116
117!
118!--    Prescribed by user. Number of processors on the prescribed topology
119!--    must be equal to the number of PEs available to the job
120       IF ( ( npex * npey ) /= numprocs )  THEN
121          PRINT*, '+++ init_pegrid:'
122          PRINT*, '    number of PEs of the prescribed topology (', npex*npey, &
123                      ') does not match the number of PEs available to the ',  &
124                      'job (', numprocs, ')'
125          CALL local_stop
126       ENDIF
127       pdims(1) = npex
128       pdims(2) = npey
129
130    ELSE
131!
132!--    If the processor topology is prescribed by the user, the number of
133!--    PEs must be given in both directions
134       PRINT*, '+++ init_pegrid:'
135       PRINT*, '    if the processor topology is prescribed by the user, ',   &
136                    'both values of "npex" and "npey" must be given in the ', &
137                    'NAMELIST-parameter file'
138       CALL local_stop
139
140    ENDIF
141
142!
143!-- The hybrid solver can only be used in case of a 1d-decomposition along x
144    IF ( pdims(2) /= 1  .AND.  psolver == 'poisfft_hybrid' )  THEN
145       IF ( myid == 0 )  THEN
146          PRINT*, '*** init_pegrid: psolver = "poisfft_hybrid" can only be'
147          PRINT*, '                 used in case of a 1d-decomposition along x'
148       ENDIF
149    ENDIF
150
151!
152!-- If necessary, set horizontal boundary conditions to non-cyclic
153    IF ( bc_lr /= 'cyclic' )  cyclic(1) = .FALSE.
154    IF ( bc_ns /= 'cyclic' )  cyclic(2) = .FALSE.
155
156!
157!-- Create the virtual processor grid
158    CALL MPI_CART_CREATE( comm_palm, ndim, pdims, cyclic, reorder, &
159                          comm2d, ierr )
160    CALL MPI_COMM_RANK( comm2d, myid, ierr )
161    WRITE (myid_char,'(''_'',I4.4)')  myid
162
163    CALL MPI_CART_COORDS( comm2d, myid, ndim, pcoord, ierr )
164    CALL MPI_CART_SHIFT( comm2d, 0, 1, pleft, pright, ierr )
165    CALL MPI_CART_SHIFT( comm2d, 1, 1, psouth, pnorth, ierr )
166
167!
168!-- Determine sub-topologies for transpositions
169!-- Transposition from z to x:
170    remain_dims(1) = .TRUE.
171    remain_dims(2) = .FALSE.
172    CALL MPI_CART_SUB( comm2d, remain_dims, comm1dx, ierr )
173    CALL MPI_COMM_RANK( comm1dx, myidx, ierr )
174!
175!-- Transposition from x to y
176    remain_dims(1) = .FALSE.
177    remain_dims(2) = .TRUE.
178    CALL MPI_CART_SUB( comm2d, remain_dims, comm1dy, ierr )
179    CALL MPI_COMM_RANK( comm1dy, myidy, ierr )
180
181
182!
183!-- Find a grid (used for array d) which will match the transposition demands
184    IF ( grid_matching == 'strict' )  THEN
185
186       nxa = nx;  nya = ny;  nza = nz
187
188    ELSE
189
190       found = .FALSE.
191   xn: DO  nxa = nx, 2*nx
192!
193!--       Meet conditions for nx
194          IF ( MOD( nxa+1, pdims(1) ) /= 0 .OR. &
195               MOD( nxa+1, pdims(2) ) /= 0 )  CYCLE xn
196
197      yn: DO  nya = ny, 2*ny
198!
199!--          Meet conditions for ny
200             IF ( MOD( nya+1, pdims(2) ) /= 0 .OR. &
201                  MOD( nya+1, pdims(1) ) /= 0 )  CYCLE yn
202
203
204         zn: DO  nza = nz, 2*nz
205!
206!--             Meet conditions for nz
207                IF ( ( MOD( nza, pdims(1) ) /= 0  .AND.  pdims(1) /= 1  .AND. &
208                       pdims(2) /= 1 )  .OR.                                  &
209                     ( MOD( nza, pdims(2) ) /= 0  .AND.  dt_dosp /= 9999999.9 &
210                     ) )  THEN
211                   CYCLE zn
212                ELSE
213                   found = .TRUE.
214                   EXIT xn
215                ENDIF
216
217             ENDDO zn
218
219          ENDDO yn
220
221       ENDDO xn
222
223       IF ( .NOT. found )  THEN
224          IF ( myid == 0 )  THEN
225             PRINT*,'+++ init_pegrid: no matching grid for transpositions found'
226          ENDIF
227          CALL local_stop
228       ENDIF
229
230    ENDIF
231
232!
233!-- Calculate array bounds in x-direction for every PE.
234!-- The last PE along x may get less grid points than the others
235    ALLOCATE( nxlf(0:pdims(1)-1), nxrf(0:pdims(1)-1), nynf(0:pdims(2)-1), &
236              nysf(0:pdims(2)-1), nnx_pe(0:pdims(1)-1), nny_pe(0:pdims(2)-1) )
237
238    IF ( MOD( nxa+1 , pdims(1) ) /= 0 )  THEN
239       IF ( myid == 0 )  THEN
240          PRINT*,'+++ x-direction:  gridpoint number (',nx+1,') is not an'
241          PRINT*,'                  integral divisor of the number of proces', &
242                                   &'sors (', pdims(1),')'
243       ENDIF
244       CALL local_stop
245    ELSE
246       nnx  = ( nxa + 1 ) / pdims(1)
247       IF ( nnx*pdims(1) - ( nx + 1) > nnx )  THEN
248          IF ( myid == 0 )  THEN
249             PRINT*,'+++ x-direction: nx does not match the requirements ', &
250                         'given by the number of PEs'
251             PRINT*,'                 used'
252             PRINT*,'    please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
253                         - ( nx + 1 ) ) ), ' instead of nx =', nx
254          ENDIF
255          CALL local_stop
256       ENDIF
257    ENDIF   
258
259!
260!-- Left and right array bounds, number of gridpoints
261    DO  i = 0, pdims(1)-1
262       nxlf(i)   = i * nnx
263       nxrf(i)   = ( i + 1 ) * nnx - 1
264       nnx_pe(i) = MIN( nx, nxrf(i) ) - nxlf(i) + 1
265    ENDDO
266
267!
268!-- Calculate array bounds in y-direction for every PE.
269    IF ( MOD( nya+1 , pdims(2) ) /= 0 )  THEN
270       IF ( myid == 0 )  THEN
271          PRINT*,'+++ y-direction:  gridpoint number (',ny+1,') is not an'
272          PRINT*,'                  integral divisor of the number of proces', &
273                                   &'sors (', pdims(2),')'
274       ENDIF
275       CALL local_stop
276    ELSE
277       nny  = ( nya + 1 ) / pdims(2)
278       IF ( nny*pdims(2) - ( ny + 1) > nny )  THEN
279          IF ( myid == 0 )  THEN
280             PRINT*,'+++ x-direction: nx does not match the requirements ', &
281                         'given by the number of PEs'
282             PRINT*,'                 used'
283             PRINT*,'    please use nx = ', nx - ( pdims(1) - ( nnx*pdims(1) &
284                         - ( nx + 1 ) ) ), ' instead of nx =', nx
285          ENDIF
286          CALL local_stop
287       ENDIF
288    ENDIF   
289
290!
291!-- South and north array bounds
292    DO  j = 0, pdims(2)-1
293       nysf(j)   = j * nny
294       nynf(j)   = ( j + 1 ) * nny - 1
295       nny_pe(j) = MIN( ny, nynf(j) ) - nysf(j) + 1
296    ENDDO
297
298!
299!-- Local array bounds of the respective PEs
300    nxl  = nxlf(pcoord(1))
301    nxra = nxrf(pcoord(1))
302    nxr  = MIN( nx, nxra )
303    nys  = nysf(pcoord(2))
304    nyna = nynf(pcoord(2))
305    nyn  = MIN( ny, nyna )
306    nzb  = 0
307    nzta = nza
308    nzt  = MIN( nz, nzta )
309    nnz  = nza
310
311!
312!-- Calculate array bounds and gridpoint numbers for the transposed arrays
313!-- (needed in the pressure solver)
314!-- For the transposed arrays, cyclic boundaries as well as top and bottom
315!-- boundaries are omitted, because they are obstructive to the transposition
316
317!
318!-- 1. transposition  z --> x
319!-- This transposition is not neccessary in case of a 1d-decomposition along x,
320!-- except that the uptream-spline method is switched on
321    IF ( pdims(2) /= 1  .OR.  momentum_advec == 'ups-scheme'  .OR. &
322         scalar_advec == 'ups-scheme' )  THEN
323
324       IF ( pdims(2) == 1  .AND. ( momentum_advec == 'ups-scheme'  .OR. &
325            scalar_advec == 'ups-scheme' ) )  THEN
326          IF ( myid == 0 )  THEN
327             PRINT*,'+++ WARNING: init_pegrid: 1d-decomposition along x ', &
328                                &'chosen but nz restrictions may occur'
329             PRINT*,'             since ups-scheme is activated'
330          ENDIF
331       ENDIF
332       nys_x  = nys
333       nyn_xa = nyna
334       nyn_x  = nyn
335       nny_x  = nny
336       IF ( MOD( nza , pdims(1) ) /= 0 )  THEN
337          IF ( myid == 0 )  THEN
338             PRINT*,'+++ transposition z --> x:'
339             PRINT*,'    nz=',nz,' is not an integral divisior of pdims(1)=', &
340                    &pdims(1)
341          ENDIF
342          CALL local_stop
343       ENDIF
344       nnz_x  = nza / pdims(1)
345       nzb_x  = 1 + myidx * nnz_x
346       nzt_xa = ( myidx + 1 ) * nnz_x
347       nzt_x  = MIN( nzt, nzt_xa )
348
349       sendrecvcount_zx = nnx * nny * nnz_x
350
351    ELSE
352!
353!---   Setting of dummy values because otherwise variables are undefined in
354!---   the next step  x --> y
355!---   WARNING: This case has still to be clarified!!!!!!!!!!!!
356       nnz_x  = 1
357       nzb_x  = 1
358       nzt_xa = 1
359       nzt_x  = 1
360       nny_x  = nny
361
362    ENDIF
363
364!
365!-- 2. transposition  x --> y
366    nnz_y  = nnz_x
367    nzb_y  = nzb_x
368    nzt_ya = nzt_xa
369    nzt_y  = nzt_x
370    IF ( MOD( nxa+1 , pdims(2) ) /= 0 )  THEN
371       IF ( myid == 0 )  THEN
372          PRINT*,'+++ transposition x --> y:'
373          PRINT*,'    nx+1=',nx+1,' is not an integral divisor of ',&
374                 &'pdims(2)=',pdims(2)
375       ENDIF
376       CALL local_stop
377    ENDIF
378    nnx_y = (nxa+1) / pdims(2)
379    nxl_y = myidy * nnx_y
380    nxr_ya = ( myidy + 1 ) * nnx_y - 1
381    nxr_y  = MIN( nx, nxr_ya )
382
383    sendrecvcount_xy = nnx_y * nny_x * nnz_y
384
385!
386!-- 3. transposition  y --> z  (ELSE:  x --> y  in case of 1D-decomposition
387!-- along x)
388    IF ( pdims(2) /= 1  .OR.  momentum_advec == 'ups-scheme'  .OR. &
389         scalar_advec == 'ups-scheme' )  THEN
390!
391!--    y --> z
392!--    This transposition is not neccessary in case of a 1d-decomposition
393!--    along x, except that the uptream-spline method is switched on
394       nnx_z  = nnx_y
395       nxl_z  = nxl_y
396       nxr_za = nxr_ya
397       nxr_z  = nxr_y
398       IF ( MOD( nya+1 , pdims(1) ) /= 0 )  THEN
399          IF ( myid == 0 )  THEN
400             PRINT*,'+++ Transposition y --> z:'
401             PRINT*,'    ny+1=',ny+1,' is not an integral divisor of ',&
402                    &'pdims(1)=',pdims(1)
403          ENDIF
404          CALL local_stop
405       ENDIF
406       nny_z  = (nya+1) / pdims(1)
407       nys_z  = myidx * nny_z
408       nyn_za = ( myidx + 1 ) * nny_z - 1
409       nyn_z  = MIN( ny, nyn_za )
410
411       sendrecvcount_yz = nnx_y * nny_z * nnz_y
412
413    ELSE
414!
415!--    x --> y. This condition must be fulfilled for a 1D-decomposition along x
416       IF ( MOD( nya+1 , pdims(1) ) /= 0 )  THEN
417          IF ( myid == 0 )  THEN
418             PRINT*,'+++ Transposition x --> y:'
419             PRINT*,'    ny+1=',ny+1,' is not an integral divisor of ',&
420                    &'pdims(1)=',pdims(1)
421          ENDIF
422          CALL local_stop
423       ENDIF
424
425    ENDIF
426
427!
428!-- Indices for direct transpositions z --> y (used for calculating spectra)
429    IF ( dt_dosp /= 9999999.9 )  THEN
430       IF ( MOD( nza, pdims(2) ) /= 0 )  THEN
431          IF ( myid == 0 )  THEN
432             PRINT*,'+++ Direct transposition z --> y (needed for spectra):'
433             PRINT*,'    nz=',nz,' is not an integral divisor of ',&
434                    &'pdims(2)=',pdims(2)
435          ENDIF
436          CALL local_stop
437       ELSE
438          nxl_yd  = nxl
439          nxr_yda = nxra
440          nxr_yd  = nxr
441          nzb_yd  = 1 + myidy * ( nza / pdims(2) )
442          nzt_yda = ( myidy + 1 ) * ( nza / pdims(2) )
443          nzt_yd  = MIN( nzt, nzt_yda )
444
445          sendrecvcount_zyd = nnx * nny * ( nza / pdims(2) )
446       ENDIF
447    ENDIF
448
449!
450!-- Indices for direct transpositions y --> x (they are only possible in case
451!-- of a 1d-decomposition along x)
452    IF ( pdims(2) == 1 )  THEN
453       nny_x  = nny / pdims(1)
454       nys_x  = myid * nny_x
455       nyn_xa = ( myid + 1 ) * nny_x - 1
456       nyn_x  = MIN( ny, nyn_xa )
457       nzb_x  = 1
458       nzt_xa = nza
459       nzt_x  = nz
460       sendrecvcount_xy = nnx * nny_x * nza
461    ENDIF
462
463!
464!-- Indices for direct transpositions x --> y (they are only possible in case
465!-- of a 1d-decomposition along y)
466    IF ( pdims(1) == 1 )  THEN
467       nnx_y  = nnx / pdims(2)
468       nxl_y  = myid * nnx_y
469       nxr_ya = ( myid + 1 ) * nnx_y - 1
470       nxr_y  = MIN( nx, nxr_ya )
471       nzb_y  = 1
472       nzt_ya = nza
473       nzt_y  = nz
474       sendrecvcount_xy = nnx_y * nny * nza
475    ENDIF
476
477!
478!-- Arrays for storing the array bounds are needed any more
479    DEALLOCATE( nxlf , nxrf , nynf , nysf )
480
481!
482!-- Collect index bounds from other PEs (to be written to restart file later)
483    ALLOCATE( hor_index_bounds(4,0:numprocs-1) )
484
485    IF ( myid == 0 )  THEN
486
487       hor_index_bounds(1,0) = nxl
488       hor_index_bounds(2,0) = nxr
489       hor_index_bounds(3,0) = nys
490       hor_index_bounds(4,0) = nyn
491
492!
493!--    Receive data from all other PEs
494       DO  i = 1, numprocs-1
495          CALL MPI_RECV( ibuf, 4, MPI_INTEGER, i, MPI_ANY_TAG, comm2d, status, &
496                         ierr )
497          hor_index_bounds(:,i) = ibuf(1:4)
498       ENDDO
499
500    ELSE
501!
502!--    Send index bounds to PE0
503       ibuf(1) = nxl
504       ibuf(2) = nxr
505       ibuf(3) = nys
506       ibuf(4) = nyn
507       CALL MPI_SEND( ibuf, 4, MPI_INTEGER, 0, myid, comm2d, ierr )
508
509    ENDIF
510
511#if defined( __print )
512!
513!-- Control output
514    IF ( myid == 0 )  THEN
515       PRINT*, '*** processor topology ***'
516       PRINT*, ' '
517       PRINT*, 'myid   pcoord    left right  south north  idx idy   nxl: nxr',&
518               &'   nys: nyn'
519       PRINT*, '------------------------------------------------------------',&
520               &'-----------'
521       WRITE (*,1000)  0, pcoord(1), pcoord(2), pleft, pright, psouth, pnorth, &
522                       myidx, myidy, nxl, nxr, nys, nyn
5231000   FORMAT (I4,2X,'(',I3,',',I3,')',3X,I4,2X,I4,3X,I4,2X,I4,2X,I3,1X,I3, &
524               2(2X,I4,':',I4))
525
526!
527!--    Receive data from the other PEs
528       DO  i = 1,numprocs-1
529          CALL MPI_RECV( ibuf, 12, MPI_INTEGER, i, MPI_ANY_TAG, comm2d, status, &
530                         ierr )
531          WRITE (*,1000)  i, ( ibuf(j) , j = 1,12 )
532       ENDDO
533    ELSE
534
535!
536!--    Send data to PE0
537       ibuf(1) = pcoord(1); ibuf(2) = pcoord(2); ibuf(3) = pleft
538       ibuf(4) = pright; ibuf(5) = psouth; ibuf(6) = pnorth; ibuf(7) = myidx
539       ibuf(8) = myidy; ibuf(9) = nxl; ibuf(10) = nxr; ibuf(11) = nys
540       ibuf(12) = nyn
541       CALL MPI_SEND( ibuf, 12, MPI_INTEGER, 0, myid, comm2d, ierr )       
542    ENDIF
543#endif
544
545#if defined( __parallel )
546#if defined( __mpi2 )
547!
548!-- In case of coupled runs, get the port name on PE0 of the atmosphere model
549!-- and pass it to PE0 of the ocean model
550    IF ( myid == 0 )  THEN
551
552       IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
553
554          CALL MPI_OPEN_PORT( MPI_INFO_NULL, port_name, ierr )
555!
556!--       TEST OUTPUT (TO BE REMOVED)
557          WRITE(9,*)  TRIM( coupling_mode ),  &
558               ', ierr after MPI_OPEN_PORT: ', ierr
559          CALL LOCAL_FLUSH( 9 )
560
561          CALL MPI_PUBLISH_NAME( 'palm_coupler', MPI_INFO_NULL, port_name, &
562                                 ierr )
563!
564!--       TEST OUTPUT (TO BE REMOVED)
565          WRITE(9,*)  TRIM( coupling_mode ),  &
566               ', ierr after MPI_PUBLISH_NAME: ', ierr
567          CALL LOCAL_FLUSH( 9 )
568
569!
570!--       Write a flag file for the ocean model and the other atmosphere
571!--       processes.
572!--       There seems to be a bug in MPICH2 which causes hanging processes
573!--       in case that execution of LOOKUP_NAME is continued too early
574!--       (i.e. before the port has been created)
575          OPEN( 90, FILE='COUPLING_PORT_OPENED', FORM='FORMATTED' )
576          WRITE ( 90, '(''TRUE'')' )
577          CLOSE ( 90 )
578
579       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
580
581!
582!--       Continue only if the atmosphere model has created the port.
583!--       There seems to be a bug in MPICH2 which causes hanging processes
584!--       in case that execution of LOOKUP_NAME is continued too early
585!--       (i.e. before the port has been created)
586          INQUIRE( FILE='COUPLING_PORT_OPENED', EXIST=found )
587          DO WHILE ( .NOT. found )
588             INQUIRE( FILE='COUPLING_PORT_OPENED', EXIST=found )
589          ENDDO
590
591          CALL MPI_LOOKUP_NAME( 'palm_coupler', MPI_INFO_NULL, port_name, ierr )
592!
593!--       TEST OUTPUT (TO BE REMOVED)
594          WRITE(9,*)  TRIM( coupling_mode ),  &
595               ', ierr after MPI_LOOKUP_NAME: ', ierr
596          CALL LOCAL_FLUSH( 9 )
597
598
599       ENDIF
600
601    ENDIF
602
603!
604!-- In case of coupled runs, establish the connection between the atmosphere
605!-- and the ocean model and define the intercommunicator (comm_inter)
606    CALL MPI_BARRIER( comm2d, ierr )
607    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
608
609       print*, '... before COMM_ACCEPT'
610       CALL MPI_COMM_ACCEPT( port_name, MPI_INFO_NULL, 0, MPI_COMM_WORLD, &
611                             comm_inter, ierr )
612       print*, '--- ierr = ', ierr
613       print*, '--- comm_inter atmosphere = ', comm_inter
614
615       coupling_mode_remote = 'ocean_to_atmosphere'
616
617    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
618
619       IF ( myid == 0 )  PRINT*, '*** read: ', port_name, '  ierr = ', ierr
620       print*, '... before COMM_CONNECT'
621       CALL MPI_COMM_CONNECT( port_name, MPI_INFO_NULL, 0, MPI_COMM_WORLD, &
622                              comm_inter, ierr )
623       print*, '--- ierr = ', ierr
624       print*, '--- comm_inter ocean      = ', comm_inter
625
626       coupling_mode_remote = 'atmosphere_to_ocean'
627
628    ENDIF
629#endif
630
631!
632!-- In case of coupled runs, create a new MPI derived datatype for the
633!-- exchange of surface (xy) data .
634!-- Gridpoint number for the exchange of ghost points (xy-plane)
635    ngp_xy  = ( nxr - nxl + 3 ) * ( nyn - nys + 3 )
636
637!
638!-- Define a new MPI derived datatype for the exchange of ghost points in
639!-- y-direction for 2D-arrays (line)
640    CALL MPI_TYPE_VECTOR( ngp_xy, 1, nzt-nzb+2, MPI_REAL, type_xy, ierr )
641    CALL MPI_TYPE_COMMIT( type_xy, ierr )
642#endif
643
644#else
645
646!
647!-- Array bounds when running on a single PE (respectively a non-parallel
648!-- machine)
649    nxl  = 0
650    nxr  = nx
651    nxra = nx
652    nnx  = nxr - nxl + 1
653    nys  = 0
654    nyn  = ny
655    nyna = ny
656    nny  = nyn - nys + 1
657    nzb  = 0
658    nzt  = nz
659    nzta = nz
660    nnz  = nz
661
662    ALLOCATE( hor_index_bounds(4,0:0) )
663    hor_index_bounds(1,0) = nxl
664    hor_index_bounds(2,0) = nxr
665    hor_index_bounds(3,0) = nys
666    hor_index_bounds(4,0) = nyn
667
668!
669!-- Array bounds for the pressure solver (in the parallel code, these bounds
670!-- are the ones for the transposed arrays)
671    nys_x  = nys
672    nyn_x  = nyn
673    nyn_xa = nyn
674    nzb_x  = nzb + 1
675    nzt_x  = nzt
676    nzt_xa = nzt
677
678    nxl_y  = nxl
679    nxr_y  = nxr
680    nxr_ya = nxr
681    nzb_y  = nzb + 1
682    nzt_y  = nzt
683    nzt_ya = nzt
684
685    nxl_z  = nxl
686    nxr_z  = nxr
687    nxr_za = nxr
688    nys_z  = nys
689    nyn_z  = nyn
690    nyn_za = nyn
691
692#endif
693
694!
695!-- Calculate number of grid levels necessary for the multigrid poisson solver
696!-- as well as the gridpoint indices on each level
697    IF ( psolver == 'multigrid' )  THEN
698
699!
700!--    First calculate number of possible grid levels for the subdomains
701       mg_levels_x = 1
702       mg_levels_y = 1
703       mg_levels_z = 1
704
705       i = nnx
706       DO WHILE ( MOD( i, 2 ) == 0  .AND.  i /= 2 )
707          i = i / 2
708          mg_levels_x = mg_levels_x + 1
709       ENDDO
710
711       j = nny
712       DO WHILE ( MOD( j, 2 ) == 0  .AND.  j /= 2 )
713          j = j / 2
714          mg_levels_y = mg_levels_y + 1
715       ENDDO
716
717       k = nz    ! do not use nnz because it might be > nz due to transposition
718                 ! requirements
719       DO WHILE ( MOD( k, 2 ) == 0  .AND.  k /= 2 )
720          k = k / 2
721          mg_levels_z = mg_levels_z + 1
722       ENDDO
723
724       maximum_grid_level = MIN( mg_levels_x, mg_levels_y, mg_levels_z )
725
726!
727!--    Find out, if the total domain allows more levels. These additional
728!--    levels are processed on PE0 only.
729       IF ( numprocs > 1  .AND.  mg_switch_to_pe0_level /= -1 )  THEN
730          IF ( mg_levels_z > MIN( mg_levels_x, mg_levels_y ) )  THEN
731             mg_switch_to_pe0_level_l = maximum_grid_level
732
733             mg_levels_x = 1
734             mg_levels_y = 1
735
736             i = nx+1
737             DO WHILE ( MOD( i, 2 ) == 0  .AND.  i /= 2 )
738                i = i / 2
739                mg_levels_x = mg_levels_x + 1
740             ENDDO
741
742             j = ny+1
743             DO WHILE ( MOD( j, 2 ) == 0  .AND.  j /= 2 )
744                j = j / 2
745                mg_levels_y = mg_levels_y + 1
746             ENDDO
747
748             maximum_grid_level_l = MIN( mg_levels_x, mg_levels_y, mg_levels_z )
749
750             IF ( maximum_grid_level_l > mg_switch_to_pe0_level_l )  THEN
751                mg_switch_to_pe0_level_l = maximum_grid_level_l - &
752                                           mg_switch_to_pe0_level_l + 1
753             ELSE
754                mg_switch_to_pe0_level_l = 0
755             ENDIF
756          ELSE
757             mg_switch_to_pe0_level_l = 0
758             maximum_grid_level_l = maximum_grid_level
759          ENDIF
760
761!
762!--       Use switch level calculated above only if it is not pre-defined
763!--       by user
764          IF ( mg_switch_to_pe0_level == 0 )  THEN
765
766             IF ( mg_switch_to_pe0_level_l /= 0 )  THEN
767                mg_switch_to_pe0_level = mg_switch_to_pe0_level_l
768                maximum_grid_level     = maximum_grid_level_l
769             ENDIF
770
771          ELSE
772!
773!--          Check pre-defined value and reset to default, if neccessary
774             IF ( mg_switch_to_pe0_level < mg_switch_to_pe0_level_l  .OR.  &
775                  mg_switch_to_pe0_level >= maximum_grid_level_l )  THEN
776                IF ( myid == 0 )  THEN
777                   PRINT*, '+++ WARNING init_pegrid: mg_switch_to_pe0_level ', &
778                               'out of range and reset to default (=0)'
779                ENDIF
780                mg_switch_to_pe0_level = 0
781             ELSE
782!
783!--             Use the largest number of possible levels anyway and recalculate
784!--             the switch level to this largest number of possible values
785                maximum_grid_level = maximum_grid_level_l
786
787             ENDIF
788          ENDIF
789
790       ENDIF
791
792       ALLOCATE( grid_level_count(maximum_grid_level),                   &
793                 nxl_mg(maximum_grid_level), nxr_mg(maximum_grid_level), &
794                 nyn_mg(maximum_grid_level), nys_mg(maximum_grid_level), &
795                 nzt_mg(maximum_grid_level) )
796
797       grid_level_count = 0
798       nxl_l = nxl; nxr_l = nxr; nys_l = nys; nyn_l = nyn; nzt_l = nzt
799
800       DO  i = maximum_grid_level, 1 , -1
801
802          IF ( i == mg_switch_to_pe0_level )  THEN
803#if defined( __parallel )
804!
805!--          Save the grid size of the subdomain at the switch level, because
806!--          it is needed in poismg.
807!--          Array bounds of the local subdomain grids are gathered on PE0
808             ind(1) = nxl_l; ind(2) = nxr_l
809             ind(3) = nys_l; ind(4) = nyn_l
810             ind(5) = nzt_l
811             ALLOCATE( ind_all(5*numprocs), mg_loc_ind(5,0:numprocs-1) )
812             CALL MPI_ALLGATHER( ind, 5, MPI_INTEGER, ind_all, 5, &
813                                 MPI_INTEGER, comm2d, ierr )
814             DO  j = 0, numprocs-1
815                DO  k = 1, 5
816                   mg_loc_ind(k,j) = ind_all(k+j*5)
817                ENDDO
818             ENDDO
819             DEALLOCATE( ind_all )
820!
821!--          Calculate the grid size of the total domain gathered on PE0
822             nxr_l = ( nxr_l-nxl_l+1 ) * pdims(1) - 1
823             nxl_l = 0
824             nyn_l = ( nyn_l-nys_l+1 ) * pdims(2) - 1
825             nys_l = 0
826!
827!--          The size of this gathered array must not be larger than the
828!--          array tend, which is used in the multigrid scheme as a temporary
829!--          array
830             subdomain_size = ( nxr - nxl + 3 )     * ( nyn - nys + 3 )     * &
831                              ( nzt - nzb + 2 )
832             gathered_size  = ( nxr_l - nxl_l + 3 ) * ( nyn_l - nys_l + 3 ) * &
833                              ( nzt_l - nzb + 2 )
834
835             IF ( gathered_size > subdomain_size )  THEN
836                IF ( myid == 0 )  THEN
837                   PRINT*, '+++ init_pegrid: not enough memory for storing ', &
838                               'gathered multigrid data on PE0'
839                ENDIF
840                CALL local_stop
841             ENDIF
842#else
843             PRINT*, '+++ init_pegrid: multigrid gather/scatter impossible ', &
844                          'in non parallel mode'
845             CALL local_stop
846#endif
847          ENDIF
848
849          nxl_mg(i) = nxl_l
850          nxr_mg(i) = nxr_l
851          nys_mg(i) = nys_l
852          nyn_mg(i) = nyn_l
853          nzt_mg(i) = nzt_l
854
855          nxl_l = nxl_l / 2 
856          nxr_l = nxr_l / 2
857          nys_l = nys_l / 2 
858          nyn_l = nyn_l / 2 
859          nzt_l = nzt_l / 2 
860       ENDDO
861
862    ELSE
863
864       maximum_grid_level = 1
865
866    ENDIF
867
868    grid_level = maximum_grid_level
869
870#if defined( __parallel )
871!
872!-- Gridpoint number for the exchange of ghost points (y-line for 2D-arrays)
873    ngp_y  = nyn - nys + 1
874
875!
876!-- Define a new MPI derived datatype for the exchange of ghost points in
877!-- y-direction for 2D-arrays (line)
878    CALL MPI_TYPE_VECTOR( nxr-nxl+3, 1, ngp_y+2, MPI_REAL, type_x, ierr )
879    CALL MPI_TYPE_COMMIT( type_x, ierr )
880    CALL MPI_TYPE_VECTOR( nxr-nxl+3, 1, ngp_y+2, MPI_INTEGER, type_x_int, ierr )
881    CALL MPI_TYPE_COMMIT( type_x_int, ierr )
882
883!
884!-- Calculate gridpoint numbers for the exchange of ghost points along x
885!-- (yz-plane for 3D-arrays) and define MPI derived data type(s) for the
886!-- exchange of ghost points in y-direction (xz-plane).
887!-- Do these calculations for the model grid and (if necessary) also
888!-- for the coarser grid levels used in the multigrid method
889    ALLOCATE ( ngp_yz(maximum_grid_level), type_xz(maximum_grid_level) )
890
891    nxl_l = nxl; nxr_l = nxr; nys_l = nys; nyn_l = nyn; nzb_l = nzb; nzt_l = nzt
892         
893    DO i = maximum_grid_level, 1 , -1
894       ngp_yz(i) = (nzt_l - nzb_l + 2) * (nyn_l - nys_l + 3)
895
896       CALL MPI_TYPE_VECTOR( nxr_l-nxl_l+3, nzt_l-nzb_l+2, ngp_yz(i), &
897                             MPI_REAL, type_xz(i), ierr )
898       CALL MPI_TYPE_COMMIT( type_xz(i), ierr )
899
900       nxl_l = nxl_l / 2 
901       nxr_l = nxr_l / 2
902       nys_l = nys_l / 2 
903       nyn_l = nyn_l / 2 
904       nzt_l = nzt_l / 2 
905    ENDDO
906#endif
907
908#if defined( __parallel )
909!
910!-- Setting of flags for inflow/outflow conditions in case of non-cyclic
911!-- horizontal boundary conditions.
912    IF ( pleft == MPI_PROC_NULL )  THEN
913       IF ( bc_lr == 'dirichlet/radiation' )  THEN
914          inflow_l  = .TRUE.
915       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
916          outflow_l = .TRUE.
917       ENDIF
918    ENDIF
919
920    IF ( pright == MPI_PROC_NULL )  THEN
921       IF ( bc_lr == 'dirichlet/radiation' )  THEN
922          outflow_r = .TRUE.
923       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
924          inflow_r  = .TRUE.
925       ENDIF
926    ENDIF
927
928    IF ( psouth == MPI_PROC_NULL )  THEN
929       IF ( bc_ns == 'dirichlet/radiation' )  THEN
930          outflow_s = .TRUE.
931       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
932          inflow_s  = .TRUE.
933       ENDIF
934    ENDIF
935
936    IF ( pnorth == MPI_PROC_NULL )  THEN
937       IF ( bc_ns == 'dirichlet/radiation' )  THEN
938          inflow_n  = .TRUE.
939       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
940          outflow_n = .TRUE.
941       ENDIF
942    ENDIF
943
944!
945!-- Broadcast the id of the inflow PE
946    IF ( inflow_l )  THEN
947       id_inflow_l = myidx
948    ELSE
949       id_inflow_l = 0
950    ENDIF
951    CALL MPI_ALLREDUCE( id_inflow_l, id_inflow, 1, MPI_INTEGER, MPI_SUM, &
952                        comm1dx, ierr )
953
954!
955!-- Broadcast the id of the recycling plane
956!-- WARNING: needs to be adjusted in case of inflows other than from left side!
957    IF ( ( recycling_width / dx ) >= nxl  .AND.  ( recycling_width / dx ) <= nxr ) &
958    THEN
959       id_recycling_l = myidx
960    ELSE
961       id_recycling_l = 0
962    ENDIF
963    CALL MPI_ALLREDUCE( id_recycling_l, id_recycling, 1, MPI_INTEGER, MPI_SUM, &
964                        comm1dx, ierr )
965
966#else
967    IF ( bc_lr == 'dirichlet/radiation' )  THEN
968       inflow_l  = .TRUE.
969       outflow_r = .TRUE.
970    ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
971       outflow_l = .TRUE.
972       inflow_r  = .TRUE.
973    ENDIF
974
975    IF ( bc_ns == 'dirichlet/radiation' )  THEN
976       inflow_n  = .TRUE.
977       outflow_s = .TRUE.
978    ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
979       outflow_n = .TRUE.
980       inflow_s  = .TRUE.
981    ENDIF
982#endif
983!
984!-- At the outflow, u or v, respectively, have to be calculated for one more
985!-- grid point.
986    IF ( outflow_l )  THEN
987       nxlu = nxl + 1
988    ELSE
989       nxlu = nxl
990    ENDIF
991    IF ( outflow_s )  THEN
992       nysv = nys + 1
993    ELSE
994       nysv = nys
995    ENDIF
996
997    IF ( psolver == 'poisfft_hybrid' )  THEN
998       CALL poisfft_hybrid_ini
999    ELSEIF ( psolver == 'poisfft' )  THEN
1000       CALL poisfft_init
1001    ENDIF
1002
1003!
1004!-- Allocate wall flag arrays used in the multigrid solver
1005    IF ( psolver == 'multigrid' )  THEN
1006
1007       DO  i = maximum_grid_level, 1, -1
1008
1009           SELECT CASE ( i )
1010
1011              CASE ( 1 )
1012                 ALLOCATE( wall_flags_1(nzb:nzt_mg(i)+1,         &
1013                                        nys_mg(i)-1:nyn_mg(i)+1, &
1014                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1015
1016              CASE ( 2 )
1017                 ALLOCATE( wall_flags_2(nzb:nzt_mg(i)+1,         &
1018                                        nys_mg(i)-1:nyn_mg(i)+1, &
1019                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1020
1021              CASE ( 3 )
1022                 ALLOCATE( wall_flags_3(nzb:nzt_mg(i)+1,         &
1023                                        nys_mg(i)-1:nyn_mg(i)+1, &
1024                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1025
1026              CASE ( 4 )
1027                 ALLOCATE( wall_flags_4(nzb:nzt_mg(i)+1,         &
1028                                        nys_mg(i)-1:nyn_mg(i)+1, &
1029                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1030
1031              CASE ( 5 )
1032                 ALLOCATE( wall_flags_5(nzb:nzt_mg(i)+1,         &
1033                                        nys_mg(i)-1:nyn_mg(i)+1, &
1034                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1035
1036              CASE ( 6 )
1037                 ALLOCATE( wall_flags_6(nzb:nzt_mg(i)+1,         &
1038                                        nys_mg(i)-1:nyn_mg(i)+1, &
1039                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1040
1041              CASE ( 7 )
1042                 ALLOCATE( wall_flags_7(nzb:nzt_mg(i)+1,         &
1043                                        nys_mg(i)-1:nyn_mg(i)+1, &
1044                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1045
1046              CASE ( 8 )
1047                 ALLOCATE( wall_flags_8(nzb:nzt_mg(i)+1,         &
1048                                        nys_mg(i)-1:nyn_mg(i)+1, &
1049                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1050
1051              CASE ( 9 )
1052                 ALLOCATE( wall_flags_9(nzb:nzt_mg(i)+1,         &
1053                                        nys_mg(i)-1:nyn_mg(i)+1, &
1054                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1055
1056              CASE ( 10 )
1057                 ALLOCATE( wall_flags_10(nzb:nzt_mg(i)+1,        &
1058                                        nys_mg(i)-1:nyn_mg(i)+1, &
1059                                        nxl_mg(i)-1:nxr_mg(i)+1) )
1060
1061              CASE DEFAULT
1062                 IF ( myid == 0 )  PRINT*, '+++ init_pegrid: more than 10 ', &
1063                                           ' multigrid levels'
1064                 CALL local_stop
1065
1066          END SELECT
1067
1068       ENDDO
1069
1070    ENDIF
1071
1072 END SUBROUTINE init_pegrid
Note: See TracBrowser for help on using the repository browser.