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

Last change on this file since 756 was 756, checked in by witha, 13 years ago

last commit documented

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