source: palm/trunk/SOURCE/init_grid.f90 @ 4342

Last change on this file since 4342 was 4340, checked in by Giersch, 4 years ago

Topography closed channel flow with symmetric boundaries implemented, ID tag in radiation module corrected

  • Property svn:keywords set to Id
File size: 122.3 KB
Line 
1!> @file init_grid.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: init_grid.f90 4340 2019-12-16 08:17:03Z Giersch $
27! Topography closed channel flow with symmetric boundaries implemented
28!
29! 4329 2019-12-10 15:46:36Z motisi
30! Renamed wall_flags_0 to wall_flags_static_0
31!
32! 4328 2019-12-09 18:53:04Z suehring
33! Minor change in nzb_max computation. Commentation added.
34!
35! 4314 2019-11-29 10:29:20Z suehring
36! Set additional topography flag 4 to mark topography grid points emerged
37! from the filtering process.
38!
39! 4294 2019-11-13 18:34:16Z suehring
40! Bugfix, always set bit 5 and 6 of wall_flags, indicating terrain- and
41! building surfaces in all  cases, in order to enable terrain-following output
42! also when no land- or urban-surface model is applied.
43!
44! 4265 2019-10-15 16:16:24Z suehring
45! Bugfix for last commit, exchange oro_max variable only when it is allocated
46! (not necessarily the case when topography is input from ASCII file).
47!
48! 4245 2019-09-30 08:40:37Z pavelkrc
49! Store oro_max (building z-offset) in 2D for building surfaces
50!
51! 4189 2019-08-26 16:19:38Z suehring
52! - Add check for proper setting of namelist parameter topography
53! - Set flag to indicate land surfaces in case no topography is provided
54!
55! 4182 2019-08-22 15:20:23Z scharf
56! Corrected "Former revisions" section
57!
58! 4168 2019-08-16 13:50:17Z suehring
59! Pre-calculate topography top index and store it on an array (replaces former
60! functions get_topography_top_index)
61!
62! 4159 2019-08-15 13:31:35Z suehring
63! Revision of topography processing. This was not consistent between 2D and 3D
64! buildings.
65!
66! 4144 2019-08-06 09:11:47Z raasch
67! relational operators .EQ., .NE., etc. replaced by ==, /=, etc.
68!
69! 4115 2019-07-24 12:50:49Z suehring
70! Bugfix in setting near-surface flag 24, inidicating wall-bounded grid points
71!
72! 4110 2019-07-22 17:05:21Z suehring
73! - Separate initialization of advection flags for momentum and scalars.
74! - Change subroutine interface for ws_init_flags_scalar to pass boundary flags
75!
76! 4109 2019-07-22 17:00:34Z suehring
77! Fix bad commit
78!
79! 3926 2019-04-23 12:56:42Z suehring
80! Minor bugfix in building mapping when all building IDs in the model domain
81! are missing
82!
83! 3857 2019-04-03 13:00:16Z knoop
84! In projection of non-building 3D objects onto numerical grid remove
85! dependency on building_type
86!
87! 3763 2019-02-25 17:33:49Z suehring
88! Replace work-around for ghost point exchange of 1-byte arrays with specific
89! routine as already done in other routines
90!
91! 3761 2019-02-25 15:31:42Z raasch
92! unused variables removed
93!
94! 3661 2019-01-08 18:22:50Z suehring
95! Remove setting of nzb_max to nzt at non-cyclic boundary PEs, instead,
96! order degradation of advection scheme is handeled directly in advec_ws
97!
98! 3655 2019-01-07 16:51:22Z knoop
99! Comment added
100!
101! Revision 1.1  1997/08/11 06:17:45  raasch
102! Initial revision (Testversion)
103!
104!
105! Description:
106! -----------------------------------------------------------------------------!
107!> Creating grid depending constants
108!> @todo: Rearrange topo flag list
109!> @todo: reference 3D buildings on top of orography is not tested and may need
110!>        further improvement for steep slopes
111!> @todo: Use more advanced setting of building type at filled holes
112!------------------------------------------------------------------------------!
113 SUBROUTINE init_grid
114 
115    USE advec_ws,                                                              &
116        ONLY:  ws_init_flags_momentum, ws_init_flags_scalar
117
118    USE arrays_3d,                                                             &
119        ONLY:  dd2zu, ddzu, ddzu_pres, ddzw, dzu, dzw, x, xu, y, yv, zu, zw
120       
121    USE control_parameters,                                                    &
122        ONLY:  bc_lr_cyc, bc_ns_cyc,                                           &
123               bc_dirichlet_l,                                                 &
124               bc_dirichlet_n,                                                 &
125               bc_dirichlet_r,                                                 &
126               bc_dirichlet_s,                                                 &
127               bc_radiation_l,                                                 &
128               bc_radiation_n,                                                 &
129               bc_radiation_r,                                                 &
130               bc_radiation_s,                                                 &
131               constant_flux_layer, dz, dz_max, dz_stretch_factor,             &
132               dz_stretch_factor_array, dz_stretch_level, dz_stretch_level_end,&
133               dz_stretch_level_end_index, dz_stretch_level_start_index,       &
134               dz_stretch_level_start, ibc_uv_b, message_string,               &
135               momentum_advec, number_stretch_level_end,                       &
136               number_stretch_level_start, ocean_mode, psolver, scalar_advec,  &
137               symmetry_flag, topography, use_surface_fluxes
138         
139    USE grid_variables,                                                        &
140        ONLY:  ddx, ddx2, ddy, ddy2, dx, dx2, dy, dy2, zu_s_inner, zw_w_inner
141       
142    USE indices,                                                               &
143        ONLY:  advc_flags_m,                                                   &
144               advc_flags_s,                                                   &
145               nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
146               nzb, nzb_diff, nzb_diff_s_inner, nzb_diff_s_outer,              &
147               nzb_max, nzb_s_inner, nzb_s_outer, nzb_u_inner,                 &
148               nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner,             &
149               nzb_w_outer, nzt, topo_top_ind, topo_min_level
150   
151    USE kinds
152
153    USE pegrid
154
155    USE poismg_noopt_mod
156
157    USE surface_mod,                                                           &
158        ONLY:  init_bc
159
160    USE vertical_nesting_mod,                                                  &
161        ONLY:  vnested, vnest_init_grid
162
163    IMPLICIT NONE
164
165    INTEGER(iwp) ::  i             !< index variable along x
166    INTEGER(iwp) ::  j             !< index variable along y
167    INTEGER(iwp) ::  k             !< index variable along z
168    INTEGER(iwp) ::  k_top         !< topography top index on local PE
169    INTEGER(iwp) ::  n             !< loop variable for stretching
170    INTEGER(iwp) ::  number_dz     !< number of user-specified dz values       
171    INTEGER(iwp) ::  nzb_local_max !< vertical grid index of maximum topography height
172    INTEGER(iwp) ::  nzb_local_min !< vertical grid index of minimum topography height
173                                     
174    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_local  !< index for topography top at cell-center
175    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_tmp    !< dummy to calculate topography indices on u- and v-grid
176
177    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo !< input array for 3D topography and dummy array for setting "outer"-flags
178
179    REAL(wp) ::  dz_level_end  !< distance between calculated height level for u/v-grid and user-specified end level for stretching
180    REAL(wp) ::  dz_stretched  !< stretched vertical grid spacing
181   
182    REAL(wp), DIMENSION(:), ALLOCATABLE ::  min_dz_stretch_level_end !< Array that contains all minimum heights where the stretching can end
183
184
185!
186!-- Calculation of horizontal array bounds including ghost layers
187    nxlg = nxl - nbgp
188    nxrg = nxr + nbgp
189    nysg = nys - nbgp
190    nyng = nyn + nbgp
191
192!
193!-- Allocate grid arrays
194    ALLOCATE( x(0:nx), xu(0:nx) )
195    DO i = 0, nx
196       xu(i) = i * dx
197       x(i)  = i * dx + 0.5_wp * dx
198    ENDDO
199
200    ALLOCATE( y(0:ny), yv(0:ny) )
201    DO j = 0, ny
202       yv(j) = j * dy
203       y(j)  = j * dy + 0.5_wp * dy
204    ENDDO
205
206!
207!-- Allocate grid arrays
208    ALLOCATE( ddzu(1:nzt+1), ddzw(1:nzt+1), dd2zu(1:nzt), dzu(1:nzt+1),        &
209              dzw(1:nzt+1), zu(nzb:nzt+1), zw(nzb:nzt+1) )
210
211!
212!-- Compute height of u-levels from constant grid length and dz stretch factors
213    IF ( dz(1) == -1.0_wp )  THEN
214       message_string = 'missing dz'
215       CALL message( 'init_grid', 'PA0200', 1, 2, 0, 6, 0 ) 
216    ELSEIF ( dz(1) <= 0.0_wp )  THEN
217       WRITE( message_string, * ) 'dz=',dz(1),' <= 0.0'
218       CALL message( 'init_grid', 'PA0201', 1, 2, 0, 6, 0 )
219    ENDIF
220
221!
222!-- Initialize dz_stretch_level_start with the value of dz_stretch_level
223!-- if it was set by the user
224    IF ( dz_stretch_level /= -9999999.9_wp ) THEN
225       dz_stretch_level_start(1) = dz_stretch_level
226    ENDIF
227       
228!
229!-- Determine number of dz values and stretching levels specified by the
230!-- user to allow right controlling of the stretching mechanism and to
231!-- perform error checks. The additional requirement that dz /= dz_max
232!-- for counting number of user-specified dz values is necessary. Otherwise
233!-- restarts would abort if the old stretching mechanism with dz_stretch_level
234!-- is used (Attention: The user is not allowed to specify a dz value equal
235!-- to the default of dz_max = 999.0).
236    number_dz = COUNT( dz /= -1.0_wp .AND. dz /= dz_max)
237    number_stretch_level_start = COUNT( dz_stretch_level_start /=              &
238                                       -9999999.9_wp )
239    number_stretch_level_end = COUNT( dz_stretch_level_end /=                  &
240                                      9999999.9_wp )
241
242!
243!-- The number of specified end levels +1 has to be the same than the number
244!-- of specified dz values
245    IF ( number_dz /= number_stretch_level_end + 1 ) THEN
246       WRITE( message_string, * ) 'The number of values for dz = ',         &
247                                   number_dz, 'has to be the same than& ',  &
248                                   'the number of values for ',             &
249                                   'dz_stretch_level_end + 1 = ',           &
250                                   number_stretch_level_end+1
251          CALL message( 'init_grid', 'PA0156', 1, 2, 0, 6, 0 )
252    ENDIF
253   
254!
255!--    The number of specified start levels has to be the same or one less than
256!--    the number of specified dz values
257    IF ( number_dz /= number_stretch_level_start + 1 .AND.                  &
258         number_dz /= number_stretch_level_start ) THEN
259       WRITE( message_string, * ) 'The number of values for dz = ',         &
260                                   number_dz, 'has to be the same or one ', &
261                                   'more than& the number of values for ',  &
262                                   'dz_stretch_level_start = ',             &
263                                   number_stretch_level_start
264          CALL message( 'init_grid', 'PA0211', 1, 2, 0, 6, 0 )
265    ENDIF
266   
267!--    The number of specified start levels has to be the same or one more than
268!--    the number of specified end levels
269    IF ( number_stretch_level_start /= number_stretch_level_end + 1 .AND.   &
270         number_stretch_level_start /= number_stretch_level_end ) THEN
271       WRITE( message_string, * ) 'The number of values for ',              &
272                                  'dz_stretch_level_start = ',              &
273                                   dz_stretch_level_start, 'has to be the ',&
274                                   'same or one more than& the number of ', &
275                                   'values for dz_stretch_level_end = ',    &
276                                   number_stretch_level_end
277          CALL message( 'init_grid', 'PA0216', 1, 2, 0, 6, 0 )
278    ENDIF
279
280!
281!-- Initialize dz for the free atmosphere with the value of dz_max
282    IF ( dz(number_stretch_level_start+1) == -1.0_wp .AND.                     &
283         number_stretch_level_start /= 0 ) THEN
284       dz(number_stretch_level_start+1) = dz_max
285    ENDIF
286       
287!
288!-- Initialize the stretching factor if (infinitely) stretching in the free
289!-- atmosphere is desired (dz_stretch_level_end was not specified for the
290!-- free atmosphere)
291    IF ( number_stretch_level_start == number_stretch_level_end + 1 ) THEN
292       dz_stretch_factor_array(number_stretch_level_start) =                   &
293       dz_stretch_factor
294    ENDIF
295   
296!
297!-- Allocation of arrays for stretching
298    ALLOCATE( min_dz_stretch_level_end(number_stretch_level_start) )
299
300!
301!-- Define the vertical grid levels
302    IF ( .NOT. ocean_mode )  THEN
303   
304!
305!--    The stretching region has to be large enough to allow for a smooth
306!--    transition between two different grid spacings
307       DO n = 1, number_stretch_level_start
308          min_dz_stretch_level_end(n) = dz_stretch_level_start(n) +            &
309                                        4 * MAX( dz(n),dz(n+1) )
310       ENDDO
311
312       IF ( ANY( min_dz_stretch_level_end(1:number_stretch_level_start) >      &
313                 dz_stretch_level_end(1:number_stretch_level_start) ) ) THEN
314             message_string= 'Eeach dz_stretch_level_end has to be larger ' // &
315                             'than its corresponding value for &' //           &
316                             'dz_stretch_level_start + 4*MAX(dz(n),dz(n+1)) '//&
317                             'to allow for smooth grid stretching'
318             CALL message( 'init_grid', 'PA0224', 1, 2, 0, 6, 0 )
319       ENDIF
320       
321!
322!--    Stretching must not be applied within the prandtl_layer
323!--    (first two grid points). For the default case dz_stretch_level_start
324!--    is negative. Therefore the absolut value is checked here.
325       IF ( ANY( ABS( dz_stretch_level_start ) < dz(1) * 1.5_wp ) ) THEN
326          WRITE( message_string, * ) 'Eeach dz_stretch_level_start has to be ',&
327                                     'larger than ', dz(1) * 1.5
328             CALL message( 'init_grid', 'PA0226', 1, 2, 0, 6, 0 )
329       ENDIF
330
331!
332!--    The stretching has to start and end on a grid level. Therefore
333!--    user-specified values have to ''interpolate'' to the next lowest level
334       IF ( number_stretch_level_start /= 0 ) THEN
335          dz_stretch_level_start(1) = INT( (dz_stretch_level_start(1) -        &
336                                            dz(1)/2.0) / dz(1) )               &
337                                      * dz(1) + dz(1)/2.0
338       ENDIF
339       
340       IF ( number_stretch_level_start > 1 ) THEN
341          DO n = 2, number_stretch_level_start
342             dz_stretch_level_start(n) = INT( dz_stretch_level_start(n) /      &
343                                              dz(n) ) * dz(n)
344          ENDDO
345       ENDIF
346       
347       IF ( number_stretch_level_end /= 0 ) THEN
348          DO n = 1, number_stretch_level_end
349             dz_stretch_level_end(n) = INT( dz_stretch_level_end(n) /          &
350                                            dz(n+1) ) * dz(n+1)
351          ENDDO
352       ENDIF
353 
354!
355!--    Determine stretching factor if necessary
356       IF ( number_stretch_level_end >= 1 ) THEN
357          CALL calculate_stretching_factor( number_stretch_level_end )
358       ENDIF
359
360!
361!--    Grid for atmosphere with surface at z=0 (k=0, w-grid).
362!--    First compute the u- and v-levels. In case of dirichlet bc for u and v
363!--    the first u/v- and w-level (k=0) are defined at same height (z=0).
364!--    The second u-level (k=1) corresponds to the top of the
365!--    Prandtl-layer. In case of symmetric boundaries (closed channel flow),
366!--    the first grid point is always at z=0.
367       IF ( ibc_uv_b == 0 .OR. ibc_uv_b == 2 .OR.                              & 
368            topography == 'closed_channel' ) THEN
369          zu(0) = 0.0_wp
370       ELSE
371          zu(0) = - dz(1) * 0.5_wp
372       ENDIF
373         
374       zu(1) =   dz(1) * 0.5_wp
375       
376!
377!--    Determine u and v height levels considering the possibility of grid
378!--    stretching in several heights.
379       n = 1
380       dz_stretch_level_start_index = nzt+1
381       dz_stretch_level_end_index = nzt+1
382       dz_stretched = dz(1)
383
384!--    The default value of dz_stretch_level_start is negative, thus the first
385!--    condition is always true. Hence, the second condition is necessary.
386       DO  k = 2, nzt+1-symmetry_flag
387          IF ( dz_stretch_level_start(n) <= zu(k-1) .AND.                      &
388               dz_stretch_level_start(n) /= -9999999.9_wp ) THEN
389             dz_stretched = dz_stretched * dz_stretch_factor_array(n)
390             
391             IF ( dz(n) > dz(n+1) ) THEN
392                dz_stretched = MAX( dz_stretched, dz(n+1) ) !Restrict dz_stretched to the user-specified (higher) dz
393             ELSE
394                dz_stretched = MIN( dz_stretched, dz(n+1) ) !Restrict dz_stretched to the user-specified (lower) dz
395             ENDIF
396             
397             IF ( dz_stretch_level_start_index(n) == nzt+1 )                         &
398             dz_stretch_level_start_index(n) = k-1
399             
400          ENDIF
401         
402          zu(k) = zu(k-1) + dz_stretched
403         
404!
405!--       Make sure that the stretching ends exactly at dz_stretch_level_end
406          dz_level_end = ABS( zu(k) - dz_stretch_level_end(n) ) 
407         
408          IF ( dz_level_end  < dz(n+1)/3.0 ) THEN
409             zu(k) = dz_stretch_level_end(n)
410             dz_stretched = dz(n+1)
411             dz_stretch_level_end_index(n) = k
412             n = n + 1             
413          ENDIF
414       ENDDO
415       
416!
417!--    If a closed channel flow is simulated, make sure that grid structure is 
418!--    the same for both bottom and top boundary. (Hint: Using a different dz
419!--    at the bottom and at the top makes no sense due to symmetric boundaries
420!--    where dz should be equal. Therefore, different dz at the bottom and top 
421!--    causes an abort (see check_parameters).)
422       IF ( topography == 'closed_channel' ) THEN
423          zu(nzt+1) = zu(nzt) + dz(1) * 0.5_wp
424       ENDIF
425
426!
427!--    Compute the w-levels. They are always staggered half-way between the
428!--    corresponding u-levels. In case of dirichlet bc for u and v at the
429!--    ground the first u- and w-level (k=0) are defined at same height (z=0).
430!--    Per default, the top w-level is extrapolated linearly. In case of
431!--    a closed channel flow, zu(nzt+1) and zw(nzt) must be set explicitely.
432!--    (Hint: Using a different dz at the bottom and at the top makes no sense
433!--    due to symmetric boundaries where dz should be equal. Therefore,
434!--    different dz at the bottom and top causes an abort (see
435!--    check_parameters).)
436       zw(0) = 0.0_wp
437       DO  k = 1, nzt-symmetry_flag
438          zw(k) = ( zu(k) + zu(k+1) ) * 0.5_wp
439       ENDDO
440       IF ( topography == 'closed_channel' ) THEN
441          zw(nzt)   = zw(nzt-1) + dz(1)
442          zw(nzt+1) = zw(nzt) + dz(1)
443       ELSE
444          zw(nzt+1) = zw(nzt) + 2.0_wp * ( zu(nzt+1) - zw(nzt) )
445       ENDIF
446
447    ELSE
448
449!
450!--    The stretching region has to be large enough to allow for a smooth
451!--    transition between two different grid spacings
452       DO n = 1, number_stretch_level_start
453          min_dz_stretch_level_end(n) = dz_stretch_level_start(n) -            &
454                                        4 * MAX( dz(n),dz(n+1) )
455       ENDDO
456       
457       IF ( ANY( min_dz_stretch_level_end (1:number_stretch_level_start) <     &
458                 dz_stretch_level_end(1:number_stretch_level_start) ) ) THEN
459             message_string= 'Eeach dz_stretch_level_end has to be less ' //   &
460                             'than its corresponding value for &' //           &
461                             'dz_stretch_level_start - 4*MAX(dz(n),dz(n+1)) '//&
462                             'to allow for smooth grid stretching'
463             CALL message( 'init_grid', 'PA0224', 1, 2, 0, 6, 0 )
464       ENDIF
465       
466!
467!--    Stretching must not be applied close to the surface (last two grid
468!--    points). For the default case dz_stretch_level_start is negative.
469       IF ( ANY( dz_stretch_level_start > - dz(1) * 1.5_wp ) ) THEN
470          WRITE( message_string, * ) 'Eeach dz_stretch_level_start has to be ',&
471                                     'less than ', dz(1) * 1.5
472             CALL message( 'init_grid', 'PA0226', 1, 2, 0, 6, 0 )
473       ENDIF
474
475!
476!--    The stretching has to start and end on a grid level. Therefore
477!--    user-specified values have to ''interpolate'' to the next highest level
478       IF ( number_stretch_level_start /= 0 ) THEN
479          dz_stretch_level_start(1) = INT( (dz_stretch_level_start(1) +        &
480                                            dz(1)/2.0) / dz(1) )               &
481                                      * dz(1) - dz(1)/2.0
482       ENDIF
483       
484       IF ( number_stretch_level_start > 1 ) THEN
485          DO n = 2, number_stretch_level_start
486             dz_stretch_level_start(n) = INT( dz_stretch_level_start(n) /      &
487                                              dz(n) ) * dz(n)
488          ENDDO
489       ENDIF
490       
491       IF ( number_stretch_level_end /= 0 ) THEN
492          DO n = 1, number_stretch_level_end
493             dz_stretch_level_end(n) = INT( dz_stretch_level_end(n) /          &
494                                            dz(n+1) ) * dz(n+1)
495          ENDDO
496       ENDIF
497       
498!
499!--    Determine stretching factor if necessary
500       IF ( number_stretch_level_end >= 1 ) THEN
501          CALL calculate_stretching_factor( number_stretch_level_end )
502       ENDIF
503
504!
505!--    Grid for ocean with free water surface is at k=nzt (w-grid).
506!--    In case of neumann bc at the ground the first first u-level (k=0) lies
507!--    below the first w-level (k=0). In case of dirichlet bc the first u- and
508!--    w-level are defined at same height, but staggered from the second level.
509!--    The second u-level (k=1) corresponds to the top of the Prandtl-layer.
510!--    z values are negative starting from z=0 (surface)
511       zu(nzt+1) =   dz(1) * 0.5_wp
512       zu(nzt)   = - dz(1) * 0.5_wp
513
514!
515!--    Determine u and v height levels considering the possibility of grid
516!--    stretching in several heights.
517       n = 1
518       dz_stretch_level_start_index = 0
519       dz_stretch_level_end_index = 0
520       dz_stretched = dz(1)
521
522       DO  k = nzt-1, 0, -1
523         
524          IF ( dz_stretch_level_start(n) >= zu(k+1) ) THEN
525             dz_stretched = dz_stretched * dz_stretch_factor_array(n)
526
527             IF ( dz(n) > dz(n+1) ) THEN
528                dz_stretched = MAX( dz_stretched, dz(n+1) ) !Restrict dz_stretched to the user-specified (higher) dz
529             ELSE
530                dz_stretched = MIN( dz_stretched, dz(n+1) ) !Restrict dz_stretched to the user-specified (lower) dz
531             ENDIF
532             
533             IF ( dz_stretch_level_start_index(n) == 0 )                             &
534             dz_stretch_level_start_index(n) = k+1
535             
536          ENDIF
537         
538          zu(k) = zu(k+1) - dz_stretched
539         
540!
541!--       Make sure that the stretching ends exactly at dz_stretch_level_end
542          dz_level_end = ABS( zu(k) - dz_stretch_level_end(n) ) 
543         
544          IF ( dz_level_end  < dz(n+1)/3.0 ) THEN
545             zu(k) = dz_stretch_level_end(n)
546             dz_stretched = dz(n+1)
547             dz_stretch_level_end_index(n) = k
548             n = n + 1             
549          ENDIF
550       ENDDO
551       
552!
553!--    Compute the w-levels. They are always staggered half-way between the
554!--    corresponding u-levels, except in case of dirichlet bc for u and v
555!--    at the ground. In this case the first u- and w-level are defined at
556!--    same height. The top w-level (nzt+1) is not used but set for
557!--    consistency, since w and all scalar variables are defined up tp nzt+1.
558       zw(nzt+1) = dz(1)
559       zw(nzt)   = 0.0_wp
560       DO  k = 0, nzt
561          zw(k) = ( zu(k) + zu(k+1) ) * 0.5_wp
562       ENDDO
563
564!
565!--    In case of dirichlet bc for u and v the first u- and w-level are defined
566!--    at same height.
567       IF ( ibc_uv_b == 0 ) THEN
568          zu(0) = zw(0)
569       ENDIF
570
571    ENDIF
572
573!
574!-- Compute grid lengths.
575    DO  k = 1, nzt+1
576       dzu(k)  = zu(k) - zu(k-1)
577       ddzu(k) = 1.0_wp / dzu(k)
578       dzw(k)  = zw(k) - zw(k-1)
579       ddzw(k) = 1.0_wp / dzw(k)
580    ENDDO
581
582    DO  k = 1, nzt
583       dd2zu(k) = 1.0_wp / ( dzu(k) + dzu(k+1) )
584    ENDDO
585   
586!   
587!-- The FFT- SOR-pressure solvers assume grid spacings of a staggered grid
588!-- everywhere. For the actual grid, the grid spacing at the lowest level
589!-- is only dz/2, but should be dz. Therefore, an additional array
590!-- containing with appropriate grid information is created for these
591!-- solvers.
592    IF ( psolver(1:9) /= 'multigrid' )  THEN
593       ALLOCATE( ddzu_pres(1:nzt+1) )
594       ddzu_pres = ddzu
595       ddzu_pres(1) = ddzu_pres(2)  ! change for lowest level
596    ENDIF
597
598!
599!-- Compute the reciprocal values of the horizontal grid lengths.
600    ddx = 1.0_wp / dx
601    ddy = 1.0_wp / dy
602    dx2 = dx * dx
603    dy2 = dy * dy
604    ddx2 = 1.0_wp / dx2
605    ddy2 = 1.0_wp / dy2
606
607!
608!-- Allocate 3D array to set topography
609    ALLOCATE( topo(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
610    topo = 0
611!
612!-- Initialize topography by generic topography or read from topography from file. 
613    CALL init_topo( topo )
614!
615!-- Set flags to mask topography on the grid.
616    CALL set_topo_flags( topo )   
617!
618!-- Calculate wall flag arrays for the multigrid method.
619!-- Please note, wall flags are only applied in the non-optimized version.
620    IF ( psolver == 'multigrid_noopt' )  CALL poismg_noopt_init
621
622!
623!-- Init flags for ws-scheme to degrade order of the numerics near walls, i.e.
624!-- to decrease the numerical stencil appropriately. The order of the scheme
625!-- is degraded near solid walls as well as near non-cyclic inflow and outflow
626!-- boundaries. Do this separately for momentum and scalars.
627    IF ( momentum_advec == 'ws-scheme' )  THEN
628       ALLOCATE( advc_flags_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
629       CALL ws_init_flags_momentum
630    ENDIF
631    IF ( scalar_advec == 'ws-scheme'   )  THEN
632       ALLOCATE( advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
633       advc_flags_s = 0
634       
635       CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l,        &
636                                  bc_dirichlet_n  .OR.  bc_radiation_n,        &
637                                  bc_dirichlet_r  .OR.  bc_radiation_r,        &
638                                  bc_dirichlet_s  .OR.  bc_radiation_s,        &
639                                  advc_flags_s )
640    ENDIF
641
642!
643!-- Determine the maximum level of topography. It is used for
644!-- steering the degradation of order of the applied advection scheme,
645!-- as well in the lpm.
646    k_top = 0
647    DO  i = nxl, nxr
648       DO  j = nys, nyn
649          DO  k = nzb, nzt + 1
650             k_top = MAX( k_top, MERGE( k, 0, .NOT. BTEST( topo(k,j,i), 0 ) ) )
651          ENDDO
652       ENDDO
653    ENDDO
654#if defined( __parallel )
655    CALL MPI_ALLREDUCE( k_top, nzb_max, 1, MPI_INTEGER,                        &
656                        MPI_MAX, comm2d, ierr )
657#else
658    nzb_max = k_top
659#endif
660!
661!-- Increment nzb_max by 1 in order to allow for proper diverengence correction.
662!-- Further, in case topography extents up to the model top, limit to nzt.
663    nzb_max = MIN( nzb_max+1, nzt ) 
664!
665!-- Determine minimum index of topography. Usually, this will be nzb. In case
666!-- there is elevated topography, however, the lowest topography will be higher.
667!-- This index is e.g. used to calculate mean first-grid point atmosphere
668!-- temperature, surface pressure and density, etc. .
669    topo_min_level   = 0
670#if defined( __parallel )
671    CALL MPI_ALLREDUCE( MINVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ),             &
672                        topo_min_level, 1, MPI_INTEGER, MPI_MIN, comm2d, ierr )
673#else
674    topo_min_level = MINVAL( topo_top_ind(nys:nyn,nxl:nxr,0) )
675#endif
676!
677!-- Initialize boundary conditions via surface type
678    CALL init_bc
679
680!
681!-- Allocate and set topography height arrays required for data output
682    IF ( TRIM( topography ) /= 'flat' )  THEN
683!
684!--    Allocate and set the arrays containing the topography height
685       IF ( nxr == nx  .AND.  nyn /= ny )  THEN
686          ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn),                             &
687                    zw_w_inner(nxl:nxr+1,nys:nyn) )
688       ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
689          ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn+1),                             &
690                    zw_w_inner(nxl:nxr,nys:nyn+1) )
691       ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
692          ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn+1),                           &
693                    zw_w_inner(nxl:nxr+1,nys:nyn+1) )
694       ELSE
695          ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn),                               &
696                    zw_w_inner(nxl:nxr,nys:nyn) )
697       ENDIF
698
699       zu_s_inner   = 0.0_wp
700       zw_w_inner   = 0.0_wp
701!
702!--    Determine local topography height on scalar and w-grid. Note, setting
703!--    lateral boundary values is not necessary, realized via wall_flags_static_0
704!--    array. Further, please note that loop bounds are different from
705!--    nxl to nxr and nys to nyn on south and right model boundary, hence,
706!--    use intrinsic lbound and ubound functions to infer array bounds.
707       DO  i = LBOUND(zu_s_inner, 1), UBOUND(zu_s_inner, 1)
708          DO  j = LBOUND(zu_s_inner, 2), UBOUND(zu_s_inner, 2)
709!
710!--          Topography height on scalar grid. Therefore, determine index of
711!--          upward-facing surface element on scalar grid.
712             zu_s_inner(i,j) = zu(topo_top_ind(j,i,0))
713!
714!--          Topography height on w grid. Therefore, determine index of
715!--          upward-facing surface element on w grid.
716             zw_w_inner(i,j) = zw(topo_top_ind(j,i,3))
717          ENDDO
718       ENDDO
719    ENDIF
720
721!
722!-- In the following, calculate 2D index arrays. Note, these will be removed
723!-- soon.
724!-- Allocate outer and inner index arrays for topography and set
725!-- defaults.                   
726    ALLOCATE( nzb_s_inner(nysg:nyng,nxlg:nxrg),                                &
727              nzb_s_outer(nysg:nyng,nxlg:nxrg),                                &
728              nzb_u_inner(nysg:nyng,nxlg:nxrg),                                &
729              nzb_u_outer(nysg:nyng,nxlg:nxrg),                                &
730              nzb_v_inner(nysg:nyng,nxlg:nxrg),                                &
731              nzb_v_outer(nysg:nyng,nxlg:nxrg),                                &
732              nzb_w_inner(nysg:nyng,nxlg:nxrg),                                &
733              nzb_w_outer(nysg:nyng,nxlg:nxrg),                                &
734              nzb_diff_s_inner(nysg:nyng,nxlg:nxrg),                           &
735              nzb_diff_s_outer(nysg:nyng,nxlg:nxrg),                           &
736              nzb_local(nysg:nyng,nxlg:nxrg),                                  &
737              nzb_tmp(nysg:nyng,nxlg:nxrg) )
738!
739!-- Initialize 2D-index arrays. Note, these will be removed soon!
740    nzb_local(nys:nyn,nxl:nxr) = topo_top_ind(nys:nyn,nxl:nxr,0)
741    CALL exchange_horiz_2d_int( nzb_local, nys, nyn, nxl, nxr, nbgp )
742!
743!-- Check topography for consistency with model domain. Therefore, use
744!-- maximum and minium topography-top indices. Note, minimum topography top
745!-- index is already calculated. 
746    IF ( TRIM( topography ) /= 'flat' )  THEN
747#if defined( __parallel )
748       CALL MPI_ALLREDUCE( MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ),          &
749                           nzb_local_max, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr )               
750#else
751       nzb_local_max = MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) )
752#endif
753       nzb_local_min = topo_min_level
754!
755!--    Consistency checks
756       IF ( nzb_local_min < 0  .OR.  nzb_local_max  > nz + 1 )  THEN
757          WRITE( message_string, * ) 'nzb_local values are outside the',       &
758                                ' model domain',                               &
759                                '&MINVAL( nzb_local ) = ', nzb_local_min,      &
760                                '&MAXVAL( nzb_local ) = ', nzb_local_max
761          CALL message( 'init_grid', 'PA0210', 1, 2, 0, 6, 0 )
762       ENDIF
763    ENDIF
764
765    nzb_s_inner = nzb;  nzb_s_outer = nzb
766    nzb_u_inner = nzb;  nzb_u_outer = nzb
767    nzb_v_inner = nzb;  nzb_v_outer = nzb
768    nzb_w_inner = nzb;  nzb_w_outer = nzb
769
770!
771!-- Define vertical gridpoint from (or to) which on the usual finite difference
772!-- form (which does not use surface fluxes) is applied
773    IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
774       nzb_diff = nzb + 2
775    ELSE
776       nzb_diff = nzb + 1
777    ENDIF
778
779    nzb_diff_s_inner = nzb_diff;  nzb_diff_s_outer = nzb_diff
780!
781!-- Set Neumann conditions for topography. Will be removed soon.
782    IF ( .NOT. bc_ns_cyc )  THEN
783       IF ( nys == 0  )  THEN
784          DO  i = 1, nbgp 
785             nzb_local(nys-i,:)   = nzb_local(nys,:)
786          ENDDO
787       ELSEIF ( nyn == ny )  THEN
788          DO  i = 1, nbgp 
789             nzb_local(ny+i,:) = nzb_local(ny,:)
790          ENDDO
791       ENDIF
792    ENDIF
793
794    IF ( .NOT. bc_lr_cyc )  THEN
795       IF ( nxl == 0  )  THEN
796          DO  i = 1, nbgp 
797             nzb_local(:,nxl-i)   = nzb_local(:,nxl)
798          ENDDO
799       ELSEIF ( nxr == nx )  THEN
800          DO  i = 1, nbgp 
801             nzb_local(:,nx+i) = nzb_local(:,nx)
802          ENDDO 
803       ENDIF         
804    ENDIF
805!
806!-- Initialization of 2D index arrays, will be removed soon!
807!-- Initialize nzb_s_inner and nzb_w_inner
808    nzb_s_inner = nzb_local
809    nzb_w_inner = nzb_local
810
811!
812!-- Initialize remaining index arrays:
813!-- first pre-initialize them with nzb_s_inner...
814    nzb_u_inner = nzb_s_inner
815    nzb_u_outer = nzb_s_inner
816    nzb_v_inner = nzb_s_inner
817    nzb_v_outer = nzb_s_inner
818    nzb_w_outer = nzb_s_inner
819    nzb_s_outer = nzb_s_inner
820
821!
822!-- nzb_s_outer:
823!-- extend nzb_local east-/westwards first, then north-/southwards
824    nzb_tmp = nzb_local
825    DO  j = nys, nyn
826       DO  i = nxl, nxr
827          nzb_tmp(j,i) = MAX( nzb_local(j,i-1), nzb_local(j,i),             &
828                              nzb_local(j,i+1) )
829       ENDDO
830    ENDDO
831       
832    CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )
833     
834    DO  i = nxl, nxr
835       DO  j = nys, nyn
836          nzb_s_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i),             &
837                                  nzb_tmp(j+1,i) )
838       ENDDO
839!
840!--    non-cyclic boundary conditions (overwritten by call of
841!--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
842       IF ( nys == 0 )  THEN
843          j = -1
844          nzb_s_outer(j,i) = MAX( nzb_tmp(j+1,i), nzb_tmp(j,i) )
845       ENDIF
846       IF ( nyn == ny )  THEN
847          j = ny + 1
848          nzb_s_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i) )
849       ENDIF
850    ENDDO
851!
852!-- nzb_w_outer:
853!-- identical to nzb_s_outer
854    nzb_w_outer = nzb_s_outer
855!
856!-- nzb_u_inner:
857!-- extend nzb_local rightwards only
858    nzb_tmp = nzb_local
859    DO  j = nys, nyn
860       DO  i = nxl, nxr
861          nzb_tmp(j,i) = MAX( nzb_local(j,i-1), nzb_local(j,i) )
862       ENDDO
863    ENDDO
864       
865    CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )
866       
867    nzb_u_inner = nzb_tmp
868!
869!-- nzb_u_outer:
870!-- extend current nzb_tmp (nzb_u_inner) north-/southwards
871    DO  i = nxl, nxr
872       DO  j = nys, nyn
873          nzb_u_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i),             &
874                                  nzb_tmp(j+1,i) )
875       ENDDO
876!
877!--    non-cyclic boundary conditions (overwritten by call of
878!--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
879       IF ( nys == 0 )  THEN
880          j = -1
881          nzb_u_outer(j,i) = MAX( nzb_tmp(j+1,i), nzb_tmp(j,i) )
882       ENDIF
883       IF ( nyn == ny )  THEN
884          j = ny + 1
885          nzb_u_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i) )
886       ENDIF
887    ENDDO
888
889!
890!-- nzb_v_inner:
891!-- extend nzb_local northwards only
892    nzb_tmp = nzb_local
893    DO  i = nxl, nxr
894       DO  j = nys, nyn
895          nzb_tmp(j,i) = MAX( nzb_local(j-1,i), nzb_local(j,i) )
896       ENDDO
897    ENDDO
898       
899    CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )     
900    nzb_v_inner = nzb_tmp
901
902!
903!-- nzb_v_outer:
904!-- extend current nzb_tmp (nzb_v_inner) right-/leftwards
905    DO  j = nys, nyn
906       DO  i = nxl, nxr
907          nzb_v_outer(j,i) = MAX( nzb_tmp(j,i-1), nzb_tmp(j,i),                &
908                                  nzb_tmp(j,i+1) )
909       ENDDO
910!
911!--    non-cyclic boundary conditions (overwritten by call of
912!--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
913       IF ( nxl == 0 )  THEN
914          i = -1
915          nzb_v_outer(j,i) = MAX( nzb_tmp(j,i+1), nzb_tmp(j,i) )
916       ENDIF
917       IF ( nxr == nx )  THEN
918          i = nx + 1
919          nzb_v_outer(j,i) = MAX( nzb_tmp(j,i-1), nzb_tmp(j,i) )
920       ENDIF
921    ENDDO
922
923!
924!-- Exchange of lateral boundary values (parallel computers) and cyclic
925!-- boundary conditions, if applicable.
926!-- Since nzb_s_inner and nzb_w_inner are derived directly from nzb_local
927!-- they do not require exchange and are not included here.
928    CALL exchange_horiz_2d_int( nzb_u_inner, nys, nyn, nxl, nxr, nbgp )
929    CALL exchange_horiz_2d_int( nzb_u_outer, nys, nyn, nxl, nxr, nbgp )
930    CALL exchange_horiz_2d_int( nzb_v_inner, nys, nyn, nxl, nxr, nbgp )
931    CALL exchange_horiz_2d_int( nzb_v_outer, nys, nyn, nxl, nxr, nbgp )
932    CALL exchange_horiz_2d_int( nzb_w_outer, nys, nyn, nxl, nxr, nbgp )
933    CALL exchange_horiz_2d_int( nzb_s_outer, nys, nyn, nxl, nxr, nbgp )
934
935!
936!-- Set the individual index arrays which define the k index from which on
937!-- the usual finite difference form (which does not use surface fluxes) is
938!-- applied
939    IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
940       nzb_diff_s_inner   = nzb_s_inner + 2
941       nzb_diff_s_outer   = nzb_s_outer + 2
942    ELSE
943       nzb_diff_s_inner   = nzb_s_inner + 1
944       nzb_diff_s_outer   = nzb_s_outer + 1
945    ENDIF
946!
947!-- Vertical nesting: communicate vertical grid level arrays between fine and
948!-- coarse grid
949    IF ( vnested )  CALL vnest_init_grid
950
951 END SUBROUTINE init_grid
952
953
954! Description:
955! -----------------------------------------------------------------------------!
956!> Calculation of the stretching factor through an iterative method. Ideas were
957!> taken from the paper "Regional stretched grid generation and its application
958!> to the NCAR RegCM (1999)". Normally, no analytic solution exists because the
959!> system of equations has two variables (r,l) but four requirements
960!> (l=integer, r=[0,88;1,2], Eq(6), Eq(5) starting from index j=1) which
961!> results into an overdetermined system.
962!------------------------------------------------------------------------------!
963 SUBROUTINE calculate_stretching_factor( number_end )
964 
965    USE control_parameters,                                                    &
966        ONLY:  dz, dz_stretch_factor_array,                 &
967               dz_stretch_level_end, dz_stretch_level_start, message_string
968 
969    USE kinds
970   
971    IMPLICIT NONE
972   
973    INTEGER(iwp) ::  iterations  !< number of iterations until stretch_factor_lower/upper_limit is reached 
974    INTEGER(iwp) ::  l_rounded   !< after l_rounded grid levels dz(n) is strechted to dz(n+1) with stretch_factor_2
975    INTEGER(iwp) ::  n           !< loop variable for stretching
976   
977    INTEGER(iwp), INTENT(IN) ::  number_end !< number of user-specified end levels for stretching
978       
979    REAL(wp) ::  delta_l               !< absolute difference between l and l_rounded
980    REAL(wp) ::  delta_stretch_factor  !< absolute difference between stretch_factor_1 and stretch_factor_2
981    REAL(wp) ::  delta_total_new       !< sum of delta_l and delta_stretch_factor for the next iteration (should be as small as possible)
982    REAL(wp) ::  delta_total_old       !< sum of delta_l and delta_stretch_factor for the last iteration
983    REAL(wp) ::  distance              !< distance between dz_stretch_level_start and dz_stretch_level_end (stretching region)
984    REAL(wp) ::  l                     !< value that fulfil Eq. (5) in the paper mentioned above together with stretch_factor_1 exactly
985    REAL(wp) ::  numerator             !< numerator of the quotient
986    REAL(wp) ::  stretch_factor_1      !< stretching factor that fulfil Eq. (5) togehter with l exactly
987    REAL(wp) ::  stretch_factor_2      !< stretching factor that fulfil Eq. (6) togehter with l_rounded exactly
988   
989    REAL(wp) ::  dz_stretch_factor_array_2(9) = 1.08_wp  !< Array that contains all stretch_factor_2 that belongs to stretch_factor_1
990   
991    REAL(wp), PARAMETER ::  stretch_factor_interval = 1.0E-06  !< interval for sampling possible stretching factors
992    REAL(wp), PARAMETER ::  stretch_factor_lower_limit = 0.88  !< lowest possible stretching factor
993    REAL(wp), PARAMETER ::  stretch_factor_upper_limit = 1.12  !< highest possible stretching factor
994 
995 
996    l = 0
997    DO  n = 1, number_end
998   
999       iterations = 1
1000       stretch_factor_1 = 1.0 
1001       stretch_factor_2 = 1.0
1002       delta_total_old = 1.0
1003       
1004       IF ( dz(n) > dz(n+1) ) THEN
1005          DO WHILE ( stretch_factor_1 >= stretch_factor_lower_limit ) 
1006             
1007             stretch_factor_1 = 1.0 - iterations * stretch_factor_interval
1008             distance = ABS( dz_stretch_level_end(n) -                   &
1009                        dz_stretch_level_start(n) ) 
1010             numerator = distance*stretch_factor_1/dz(n) +               &
1011                         stretch_factor_1 - distance/dz(n)
1012             
1013             IF ( numerator > 0.0 ) THEN
1014                l = LOG( numerator ) / LOG( stretch_factor_1 ) - 1.0
1015                l_rounded = NINT( l )
1016                delta_l = ABS( l_rounded - l ) / l
1017             ENDIF
1018             
1019             stretch_factor_2 = EXP( LOG( dz(n+1)/dz(n) ) / (l_rounded) )
1020             
1021             delta_stretch_factor = ABS( stretch_factor_1 -              &
1022                                         stretch_factor_2 ) /            &
1023                                    stretch_factor_2
1024             
1025             delta_total_new = delta_l + delta_stretch_factor
1026
1027!
1028!--                stretch_factor_1 is taken to guarantee that the stretching
1029!--                procedure ends as close as possible to dz_stretch_level_end.
1030!--                stretch_factor_2 would guarantee that the stretched dz(n) is
1031!--                equal to dz(n+1) after l_rounded grid levels.
1032             IF (delta_total_new < delta_total_old) THEN
1033                dz_stretch_factor_array(n) = stretch_factor_1
1034                dz_stretch_factor_array_2(n) = stretch_factor_2
1035                delta_total_old = delta_total_new
1036             ENDIF
1037             
1038             iterations = iterations + 1
1039           
1040          ENDDO
1041             
1042       ELSEIF ( dz(n) < dz(n+1) ) THEN
1043          DO WHILE ( stretch_factor_1 <= stretch_factor_upper_limit )
1044                     
1045             stretch_factor_1 = 1.0 + iterations * stretch_factor_interval
1046             distance = ABS( dz_stretch_level_end(n) -                      &
1047                        dz_stretch_level_start(n) ) 
1048             numerator = distance*stretch_factor_1/dz(n) +                  &
1049                         stretch_factor_1 - distance/dz(n)
1050             
1051             l = LOG( numerator ) / LOG( stretch_factor_1 ) - 1.0
1052             l_rounded = NINT( l )
1053             delta_l = ABS( l_rounded - l ) / l
1054             
1055             stretch_factor_2 = EXP( LOG( dz(n+1)/dz(n) ) / (l_rounded) )
1056
1057             delta_stretch_factor = ABS( stretch_factor_1 -                 &
1058                                        stretch_factor_2 ) /                &
1059                                        stretch_factor_2
1060             
1061             delta_total_new = delta_l + delta_stretch_factor
1062             
1063!
1064!--                stretch_factor_1 is taken to guarantee that the stretching
1065!--                procedure ends as close as possible to dz_stretch_level_end.
1066!--                stretch_factor_2 would guarantee that the stretched dz(n) is
1067!--                equal to dz(n+1) after l_rounded grid levels.
1068             IF (delta_total_new < delta_total_old) THEN
1069                dz_stretch_factor_array(n) = stretch_factor_1
1070                dz_stretch_factor_array_2(n) = stretch_factor_2
1071                delta_total_old = delta_total_new
1072             ENDIF
1073             
1074             iterations = iterations + 1
1075          ENDDO
1076         
1077       ELSE
1078          message_string= 'Two adjacent values of dz must be different'
1079          CALL message( 'init_grid', 'PA0228', 1, 2, 0, 6, 0 )
1080         
1081       ENDIF
1082
1083!
1084!--    Check if also the second stretching factor fits into the allowed
1085!--    interval. If not, print a warning for the user.
1086       IF ( dz_stretch_factor_array_2(n) < stretch_factor_lower_limit .OR.     & 
1087            dz_stretch_factor_array_2(n) > stretch_factor_upper_limit ) THEN
1088          WRITE( message_string, * ) 'stretch_factor_2 = ',                    &
1089                                     dz_stretch_factor_array_2(n), ' which is',&
1090                                     ' responsible for exactly reaching& dz =',&
1091                                      dz(n+1), 'after a specific amount of',   & 
1092                                     ' grid levels& exceeds the upper',        &
1093                                     ' limit =', stretch_factor_upper_limit,   &
1094                                     ' &or lower limit = ',                    &
1095                                     stretch_factor_lower_limit
1096          CALL message( 'init_grid', 'PA0499', 0, 1, 0, 6, 0 )
1097           
1098       ENDIF
1099    ENDDO
1100       
1101 END SUBROUTINE calculate_stretching_factor
1102 
1103 
1104! Description:
1105! -----------------------------------------------------------------------------!
1106!> Set temporary topography flags and reference buildings on top of underlying
1107!> orography.
1108!------------------------------------------------------------------------------!
1109 SUBROUTINE process_topography( topo_3d )
1110
1111    USE arrays_3d,                                                             &
1112        ONLY:  zu, zw
1113
1114    USE control_parameters,                                                    &
1115        ONLY:  bc_lr_cyc, bc_ns_cyc, message_string, ocean_mode
1116
1117    USE indices,                                                               &
1118        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb,  &
1119               nzt
1120
1121    USE netcdf_data_input_mod,                                                 &
1122        ONLY:  buildings_f, building_id_f, building_type_f, input_pids_static, &
1123               terrain_height_f
1124
1125    USE kinds
1126
1127    USE pegrid
1128
1129    IMPLICIT NONE
1130
1131    INTEGER(iwp) ::  i                !< running index along x-direction
1132    INTEGER(iwp) ::  j                !< running index along y-direction
1133    INTEGER(iwp) ::  k                !< running index along z-direction with respect to numeric grid
1134    INTEGER(iwp) ::  k2               !< running index along z-direction with respect to netcdf grid
1135    INTEGER(iwp) ::  nr               !< index variable indication maximum terrain height for respective building ID
1136    INTEGER(iwp) ::  num_build        !< counter for number of buildings
1137    INTEGER(iwp) ::  topo_top_index   !< orography top index, used to map 3D buildings onto terrain
1138
1139    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displace_dum        !< displacements of start addresses, used for MPI_ALLGATHERV
1140    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
1141    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain, multiple occurences are sorted out
1142    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
1143    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
1144    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l_tmp     !< temporary array used to resize array of building IDs
1145
1146    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings     !< number of buildings with different ID on entire model domain
1147    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l   !< number of buildings with different ID on local subdomain
1148
1149    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d !< input array for 3D topography and dummy array for setting "outer"-flags
1150
1151    REAL(wp)                            ::  ocean_offset        !< offset to consider inverse vertical coordinate at topography definition
1152    REAL(wp)                            ::  oro_min = 0.0_wp    !< minimum terrain height in entire model domain, used to reference terrain to zero
1153    REAL(wp), DIMENSION(:), ALLOCATABLE ::  oro_max             !< maximum terrain height occupied by an building with certain id
1154    REAL(wp), DIMENSION(:), ALLOCATABLE ::  oro_max_l           !< maximum terrain height occupied by an building with certain id, on local subdomain
1155
1156!
1157!-- Reference lowest terrain height to zero. In case the minimum terrain height
1158!-- is non-zero, all grid points of the lower vertical grid levels might be
1159!-- entirely below the surface, meaning a waste of computational resources.
1160!-- In order to avoid this, remove the lowest terrain height. Please note,
1161!-- in case of a nested run, the global minimum from all parent and childs
1162!-- need to be remove to avoid steep edges at the child-domain boundaries.
1163    IF ( input_pids_static )  THEN
1164   
1165#if defined( __parallel ) 
1166       CALL MPI_ALLREDUCE( MINVAL( terrain_height_f%var ), oro_min, 1,         &
1167                           MPI_REAL, MPI_MIN, MPI_COMM_WORLD, ierr )
1168#else
1169       oro_min = MINVAL( terrain_height_f%var )
1170#endif
1171       terrain_height_f%var = terrain_height_f%var - oro_min
1172!                           
1173!--    Give an informative message that terrain height is referenced to zero   
1174       IF ( oro_min > 0.0_wp )  THEN
1175          WRITE( message_string, * ) 'Terrain height was internally shifted '//&
1176                          'downwards by ', oro_min, 'meter(s) to save ' //     &
1177                          'computational resources.'
1178          CALL message( 'init_grid', 'PA0505', 0, 0, 0, 6, 0 )
1179       ENDIF
1180    ENDIF   
1181   
1182!
1183!-- In the following, buildings and orography are further preprocessed
1184!-- before they are mapped on the LES grid.
1185!-- Buildings are mapped on top of the orography by maintaining the roof
1186!-- shape of the building. This can be achieved by referencing building on
1187!-- top of the maximum terrain height within the area occupied by the
1188!-- respective building. As buildings and terrain height are defined PE-wise,
1189!-- parallelization of this referencing is required (a building can be
1190!-- distributed between different PEs). 
1191!-- In a first step, determine the number of buildings with different
1192!-- building id on each PE. In a next step, all building ids are gathered
1193!-- into one array which is present to all PEs. For each building ID,
1194!-- the maximum terrain height occupied by the respective building is
1195!-- computed and distributed to each PE. 
1196!-- Finally, for each building id and its respective reference orography,
1197!-- builidings are mapped on top.   
1198!--
1199!-- First, pre-set topography flags, bit 1 indicates orography, bit 2
1200!-- buildings
1201!-- classify the respective surfaces.
1202    topo_3d          = IBSET( topo_3d, 0 )
1203    topo_3d(nzb,:,:) = IBCLR( topo_3d(nzb,:,:), 0 )
1204!
1205!-- In order to map topography on PALM grid also in case of ocean simulations,
1206!-- pre-calculate an offset value.
1207    ocean_offset = MERGE( zw(0), 0.0_wp, ocean_mode )
1208!
1209!-- Reference buildings on top of orography. This is not necessary
1210!-- if topography is read from ASCII file as no distinction between buildings
1211!-- and terrain height can be made. Moreover, this is also not necessary if
1212!-- urban-surface and land-surface model are used at the same time.
1213    IF ( input_pids_static )  THEN
1214
1215       IF ( buildings_f%from_file )  THEN
1216          num_buildings_l = 0
1217          num_buildings   = 0
1218!
1219!--       Allocate at least one element for building ids and give it an inital
1220!--       negative value that will be overwritten later. This, however, is
1221!--       necessary in case there all IDs in the model domain are fill values.
1222          ALLOCATE( build_ids_l(1) )
1223          build_ids_l = -1 
1224          DO  i = nxl, nxr
1225             DO  j = nys, nyn
1226                IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1227                   IF ( num_buildings_l(myid) > 0 )  THEN
1228                      IF ( ANY( building_id_f%var(j,i) ==  build_ids_l ) )   &
1229                      THEN
1230                         CYCLE
1231                      ELSE
1232                         num_buildings_l(myid) = num_buildings_l(myid) + 1
1233!
1234!--                   Resize array with different local building ids
1235                      ALLOCATE( build_ids_l_tmp(1:SIZE(build_ids_l)) )
1236                      build_ids_l_tmp = build_ids_l
1237                      DEALLOCATE( build_ids_l )
1238                      ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
1239                      build_ids_l(1:num_buildings_l(myid)-1) =                 &
1240                                  build_ids_l_tmp(1:num_buildings_l(myid)-1)
1241                      build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
1242                      DEALLOCATE( build_ids_l_tmp )
1243                   ENDIF
1244!
1245!--                First occuring building id on PE
1246                   ELSE
1247                      num_buildings_l(myid) = num_buildings_l(myid) + 1
1248                      build_ids_l(1) = building_id_f%var(j,i)
1249                   ENDIF
1250                ENDIF
1251             ENDDO
1252          ENDDO
1253!
1254!--       Determine number of different building ids for the entire domain
1255#if defined( __parallel ) 
1256          CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs,              &
1257                              MPI_INTEGER, MPI_SUM, comm2d, ierr ) 
1258#else
1259          num_buildings = num_buildings_l
1260#endif
1261!
1262!--       Gather all buildings ids on each PEs.
1263!--       First, allocate array encompassing all building ids in model domain. 
1264          ALLOCATE( build_ids(1:SUM(num_buildings)) )
1265#if defined( __parallel ) 
1266!
1267!--       Allocate array for displacements.
1268!--       As each PE may has a different number of buildings, so that
1269!--       the block sizes send by each PE may not be equal. Hence,
1270!--       information about the respective displacement is required, indicating
1271!--       the respective adress where each MPI-task writes into the receive
1272!--       buffer array 
1273          ALLOCATE( displace_dum(0:numprocs-1) )
1274          displace_dum(0) = 0
1275          DO i = 1, numprocs-1
1276             displace_dum(i) = displace_dum(i-1) + num_buildings(i-1)
1277          ENDDO
1278
1279          CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                 &
1280                               num_buildings(myid),                                  &
1281                               MPI_INTEGER,                                          &
1282                               build_ids,                                            &
1283                               num_buildings,                                        &
1284                               displace_dum,                                         & 
1285                               MPI_INTEGER,                                          &
1286                               comm2d, ierr )   
1287
1288          DEALLOCATE( displace_dum )
1289
1290#else
1291          build_ids = build_ids_l
1292#endif
1293
1294!
1295!--       Note, in parallel mode building ids can occure mutliple times, as
1296!--       each PE has send its own ids. Therefore, sort out building ids which
1297!--       appear more than one time.
1298          num_build = 0
1299          DO  nr = 1, SIZE(build_ids)
1300
1301             IF ( ALLOCATED(build_ids_final) )  THEN
1302                IF ( ANY( build_ids(nr) == build_ids_final ) )  THEN
1303                   CYCLE
1304                ELSE
1305                   num_build = num_build + 1
1306!
1307!--                Resize
1308                   ALLOCATE( build_ids_final_tmp(1:num_build) )
1309                   build_ids_final_tmp(1:num_build-1) = build_ids_final(1:num_build-1)
1310                   DEALLOCATE( build_ids_final )
1311                   ALLOCATE( build_ids_final(1:num_build) )
1312                   build_ids_final(1:num_build-1) = build_ids_final_tmp(1:num_build-1)
1313                   build_ids_final(num_build) = build_ids(nr)
1314                   DEALLOCATE( build_ids_final_tmp )
1315                ENDIF             
1316             ELSE
1317                num_build = num_build + 1
1318                ALLOCATE( build_ids_final(1:num_build) )
1319                build_ids_final(num_build) = build_ids(nr)
1320             ENDIF
1321          ENDDO
1322
1323!
1324!--       Determine maximumum terrain height occupied by the respective
1325!--       building and temporalily store on oro_max
1326          ALLOCATE( oro_max_l(1:SIZE(build_ids_final)) )
1327          ALLOCATE( oro_max(1:SIZE(build_ids_final))   )
1328          oro_max_l = 0.0_wp
1329
1330          DO  nr = 1, SIZE(build_ids_final)
1331             oro_max_l(nr) = MAXVAL(                                           &
1332                              MERGE( terrain_height_f%var(nys:nyn,nxl:nxr),    &
1333                                     0.0_wp,                                   &
1334                                     building_id_f%var(nys:nyn,nxl:nxr) ==     &
1335                                     build_ids_final(nr) ) )
1336          ENDDO
1337   
1338#if defined( __parallel )   
1339          IF ( SIZE(build_ids_final) >= 1 ) THEN
1340             CALL MPI_ALLREDUCE( oro_max_l, oro_max, SIZE( oro_max ), MPI_REAL,&
1341                                 MPI_MAX, comm2d, ierr ) 
1342          ENDIF
1343#else
1344          oro_max = oro_max_l
1345#endif
1346!
1347!--       Finally, determine discrete grid height of maximum orography occupied
1348!--       by a building. Use all-or-nothing approach, i.e. if terrain
1349!--       exceeds the scalar level the grid box is fully terrain and the
1350!--       maximum terrain is set to the zw level.
1351!--       terrain or
1352          oro_max_l = 0.0
1353          DO  nr = 1, SIZE(build_ids_final)
1354             DO  k = nzb, nzt
1355                IF ( zu(k) - ocean_offset <= oro_max(nr) )                     &
1356                   oro_max_l(nr) = zw(k) - ocean_offset
1357             ENDDO
1358             oro_max(nr) = oro_max_l(nr)
1359          ENDDO
1360       ENDIF
1361!
1362!--    Allocate array for storing terrain height under buildings
1363       IF ( buildings_f%from_file )  THEN
1364          ALLOCATE( buildings_f%oro_max(nysg:nyng,nxlg:nxrg) )
1365          buildings_f%oro_max = buildings_f%fill1
1366       END IF
1367!
1368!--    Map orography as well as buildings onto grid.
1369       DO  i = nxl, nxr
1370          DO  j = nys, nyn
1371             topo_top_index = 0
1372!
1373!--          Obtain index in global building_id array
1374             IF ( buildings_f%from_file )  THEN
1375                IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1376!
1377!--                Determine index where maximum terrain height occupied by
1378!--                the respective building height is stored.
1379                   nr = MINLOC( ABS( build_ids_final -                         &
1380                                     building_id_f%var(j,i) ), DIM = 1 )
1381!
1382!--                Save grid-indexed oro_max
1383                   buildings_f%oro_max(j,i) = oro_max(nr)
1384                ENDIF
1385             ENDIF
1386             DO  k = nzb, nzt
1387!
1388!--             In a first step, if grid point is below or equal the given
1389!--             terrain height, grid point is flagged to be of type natural.
1390!--             Please note, in case there is also a building which is lower
1391!--             than the vertical grid spacing, initialization of surface
1392!--             attributes will not be correct as given surface information
1393!--             will not be in accordance to the classified grid points.
1394!--             Hence, in this case, also a building flag.
1395                IF ( zu(k) - ocean_offset <= terrain_height_f%var(j,i) )  THEN
1396                   topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1397                   topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 1 )
1398                   topo_top_index = k ! topo_top_index + 1
1399                ENDIF
1400!
1401!--             Set building grid points. Here, only consider 2D buildings.
1402!--             3D buildings require separate treatment.
1403                IF ( buildings_f%from_file  .AND.  buildings_f%lod == 1 )  THEN
1404!
1405!--                Fill-up the terrain to the level of maximum orography
1406!--                within the building-covered area.
1407                   IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1408!
1409!--                   Note, oro_max is always on zw level                   
1410                      IF ( zu(k) - ocean_offset < oro_max(nr) )  THEN
1411                         topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1412                         topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 1 )
1413                      ELSEIF ( zu(k) - ocean_offset <=                         &
1414                               oro_max(nr) + buildings_f%var_2d(j,i) )  THEN
1415                         topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1416                         topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 2 )
1417                      ENDIF
1418                   ENDIF
1419                ENDIF
1420             ENDDO
1421!
1422!--          Special treatment for non grid-resolved buildings. This case,
1423!--          the uppermost terrain grid point is flagged as building as well
1424!--          well, even though no building exists at all. However, the
1425!--          surface element will be identified as urban-surface and the
1426!--          input data provided by the drivers is consistent to the surface
1427!--          classification. Else, all non grid-resolved buildings would vanish
1428!--          and identified as terrain grid points, which, however, won't be
1429!--          consistent with the input data.
1430             IF ( buildings_f%from_file  .AND.  buildings_f%lod == 1 )  THEN
1431                IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1432                   DO  k = nzb, nzt
1433                      IF( zw(k) - ocean_offset == oro_max(nr) )  THEN
1434                         IF ( buildings_f%var_2d(j,i) <= zu(k+1) - zw(k) )  THEN
1435                            topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 2 )
1436                         ENDIF
1437                      ENDIF
1438                   ENDDO
1439                ENDIF
1440             ENDIF
1441!
1442!--          Map 3D buildings onto terrain height. 
1443!--          In case of any slopes, map building on top of maximum terrain
1444!--          height covered by the building. In other words, extend
1445!--          building down to the respective local terrain-surface height.
1446             IF ( buildings_f%from_file  .AND.  buildings_f%lod == 2 )  THEN
1447                IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
1448!
1449!--                Extend building down to the terrain surface, i.e. fill-up
1450!--                surface irregularities below a building. Note, oro_max
1451!--                is already a discrete height according to the all-or-nothing
1452!--                approach, i.e. grid box is either topography or atmosphere,
1453!--                terrain top is defined at upper bound of the grid box.
1454!--                Hence, check for zw in this case.
1455!--                Note, do this only for buildings which are surface mounted,
1456!--                i.e. building types 1-6. Below bridges, which are represented
1457!--                exclusively by building type 7, terrain shape should be
1458!--                maintained.
1459                   IF ( building_type_f%from_file )  THEN
1460                      IF ( building_type_f%var(j,i) /= 7 )  THEN
1461                         DO k = topo_top_index + 1, nzt + 1     
1462                            IF ( zu(k) - ocean_offset <= oro_max(nr) )  THEN
1463                               topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1464                               topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 1 )
1465                            ENDIF
1466                         ENDDO       
1467!                     
1468!--                      After surface irregularities are smoothen, determine
1469!--                      lower start index where building starts.
1470                         DO  k = nzb, nzt
1471                            IF ( zu(k) - ocean_offset <= oro_max(nr) )         &
1472                               topo_top_index = k
1473                         ENDDO
1474                      ENDIF
1475                   ENDIF
1476!
1477!--                Finally, map building on top.
1478                   k2 = 0
1479                   DO k = topo_top_index, nzt + 1
1480                      IF ( k2 <= buildings_f%nz-1 )  THEN
1481                         IF ( buildings_f%var_3d(k2,j,i) == 1 )  THEN
1482                            topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1483                            topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 2 )
1484                         ENDIF
1485                      ENDIF
1486                      k2 = k2 + 1
1487                   ENDDO
1488                ENDIF
1489             ENDIF
1490          ENDDO
1491       ENDDO
1492!
1493!--    Horizontal exchange the oro_max array, which is required to for
1494!--    initialization of building-surface properties.
1495       IF ( ALLOCATED( buildings_f%oro_max ) )  THEN
1496          CALL exchange_horiz_2d( buildings_f%oro_max(:,:), nbgp )
1497       ENDIF
1498!
1499!--    Deallocate temporary arrays required for processing and reading data
1500       IF ( ALLOCATED( oro_max         ) )  DEALLOCATE( oro_max         )
1501       IF ( ALLOCATED( oro_max_l       ) )  DEALLOCATE( oro_max_l       )
1502       IF ( ALLOCATED( build_ids_final ) )  DEALLOCATE( build_ids_final )
1503!
1504!-- Topography input via ASCII format.
1505    ELSE
1506       ocean_offset     = MERGE( zw(0), 0.0_wp, ocean_mode )
1507!
1508!--    Initialize topography bit 0 (indicates obstacle) everywhere to zero
1509!--    and clear all grid points at nzb, where alway a surface is defined.
1510!--    Further, set also bit 1 (indicates terrain) at nzb, which is further
1511!--    used for masked data output and further processing. Note, in the
1512!--    ASCII case no distinction is made between buildings and terrain,
1513!--    so that setting of bit 1 and 2 at the same time has no effect.
1514       topo_3d          = IBSET( topo_3d, 0 )
1515       topo_3d(nzb,:,:) = IBCLR( topo_3d(nzb,:,:), 0 )
1516       topo_3d(nzb,:,:) = IBSET( topo_3d(nzb,:,:), 1 )
1517       DO  i = nxl, nxr
1518          DO  j = nys, nyn
1519             DO  k = nzb, nzt
1520!
1521!--             Flag topography for all grid points which are below
1522!--             the local topography height.
1523!--             Note, each topography is flagged as building.
1524                IF ( zu(k) - ocean_offset <= buildings_f%var_2d(j,i) )  THEN
1525                   topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1526                   topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 2 ) !indicates building
1527                ENDIF
1528             ENDDO
1529          ENDDO
1530       ENDDO
1531    ENDIF
1532
1533    CALL exchange_horiz_int( topo_3d, nys, nyn, nxl, nxr, nzt, nbgp )
1534
1535    IF ( .NOT. bc_ns_cyc )  THEN
1536       IF ( nys == 0  )  topo_3d(:,-1,:)   = topo_3d(:,0,:)
1537       IF ( nyn == ny )  topo_3d(:,ny+1,:) = topo_3d(:,ny,:)
1538    ENDIF
1539
1540    IF ( .NOT. bc_lr_cyc )  THEN
1541       IF ( nxl == 0  )  topo_3d(:,:,-1)   = topo_3d(:,:,0)
1542       IF ( nxr == nx )  topo_3d(:,:,nx+1) = topo_3d(:,:,nx)         
1543    ENDIF
1544
1545 END SUBROUTINE process_topography
1546
1547
1548! Description:
1549! -----------------------------------------------------------------------------!
1550!> Filter topography, i.e. fill holes resolved by only one grid point. 
1551!> Such holes are suspected to lead to velocity blow-ups as continuity
1552!> equation on discrete grid cannot be fulfilled in such case.
1553!------------------------------------------------------------------------------!
1554 SUBROUTINE filter_topography( topo_3d )
1555
1556    USE control_parameters,                                                    &
1557        ONLY:  bc_lr_cyc, bc_ns_cyc, message_string
1558
1559    USE indices,                                                               &
1560        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb, nzt
1561
1562    USE netcdf_data_input_mod,                                                 &
1563        ONLY:  building_id_f, building_type_f 
1564
1565    USE  pegrid
1566
1567    IMPLICIT NONE
1568
1569    LOGICAL      ::  filled = .FALSE. !< flag indicating if holes were filled
1570
1571    INTEGER(iwp) ::  i          !< running index along x-direction
1572    INTEGER(iwp) ::  j          !< running index along y-direction
1573    INTEGER(iwp) ::  k          !< running index along z-direction
1574    INTEGER(iwp) ::  num_hole   !< number of holes (in topography) resolved by only one grid point
1575    INTEGER(iwp) ::  num_hole_l !< number of holes (in topography) resolved by only one grid point on local PE     
1576    INTEGER(iwp) ::  num_wall   !< number of surrounding vertical walls for a single grid point
1577
1578    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE            ::  topo_tmp          !< temporary 3D-topography used to fill holes
1579    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d           !< 3D-topography array merging buildings and orography
1580!
1581!-- Before checking for holes, set lateral boundary conditions for
1582!-- topography. After hole-filling, boundary conditions must be set again.
1583!-- Several iterations are performed, in order to fill holes which might
1584!-- emerge by the filling-algorithm itself.
1585    ALLOCATE( topo_tmp(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1586    topo_tmp = 0
1587
1588    num_hole = 99999
1589    DO WHILE ( num_hole > 0 )       
1590
1591       num_hole = 0   
1592       CALL exchange_horiz_int( topo_3d, nys, nyn, nxl, nxr, nzt, nbgp )
1593!
1594!--    Exchange also building ID and type. Note, building_type is an one-byte
1595!--    variable.
1596       IF ( building_id_f%from_file )                                          &
1597          CALL exchange_horiz_2d_int( building_id_f%var, nys, nyn, nxl, nxr, nbgp )
1598       IF ( building_type_f%from_file )                                        &
1599          CALL exchange_horiz_2d_byte( building_type_f%var, nys, nyn, nxl, nxr, nbgp )
1600
1601       topo_tmp = topo_3d
1602!
1603!--    In case of non-cyclic lateral boundaries, assume lateral boundary to be
1604!--    a solid wall. Thus, intermediate spaces of one grid point between
1605!--    boundary and some topographic structure will be filled.           
1606       IF ( .NOT. bc_ns_cyc )  THEN
1607          IF ( nys == 0  )  topo_tmp(:,-1,:)   = IBCLR( topo_tmp(:,0,:),  0 )
1608          IF ( nyn == ny )  topo_tmp(:,ny+1,:) = IBCLR( topo_tmp(:,ny,:), 0 )
1609       ENDIF
1610
1611       IF ( .NOT. bc_lr_cyc )  THEN
1612          IF ( nxl == 0  )  topo_tmp(:,:,-1)   = IBCLR( topo_tmp(:,:,0),  0 )
1613          IF ( nxr == nx )  topo_tmp(:,:,nx+1) = IBCLR( topo_tmp(:,:,nx), 0 )         
1614       ENDIF
1615
1616       num_hole_l = 0
1617       DO i = nxl, nxr
1618          DO j = nys, nyn
1619             DO  k = nzb+1, nzt
1620                IF ( BTEST( topo_tmp(k,j,i), 0 ) )  THEN
1621                   num_wall = 0
1622                   IF ( .NOT. BTEST( topo_tmp(k,j-1,i), 0 ) )                  &
1623                      num_wall = num_wall + 1
1624                   IF ( .NOT. BTEST( topo_tmp(k,j+1,i), 0 ) )                  &
1625                      num_wall = num_wall + 1
1626                   IF ( .NOT. BTEST( topo_tmp(k,j,i-1), 0 ) )                  &
1627                      num_wall = num_wall + 1
1628                   IF ( .NOT. BTEST( topo_tmp(k,j,i+1), 0 ) )                  &
1629                      num_wall = num_wall + 1
1630                   IF ( .NOT. BTEST( topo_tmp(k-1,j,i), 0 ) )                  &
1631                      num_wall = num_wall + 1   
1632                   IF ( .NOT. BTEST( topo_tmp(k+1,j,i), 0 ) )                  &
1633                      num_wall = num_wall + 1
1634
1635                   IF ( num_wall >= 4 )  THEN
1636                      num_hole_l     = num_hole_l + 1
1637!
1638!--                   Clear flag 0 and set special flag ( bit 4) to indicate
1639!--                   that new topography point is a result of filtering process.
1640                      topo_3d(k,j,i) = IBCLR( topo_3d(k,j,i), 0 )
1641                      topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 4 )
1642!
1643!--                   If filled grid point is occupied by a building, classify
1644!--                   it as building grid point.
1645                      IF ( building_type_f%from_file )  THEN
1646                         IF ( building_type_f%var(j,i)   /=                    & 
1647                              building_type_f%fill            .OR.             &       
1648                              building_type_f%var(j+1,i) /=                    & 
1649                              building_type_f%fill            .OR.             &               
1650                              building_type_f%var(j-1,i) /=                    &               
1651                              building_type_f%fill            .OR.             &               
1652                              building_type_f%var(j,i+1) /=                    &               
1653                              building_type_f%fill            .OR.             &               
1654                              building_type_f%var(j,i-1) /=                    &               
1655                              building_type_f%fill )  THEN
1656!
1657!--                         Set flag indicating building surfaces
1658                            topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 2 )
1659!
1660!--                         Set building_type and ID at this position if not
1661!--                         already set. This is required for proper
1662!--                         initialization of urban-surface energy balance
1663!--                         solver.
1664                            IF ( building_type_f%var(j,i) ==                   &
1665                                 building_type_f%fill )  THEN
1666
1667                               IF ( building_type_f%var(j+1,i) /=              &
1668                                    building_type_f%fill )  THEN
1669                                  building_type_f%var(j,i) =                   &
1670                                                    building_type_f%var(j+1,i)
1671                                  building_id_f%var(j,i) =                     &
1672                                                    building_id_f%var(j+1,i)
1673                               ELSEIF ( building_type_f%var(j-1,i) /=          &
1674                                        building_type_f%fill )  THEN
1675                                  building_type_f%var(j,i) =                   &
1676                                                    building_type_f%var(j-1,i)
1677                                  building_id_f%var(j,i) =                     &
1678                                                    building_id_f%var(j-1,i)
1679                               ELSEIF ( building_type_f%var(j,i+1) /=          &
1680                                        building_type_f%fill )  THEN
1681                                  building_type_f%var(j,i) =                   &
1682                                                    building_type_f%var(j,i+1)
1683                                  building_id_f%var(j,i) =                     &
1684                                                    building_id_f%var(j,i+1)
1685                               ELSEIF ( building_type_f%var(j,i-1) /=          &
1686                                        building_type_f%fill )  THEN
1687                                  building_type_f%var(j,i) =                   &
1688                                                    building_type_f%var(j,i-1)
1689                                  building_id_f%var(j,i) =                     &
1690                                                    building_id_f%var(j,i-1)
1691                               ENDIF
1692                            ENDIF
1693                         ENDIF
1694                      ENDIF
1695!
1696!--                   If filled grid point is already classified as building
1697!--                   everything is fine, else classify this grid point as
1698!--                   natural type grid point. This case, values for the
1699!--                   surface type are already set.
1700                      IF ( .NOT. BTEST( topo_3d(k,j,i), 2 ) )  THEN
1701                         topo_3d(k,j,i) = IBSET( topo_3d(k,j,i), 1 )
1702                      ENDIF
1703                   ENDIF
1704                ENDIF
1705             ENDDO
1706          ENDDO
1707       ENDDO
1708!
1709!--    Count the total number of holes, required for informative message.
1710#if defined( __parallel )
1711       CALL MPI_ALLREDUCE( num_hole_l, num_hole, 1, MPI_INTEGER, MPI_SUM,      &
1712                           comm2d, ierr )
1713#else
1714       num_hole = num_hole_l
1715#endif   
1716       IF ( num_hole > 0  .AND.  .NOT. filled )  filled = .TRUE.
1717
1718    ENDDO
1719!
1720!-- Create an informative message if any holes were filled.
1721    IF ( filled )  THEN
1722       WRITE( message_string, * ) 'Topography was filtered, i.e. holes ' //    &
1723                                  'resolved by only one grid point '     //    &
1724                                  'were filled during initialization.'
1725       CALL message( 'init_grid', 'PA0430', 0, 0, 0, 6, 0 )
1726    ENDIF
1727
1728    DEALLOCATE( topo_tmp )
1729!
1730!-- Finally, exchange topo_3d array again and if necessary set Neumann boundary
1731!-- condition in case of non-cyclic lateral boundaries.
1732    CALL exchange_horiz_int( topo_3d, nys, nyn, nxl, nxr, nzt, nbgp )
1733
1734    IF ( .NOT. bc_ns_cyc )  THEN
1735       IF ( nys == 0  )  topo_3d(:,-1,:)   = topo_3d(:,0,:)
1736       IF ( nyn == ny )  topo_3d(:,ny+1,:) = topo_3d(:,ny,:)
1737    ENDIF
1738
1739    IF ( .NOT. bc_lr_cyc )  THEN
1740       IF ( nxl == 0  )  topo_3d(:,:,-1)   = topo_3d(:,:,0)
1741       IF ( nxr == nx )  topo_3d(:,:,nx+1) = topo_3d(:,:,nx)         
1742    ENDIF
1743!
1744!-- Exchange building ID and type. Note, building_type is an one-byte variable.
1745    IF ( building_id_f%from_file )                                             &
1746       CALL exchange_horiz_2d_int( building_id_f%var, nys, nyn, nxl, nxr, nbgp )
1747    IF ( building_type_f%from_file )                                           &
1748       CALL exchange_horiz_2d_byte( building_type_f%var, nys, nyn, nxl, nxr, nbgp )
1749
1750 END SUBROUTINE filter_topography
1751
1752
1753! Description:
1754! -----------------------------------------------------------------------------!
1755!> Reads topography information from file or sets generic topography. Moreover,
1756!> all topography-relevant topography arrays are initialized, and grid flags
1757!> are set. 
1758!------------------------------------------------------------------------------!
1759 SUBROUTINE init_topo( topo )
1760
1761    USE arrays_3d,                                                             &
1762        ONLY:  zw
1763       
1764    USE control_parameters,                                                    &
1765        ONLY:  bc_lr_cyc, bc_ns_cyc, building_height, building_length_x,       &
1766               building_length_y, building_wall_left, building_wall_south,     &
1767               canyon_height, canyon_wall_left, canyon_wall_south,             &
1768               canyon_width_x, canyon_width_y, dp_level_ind_b, dz,             &
1769               message_string, topography, topography_grid_convention,         &
1770               tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,   &
1771               tunnel_wall_depth
1772         
1773    USE grid_variables,                                                        &
1774        ONLY:  dx, dy
1775       
1776    USE indices,                                                               &
1777        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
1778               nzb, nzt
1779   
1780    USE kinds
1781   
1782    USE netcdf_data_input_mod,                                                 &
1783        ONLY:  buildings_f, terrain_height_f 
1784
1785    USE pegrid
1786
1787    IMPLICIT NONE
1788
1789    INTEGER(iwp) ::  bh            !< temporary vertical index of building height
1790    INTEGER(iwp) ::  blx           !< grid point number of building size along x
1791    INTEGER(iwp) ::  bly           !< grid point number of building size along y
1792    INTEGER(iwp) ::  bxl           !< index for left building wall
1793    INTEGER(iwp) ::  bxr           !< index for right building wall
1794    INTEGER(iwp) ::  byn           !< index for north building wall
1795    INTEGER(iwp) ::  bys           !< index for south building wall
1796    INTEGER(iwp) ::  ch            !< temporary vertical index for canyon height
1797    INTEGER(iwp) ::  cwx           !< grid point number of canyon size along x
1798    INTEGER(iwp) ::  cwy           !< grid point number of canyon size along y
1799    INTEGER(iwp) ::  cxl           !< index for left canyon wall
1800    INTEGER(iwp) ::  cxr           !< index for right canyon wall
1801    INTEGER(iwp) ::  cyn           !< index for north canyon wall
1802    INTEGER(iwp) ::  cys           !< index for south canyon wall
1803    INTEGER(iwp) ::  i             !< index variable along x
1804    INTEGER(iwp) ::  j             !< index variable along y
1805    INTEGER(iwp) ::  k             !< index variable along z
1806    INTEGER(iwp) ::  hv_in         !< heavyside function to model inner tunnel surface
1807    INTEGER(iwp) ::  hv_out        !< heavyside function to model outer tunnel surface
1808    INTEGER(iwp) ::  txe_out       !< end position of outer tunnel wall in x
1809    INTEGER(iwp) ::  txs_out       !< start position of outer tunnel wall in x
1810    INTEGER(iwp) ::  tye_out       !< end position of outer tunnel wall in y
1811    INTEGER(iwp) ::  tys_out       !< start position of outer tunnel wall in y
1812    INTEGER(iwp) ::  txe_in        !< end position of inner tunnel wall in x
1813    INTEGER(iwp) ::  txs_in        !< start position of inner tunnel wall in x
1814    INTEGER(iwp) ::  tye_in        !< end position of inner tunnel wall in y
1815    INTEGER(iwp) ::  tys_in        !< start position of inner tunnel wall in y
1816    INTEGER(iwp) ::  td            !< tunnel wall depth
1817    INTEGER(iwp) ::  th            !< height of outer tunnel wall
1818
1819    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_local         !< index for topography top at cell-center
1820    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo !< input array for 3D topography and dummy array for setting "outer"-flags
1821!
1822!-- Check for correct setting of the namelist parameter topography. If
1823!-- topography information is read from file but topography = 'flat',
1824!-- initialization does not properly.
1825    IF ( ( buildings_f%from_file  .OR.  terrain_height_f%from_file )  .AND.    &
1826           TRIM( topography ) /= 'read_from_file' )  THEN
1827       message_string =  'If topography information is provided (via ' //      &
1828                         'Netcdf or ASCII input) topography = '        //      &
1829                         '"read_from_file" is required.'
1830       CALL message( 'init_grid', 'PA0437', 1, 2, 0, 6, 0 )     
1831    ENDIF
1832!
1833!-- Set outer and inner index arrays for non-flat topography.
1834!-- Here consistency checks concerning domain size and periodicity are
1835!-- necessary.
1836!-- Within this SELECT CASE structure only nzb_local is initialized
1837!-- individually depending on the chosen topography type, all other index
1838!-- arrays are initialized further below.
1839    SELECT CASE ( TRIM( topography ) )
1840
1841       CASE ( 'flat' )
1842!   
1843!--       Initialilize 3D topography array, used later for initializing flags
1844          topo(nzb+1:nzt+1,:,:) = IBSET( topo(nzb+1:nzt+1,:,:), 0 )
1845         
1846       CASE ( 'closed_channel' )
1847!   
1848!--       Initialilize 3D topography array, used later for initializing flags
1849          topo(nzb+1:nzt,:,:) = IBSET( topo(nzb+1:nzt,:,:), 0 ) 
1850
1851       CASE ( 'single_building' )
1852!
1853!--       Single rectangular building, by default centered in the middle of the
1854!--       total domain
1855          blx = NINT( building_length_x / dx )
1856          bly = NINT( building_length_y / dy )
1857          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
1858          IF ( ABS( zw(bh)   - building_height ) == &
1859               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
1860          IF ( building_wall_left == 9999999.9_wp )  THEN
1861             building_wall_left = ( nx + 1 - blx ) / 2 * dx
1862          ENDIF
1863          bxl = NINT( building_wall_left / dx )
1864          bxr = bxl + blx
1865
1866          IF ( building_wall_south == 9999999.9_wp )  THEN
1867              building_wall_south = ( ny + 1 - bly ) / 2 * dy
1868          ENDIF
1869          bys = NINT( building_wall_south / dy )
1870          byn = bys + bly
1871
1872!
1873!--       Building size has to meet some requirements
1874          IF ( ( bxl < 1 ) .OR. ( bxr > nx-1 ) .OR. ( bxr < bxl+3 ) .OR.       &
1875               ( bys < 1 ) .OR. ( byn > ny-1 ) .OR. ( byn < bys+3 ) )  THEN
1876             WRITE( message_string, * ) 'inconsistent building parameters:',   &
1877                                      '&bxl=', bxl, 'bxr=', bxr, 'bys=', bys,  &
1878                                      'byn=', byn, 'nx=', nx, 'ny=', ny
1879             CALL message( 'init_grid', 'PA0203', 1, 2, 0, 6, 0 )
1880          ENDIF
1881
1882          ALLOCATE( nzb_local(nysg:nyng,nxlg:nxrg) )
1883          nzb_local = 0
1884!
1885!--       Define the building.
1886          IF ( bxl <= nxr  .AND.  bxr >= nxl  .AND.                            &
1887               bys <= nyn  .AND.  byn >= nys )                                 & 
1888             nzb_local(MAX(nys,bys):MIN(nyn,byn),MAX(nxl,bxl):MIN(nxr,bxr)) = bh
1889!
1890!--       Set bit array on basis of nzb_local
1891          DO  i = nxl, nxr
1892             DO  j = nys, nyn
1893                topo(nzb_local(j,i)+1:nzt+1,j,i) =                             &
1894                                 IBSET( topo(nzb_local(j,i)+1:nzt+1,j,i), 0 ) 
1895             ENDDO
1896          ENDDO
1897       
1898          DEALLOCATE( nzb_local )
1899
1900          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
1901!
1902!--       Set boundary conditions also for flags. Can be interpreted as Neumann
1903!--       boundary conditions for topography.
1904          IF ( .NOT. bc_ns_cyc )  THEN
1905             IF ( nys == 0  )  THEN
1906                DO  i = 1, nbgp     
1907                   topo(:,nys-i,:)   = topo(:,nys,:)
1908                ENDDO
1909             ENDIF
1910             IF ( nyn == ny )  THEN
1911                DO  i = 1, nbgp 
1912                   topo(:,nyn+i,:) = topo(:,nyn,:)
1913                ENDDO
1914             ENDIF
1915          ENDIF
1916          IF ( .NOT. bc_lr_cyc )  THEN
1917             IF ( nxl == 0  )  THEN
1918                DO  i = 1, nbgp   
1919                   topo(:,:,nxl-i)   = topo(:,:,nxl)
1920                ENDDO
1921             ENDIF
1922             IF ( nxr == nx )  THEN
1923                DO  i = 1, nbgp   
1924                   topo(:,:,nxr+i) = topo(:,:,nxr)     
1925                ENDDO
1926             ENDIF     
1927          ENDIF
1928
1929       CASE ( 'single_street_canyon' )
1930!
1931!--       Single quasi-2D street canyon of infinite length in x or y direction.
1932!--       The canyon is centered in the other direction by default.
1933          IF ( canyon_width_x /= 9999999.9_wp )  THEN
1934!
1935!--          Street canyon in y direction
1936             cwx = NINT( canyon_width_x / dx )
1937             IF ( canyon_wall_left == 9999999.9_wp )  THEN
1938                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
1939             ENDIF
1940             cxl = NINT( canyon_wall_left / dx )
1941             cxr = cxl + cwx
1942          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
1943!
1944!--          Street canyon in x direction
1945             cwy = NINT( canyon_width_y / dy )
1946             IF ( canyon_wall_south == 9999999.9_wp )  THEN
1947                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
1948             ENDIF
1949             cys = NINT( canyon_wall_south / dy )
1950             cyn = cys + cwy
1951     
1952          ELSE
1953             
1954             message_string = 'no street canyon width given'
1955             CALL message( 'init_grid', 'PA0204', 1, 2, 0, 6, 0 )
1956 
1957          ENDIF
1958
1959          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
1960          IF ( ABS( zw(ch)   - canyon_height ) == &
1961               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
1962          dp_level_ind_b = ch
1963!
1964!--       Street canyon size has to meet some requirements
1965          IF ( canyon_width_x /= 9999999.9_wp )  THEN
1966             IF ( ( cxl < 1 ) .OR. ( cxr > nx-1 ) .OR. ( cwx < 3 ) .OR.        &
1967                  ( ch < 3 ) )  THEN
1968                WRITE( message_string, * ) 'inconsistent canyon parameters:',  &
1969                                           '&cxl=', cxl, ' cxr=', cxr,         &
1970                                           ' cwx=', cwx,                       &
1971                                           ' ch=', ch, ' nx=', nx, ' ny=', ny
1972                CALL message( 'init_grid', 'PA0205', 1, 2, 0, 6, 0 ) 
1973             ENDIF
1974          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
1975             IF ( ( cys < 1 ) .OR. ( cyn > ny-1 ) .OR. ( cwy < 3 ) .OR.        &
1976                  ( ch < 3 ) )  THEN
1977                WRITE( message_string, * ) 'inconsistent canyon parameters:',  &
1978                                           '&cys=', cys, ' cyn=', cyn,         &
1979                                           ' cwy=', cwy,                       &
1980                                           ' ch=', ch, ' nx=', nx, ' ny=', ny
1981                CALL message( 'init_grid', 'PA0206', 1, 2, 0, 6, 0 ) 
1982             ENDIF
1983          ENDIF
1984          IF ( canyon_width_x /= 9999999.9_wp .AND.                            &                 
1985               canyon_width_y /= 9999999.9_wp )  THEN
1986             message_string = 'inconsistent canyon parameters:' //             &   
1987                              '&street canyon can only be oriented' //         &
1988                              ' either in x- or in y-direction'
1989             CALL message( 'init_grid', 'PA0207', 1, 2, 0, 6, 0 )
1990          ENDIF
1991
1992          ALLOCATE( nzb_local(nysg:nyng,nxlg:nxrg) )
1993          nzb_local = ch
1994          IF ( canyon_width_x /= 9999999.9_wp )  THEN
1995             IF ( cxl <= nxr  .AND.  cxr >= nxl )                              &
1996                nzb_local(:,MAX(nxl,cxl+1):MIN(nxr,cxr-1)) = 0
1997          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
1998             IF ( cys <= nyn  .AND.  cyn >= nys )                              &         
1999                nzb_local(MAX(nys,cys+1):MIN(nyn,cyn-1),:) = 0
2000          ENDIF
2001!
2002!--       Set bit array on basis of nzb_local
2003          DO  i = nxl, nxr
2004             DO  j = nys, nyn
2005                topo(nzb_local(j,i)+1:nzt+1,j,i) =                             &
2006                                 IBSET( topo(nzb_local(j,i)+1:nzt+1,j,i), 0 ) 
2007             ENDDO
2008          ENDDO
2009          DEALLOCATE( nzb_local )
2010
2011          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
2012!
2013!--       Set boundary conditions also for flags. Can be interpreted as Neumann
2014!--       boundary conditions for topography.
2015          IF ( .NOT. bc_ns_cyc )  THEN
2016             IF ( nys == 0  )  THEN
2017                DO  i = 1, nbgp     
2018                   topo(:,nys-i,:)   = topo(:,nys,:)
2019                ENDDO
2020             ENDIF
2021             IF ( nyn == ny )  THEN
2022                DO  i = 1, nbgp 
2023                   topo(:,nyn+i,:) = topo(:,nyn,:)
2024                ENDDO
2025             ENDIF
2026          ENDIF
2027          IF ( .NOT. bc_lr_cyc )  THEN
2028             IF ( nxl == 0  )  THEN
2029                DO  i = 1, nbgp   
2030                   topo(:,:,nxl-i)   = topo(:,:,nxl)
2031                ENDDO
2032             ENDIF
2033             IF ( nxr == nx )  THEN
2034                DO  i = 1, nbgp   
2035                   topo(:,:,nxr+i) = topo(:,:,nxr)     
2036                ENDDO
2037             ENDIF     
2038          ENDIF
2039
2040       CASE ( 'tunnel' )
2041
2042!
2043!--       Tunnel height
2044          IF ( tunnel_height == 9999999.9_wp )  THEN
2045             th = zw( INT( 0.2 * nz) )
2046          ELSE
2047             th = tunnel_height
2048          ENDIF
2049!
2050!--       Tunnel-wall depth
2051          IF ( tunnel_wall_depth == 9999999.9_wp )  THEN 
2052             td = MAX ( dx, dy, dz(1) )
2053          ELSE
2054             td = tunnel_wall_depth
2055          ENDIF
2056!
2057!--       Check for tunnel width
2058          IF ( tunnel_width_x == 9999999.9_wp  .AND.                           &
2059               tunnel_width_y == 9999999.9_wp  )  THEN
2060             message_string = 'No tunnel width is given. '
2061             CALL message( 'init_grid', 'PA0280', 1, 2, 0, 6, 0 )
2062          ENDIF
2063          IF ( tunnel_width_x /= 9999999.9_wp  .AND.                           &
2064               tunnel_width_y /= 9999999.9_wp  )  THEN
2065             message_string = 'Inconsistent tunnel parameters:' //             &   
2066                              'tunnel can only be oriented' //                 &
2067                              'either in x- or in y-direction.'
2068             CALL message( 'init_grid', 'PA0281', 1, 2, 0, 6, 0 )
2069          ENDIF
2070!
2071!--       Tunnel axis along y
2072          IF ( tunnel_width_x /= 9999999.9_wp )  THEN
2073             IF ( tunnel_width_x > ( nx + 1 ) * dx )  THEN
2074                message_string = 'Tunnel width too large'
2075                CALL message( 'init_grid', 'PA0282', 1, 2, 0, 6, 0 )
2076             ENDIF
2077
2078             txs_out = INT( ( nx + 1 ) * 0.5_wp * dx - tunnel_width_x * 0.5_wp )
2079             txe_out = INT( ( nx + 1 ) * 0.5_wp * dx + tunnel_width_x * 0.5_wp )
2080             txs_in  = INT( ( nx + 1 ) * 0.5_wp * dx -                         &
2081                                      ( tunnel_width_x * 0.5_wp - td ) )
2082             txe_in  = INT( ( nx + 1 ) * 0.5_wp * dx +                         &
2083                                   ( tunnel_width_x * 0.5_wp - td ) )
2084
2085             tys_out = INT( ( ny + 1 ) * 0.5_wp * dy - tunnel_length * 0.5_wp )
2086             tye_out = INT( ( ny + 1 ) * 0.5_wp * dy + tunnel_length * 0.5_wp )
2087             tys_in  = tys_out
2088             tye_in  = tye_out
2089          ENDIF
2090          IF ( tunnel_width_x /= 9999999.9_wp  .AND.                           &   
2091               tunnel_width_x - 2.0_wp * td <= 2.0_wp * dx )                   &
2092          THEN
2093             message_string = 'Tunnel width too small'
2094             CALL message( 'init_grid', 'PA0175', 1, 2, 0, 6, 0 )
2095          ENDIF
2096          IF ( tunnel_width_y /= 9999999.9_wp  .AND.                           &
2097               tunnel_width_y - 2.0_wp * td <= 2.0_wp * dy )                   &
2098          THEN
2099             message_string = 'Tunnel width too small'
2100             CALL message( 'init_grid', 'PA0455', 1, 2, 0, 6, 0 )
2101          ENDIF
2102!
2103!--       Tunnel axis along x
2104          IF ( tunnel_width_y /= 9999999.9_wp )  THEN
2105             IF ( tunnel_width_y > ( ny + 1 ) * dy )  THEN
2106                message_string = 'Tunnel width too large'
2107                CALL message( 'init_grid', 'PA0456', 1, 2, 0, 6, 0 )
2108             ENDIF
2109
2110             txs_out = INT( ( nx + 1 ) * 0.5_wp * dx - tunnel_length * 0.5_wp )
2111             txe_out = INT( ( nx + 1 ) * 0.5_wp * dx + tunnel_length * 0.5_wp )
2112             txs_in  = txs_out
2113             txe_in  = txe_out
2114
2115             tys_out = INT( ( ny + 1 ) * 0.5_wp * dy - tunnel_width_y * 0.5_wp )
2116             tye_out = INT( ( ny + 1 ) * 0.5_wp * dy + tunnel_width_y * 0.5_wp )
2117             tys_in  = INT( ( ny + 1 ) * 0.5_wp * dy -                         &
2118                                        ( tunnel_width_y * 0.5_wp - td ) )
2119             tye_in  = INT( ( ny + 1 ) * 0.5_wp * dy +                         &
2120                                     ( tunnel_width_y * 0.5_wp - td ) )
2121          ENDIF
2122
2123          topo = 0
2124          DO  i = nxl, nxr
2125             DO  j = nys, nyn
2126!
2127!--             Use heaviside function to model outer tunnel surface
2128                hv_out = th * 0.5_wp *                                         &
2129                              ( ( SIGN( 1.0_wp, i * dx - txs_out ) + 1.0_wp )  &
2130                              - ( SIGN( 1.0_wp, i * dx - txe_out ) + 1.0_wp ) )
2131
2132                hv_out = hv_out * 0.5_wp *                                     &
2133                            ( ( SIGN( 1.0_wp, j * dy - tys_out ) + 1.0_wp )    &
2134                            - ( SIGN( 1.0_wp, j * dy - tye_out ) + 1.0_wp ) )
2135!   
2136!--             Use heaviside function to model inner tunnel surface
2137                hv_in  = ( th - td ) * 0.5_wp *                                &
2138                                ( ( SIGN( 1.0_wp, i * dx - txs_in ) + 1.0_wp ) &
2139                                - ( SIGN( 1.0_wp, i * dx - txe_in ) + 1.0_wp ) )
2140
2141                hv_in = hv_in * 0.5_wp *                                       &
2142                                ( ( SIGN( 1.0_wp, j * dy - tys_in ) + 1.0_wp ) &
2143                                - ( SIGN( 1.0_wp, j * dy - tye_in ) + 1.0_wp ) )
2144!
2145!--             Set flags at x-y-positions without any tunnel surface
2146                IF ( hv_out - hv_in == 0.0_wp )  THEN
2147                   topo(nzb+1:nzt+1,j,i) = IBSET( topo(nzb+1:nzt+1,j,i), 0 )
2148!
2149!--             Set flags at x-y-positions with tunnel surfaces
2150                ELSE
2151                   DO  k = nzb + 1, nzt + 1
2152!
2153!--                   Inner tunnel
2154                      IF ( hv_out - hv_in == th )  THEN
2155                         IF ( zw(k) <= hv_out )  THEN
2156                            topo(k,j,i) = IBCLR( topo(k,j,i), 0 )
2157                         ELSE
2158                            topo(k,j,i) = IBSET( topo(k,j,i), 0 )
2159                         ENDIF
2160                      ENDIF
2161!
2162!--                   Lateral tunnel walls
2163                      IF ( hv_out - hv_in == td )  THEN
2164                         IF ( zw(k) <= hv_in )  THEN
2165                            topo(k,j,i) = IBSET( topo(k,j,i), 0 )
2166                         ELSEIF ( zw(k) > hv_in  .AND.  zw(k) <= hv_out )  THEN
2167                            topo(k,j,i) = IBCLR( topo(k,j,i), 0 )
2168                         ELSEIF ( zw(k) > hv_out )  THEN
2169                            topo(k,j,i) = IBSET( topo(k,j,i), 0 )
2170                         ENDIF
2171                      ENDIF
2172                   ENDDO
2173                ENDIF
2174             ENDDO
2175          ENDDO
2176
2177          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
2178!
2179!--       Set boundary conditions also for flags. Can be interpreted as Neumann
2180!--       boundary conditions for topography.
2181          IF ( .NOT. bc_ns_cyc )  THEN
2182             IF ( nys == 0  )  THEN
2183                DO  i = 1, nbgp     
2184                   topo(:,nys-i,:)   = topo(:,nys,:)
2185                ENDDO
2186             ENDIF
2187             IF ( nyn == ny )  THEN
2188                DO  i = 1, nbgp 
2189                   topo(:,nyn+i,:) = topo(:,nyn,:)
2190                ENDDO
2191             ENDIF
2192          ENDIF
2193          IF ( .NOT. bc_lr_cyc )  THEN
2194             IF ( nxl == 0  )  THEN
2195                DO  i = 1, nbgp   
2196                   topo(:,:,nxl-i)   = topo(:,:,nxl)
2197                ENDDO
2198             ENDIF
2199             IF ( nxr == nx )  THEN
2200                DO  i = 1, nbgp   
2201                   topo(:,:,nxr+i) = topo(:,:,nxr)     
2202                ENDDO
2203             ENDIF     
2204          ENDIF
2205
2206       CASE ( 'read_from_file' )
2207!
2208!--       Note, topography information have been already read. 
2209!--       If required, further process topography, i.e. reference buildings on
2210!--       top of orography and set temporary 3D topography array, which is
2211!--       used later to set grid flags. Calling of this rouinte is also
2212!--       required in case of ASCII input, even though no distinction between
2213!--       terrain- and building height is made in this case. 
2214          CALL process_topography( topo )
2215!
2216!--       Filter holes resolved by only one grid-point
2217          CALL filter_topography( topo )
2218!
2219!--       Exchange ghost-points, as well as add cyclic or Neumann boundary
2220!--       conditions.
2221          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
2222!
2223!--       Set lateral boundary conditions for topography on all ghost layers
2224          IF ( .NOT. bc_ns_cyc )  THEN
2225             IF ( nys == 0  )  THEN
2226                DO  i = 1, nbgp         
2227                   topo(:,nys-i,:) = topo(:,nys,:)
2228                ENDDO
2229             ENDIF
2230             IF ( nyn == ny )  THEN
2231                DO  i = 1, nbgp         
2232                   topo(:,nyn+i,:) = topo(:,nyn,:)
2233                ENDDO
2234             ENDIF
2235          ENDIF
2236
2237          IF ( .NOT. bc_lr_cyc )  THEN
2238             IF ( nxl == 0  )  THEN
2239                DO  i = 1, nbgp 
2240                   topo(:,:,nxl-i) = topo(:,:,nxl)
2241                ENDDO
2242             ENDIF
2243             IF ( nxr == nx )  THEN
2244                DO  i = 1, nbgp 
2245                   topo(:,:,nxr+i) = topo(:,:,nxr)
2246                ENDDO
2247             ENDIF
2248          ENDIF
2249
2250
2251       CASE DEFAULT
2252!   
2253!--       The DEFAULT case is reached either if the parameter topography
2254!--       contains a wrong character string or if the user has defined a special
2255!--       case in the user interface. There, the subroutine user_init_grid
2256!--       checks which of these two conditions applies.
2257          CALL user_init_grid( topo )
2258          CALL filter_topography( topo )
2259
2260    END SELECT
2261!
2262!-- Consistency checks and index array initialization are only required for
2263!-- non-flat topography.
2264    IF ( TRIM( topography ) /= 'flat' )  THEN
2265!
2266!--    In case of non-flat topography, check whether the convention how to
2267!--    define the topography grid has been set correctly, or whether the default
2268!--    is applicable. If this is not possible, abort.
2269       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
2270          IF ( TRIM( topography ) /= 'closed_channel' .AND.                    &
2271               TRIM( topography ) /= 'single_building' .AND.                   &
2272               TRIM( topography ) /= 'single_street_canyon' .AND.              &
2273               TRIM( topography ) /= 'tunnel'  .AND.                           &
2274               TRIM( topography ) /= 'read_from_file')  THEN
2275!--          The default value is not applicable here, because it is only valid
2276!--          for the four standard cases 'single_building',
2277!--          'single_street_canyon', 'tunnel' and 'read_from_file'
2278!--          defined in init_grid.
2279             WRITE( message_string, * )                                        &
2280               'The value for "topography_grid_convention" ',                  &
2281               'is not set. Its default value is & only valid for ',           &
2282               '"topography" = ''single_building'', ''tunnel'' ',              &
2283               '''single_street_canyon'', ''closed_channel'' & or ',           &
2284               '''read_from_file''.',                                          &
2285               '& Choose ''cell_edge'' or ''cell_center''.'
2286             CALL message( 'init_grid', 'PA0239', 1, 2, 0, 6, 0 )
2287          ELSE
2288!--          The default value is applicable here.
2289!--          Set convention according to topography.
2290             IF ( TRIM( topography ) == 'single_building' .OR.                 &
2291                  TRIM( topography ) == 'single_street_canyon' )  THEN
2292                topography_grid_convention = 'cell_edge'
2293             ELSEIF ( TRIM( topography ) == 'read_from_file'  .OR.             &
2294                      TRIM( topography ) == 'tunnel')  THEN
2295                topography_grid_convention = 'cell_center'
2296             ENDIF
2297          ENDIF
2298       ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.        &
2299                TRIM( topography_grid_convention ) /= 'cell_center' )  THEN
2300          WRITE( message_string, * )                                           &
2301            'The value for "topography_grid_convention" is ',                  &
2302            'not recognized.& Choose ''cell_edge'' or ''cell_center''.'
2303          CALL message( 'init_grid', 'PA0240', 1, 2, 0, 6, 0 )
2304       ENDIF
2305
2306
2307       IF ( topography_grid_convention == 'cell_edge' )  THEN
2308!
2309!--       The array nzb_local as defined using the 'cell_edge' convention
2310!--       describes the actual total size of topography which is defined at the
2311!--       cell edges where u=0 on the topography walls in x-direction and v=0
2312!--       on the topography walls in y-direction. However, PALM uses individual
2313!--       arrays nzb_u|v|w|s_inner|outer that are based on nzb_s_inner.
2314!--       Therefore, the extent of topography in nzb_local is now reduced by
2315!--       1dx at the E topography walls and by 1dy at the N topography walls
2316!--       to form the basis for nzb_s_inner.
2317!--       Note, the reverse memory access (i-j instead of j-i) is absolutely
2318!--       required at this point.
2319          DO  j = nys+1, nyn+1
2320             DO  i = nxl-1, nxr
2321                DO  k = nzb, nzt+1
2322                   IF ( BTEST( topo(k,j,i), 0 )  .OR.                          &
2323                        BTEST( topo(k,j,i+1), 0 ) )                            &
2324                       topo(k,j,i) = IBSET( topo(k,j,i), 0 )
2325                ENDDO
2326             ENDDO
2327          ENDDO     
2328          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
2329
2330          DO  i = nxl, nxr+1
2331             DO  j = nys-1, nyn
2332                DO  k = nzb, nzt+1
2333                   IF ( BTEST( topo(k,j,i), 0 )  .OR.                          &
2334                        BTEST( topo(k,j+1,i), 0 ) )                            &
2335                      topo(k,j,i) = IBSET( topo(k,j,i), 0 )
2336                ENDDO
2337             ENDDO
2338          ENDDO 
2339          CALL exchange_horiz_int( topo, nys, nyn, nxl, nxr, nzt, nbgp )
2340   
2341       ENDIF
2342    ENDIF
2343
2344
2345 END SUBROUTINE init_topo
2346
2347 SUBROUTINE set_topo_flags(topo)
2348
2349    USE control_parameters,                                                    &
2350        ONLY:  bc_lr_cyc, bc_ns_cyc, constant_flux_layer,                      &
2351               scalar_advec, topography, use_surface_fluxes, use_top_fluxes
2352
2353    USE indices,                                                               &
2354        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb,  &
2355               nzt, topo_top_ind, wall_flags_static_0
2356
2357    USE kinds
2358
2359    IMPLICIT NONE
2360
2361    INTEGER(iwp) ::  i             !< index variable along x
2362    INTEGER(iwp) ::  ibit          !< integer bit position of topgraphy masking array
2363    INTEGER(iwp) ::  j             !< index variable along y
2364    INTEGER(iwp) ::  k             !< index variable along z
2365
2366    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo !< input array for 3D topography and dummy array for setting "outer"-flags
2367
2368    ALLOCATE( wall_flags_static_0(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2369    wall_flags_static_0 = 0
2370!
2371!-- Set-up topography flags. First, set flags only for s, u, v and w-grid.
2372!-- Further special flags will be set in following loops.
2373    DO  i = nxl, nxr
2374       DO  j = nys, nyn
2375          DO  k = nzb, nzt+1
2376!
2377!--          scalar grid
2378             IF ( BTEST( topo(k,j,i), 0 ) )                                    &
2379                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 0 )
2380!
2381!--          u grid
2382             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
2383                  BTEST( topo(k,j,i-1), 0 ) )                                  &
2384                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 1 )
2385!
2386!--          v grid
2387             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
2388                  BTEST( topo(k,j-1,i), 0 ) )                                  &
2389                 wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 2 )
2390
2391          ENDDO
2392
2393          DO k = nzb, nzt
2394!
2395!--          w grid
2396             IF ( BTEST( topo(k,j,i),   0 )  .AND.                             &
2397                  BTEST( topo(k+1,j,i), 0 ) )                                  &
2398                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 3 )
2399          ENDDO
2400         
2401          IF ( topography /= 'closed_channel' ) THEN
2402             wall_flags_static_0(nzt+1,j,i) = IBSET( wall_flags_static_0(nzt+1,j,i), 3 )
2403          ENDIF
2404
2405       ENDDO
2406    ENDDO
2407
2408    CALL exchange_horiz_int( wall_flags_static_0, nys, nyn, nxl, nxr, nzt, nbgp )
2409!
2410!-- Set outer array for scalars to mask near-surface grid points. Note, on
2411!-- basis of flag 24 futher flags will be derived which are used to control
2412!-- production of subgrid TKE production near walls.
2413    DO i = nxl, nxr
2414       DO j = nys, nyn
2415          DO k = nzb, nzt+1
2416             IF ( BTEST( wall_flags_static_0(k,j-1,i), 0 )    .AND.                   &
2417                  BTEST( wall_flags_static_0(k,j+1,i), 0 )    .AND.                   &
2418                  BTEST( wall_flags_static_0(k,j,i-1), 0 )    .AND.                   &
2419                  BTEST( wall_flags_static_0(k,j,i+1), 0 )    .AND.                   &
2420                  BTEST( wall_flags_static_0(k,j-1,i-1), 0 )  .AND.                   &
2421                  BTEST( wall_flags_static_0(k,j+1,i-1), 0 )  .AND.                   &
2422                  BTEST( wall_flags_static_0(k,j-1,i+1), 0 )  .AND.                   &
2423                  BTEST( wall_flags_static_0(k,j+1,i+1), 0 ) )                        &
2424                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 24 )
2425          ENDDO
2426       ENDDO
2427    ENDDO
2428!
2429!-- Set further special flags
2430    DO i = nxl, nxr
2431       DO j = nys, nyn
2432          DO k = nzb, nzt+1
2433!
2434!--          scalar grid, former nzb_diff_s_inner.
2435!--          Note, use this flag also to mask topography in diffusion_u and
2436!--          diffusion_v along the vertical direction. In case of
2437!--          use_surface_fluxes, fluxes are calculated via MOST, else, simple
2438!--          gradient approach is applied. Please note, in case of u- and v-
2439!--          diffuison, a small error is made at edges (on the east side for u,
2440!--          at the north side for v), since topography on scalar grid point
2441!--          is used instead of topography on u/v-grid. As number of topography grid
2442!--          points on uv-grid is different than s-grid, different number of
2443!--          surface elements would be required. In order to avoid this,
2444!--          treat edges (u(k,j,i+1)) simply by a gradient approach, i.e. these
2445!--          points are not masked within diffusion_u. Tests had shown that the
2446!--          effect on the flow is negligible.
2447             IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
2448                IF ( BTEST( wall_flags_static_0(k,j,i), 0 ) )                         &
2449                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 8 )
2450             ELSE
2451                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 8 )
2452             ENDIF
2453
2454          ENDDO
2455!
2456!--       Special flag to control vertical diffusion at model top - former
2457!--       nzt_diff
2458          wall_flags_static_0(:,j,i) = IBSET( wall_flags_static_0(:,j,i), 9 )
2459          IF ( use_top_fluxes )                                                &
2460             wall_flags_static_0(nzt+1,j,i) = IBCLR( wall_flags_static_0(nzt+1,j,i), 9 )
2461
2462
2463          DO k = nzb+1, nzt
2464!
2465!--          Special flag on u grid, former nzb_u_inner + 1, required   
2466!--          for disturb_field and initialization. Do not disturb directly at
2467!--          topography, as well as initialize u with zero one grid point outside
2468!--          of topography.
2469             IF ( BTEST( wall_flags_static_0(k-1,j,i), 1 )  .AND.                     &
2470                  BTEST( wall_flags_static_0(k,j,i),   1 )  .AND.                     &
2471                  BTEST( wall_flags_static_0(k+1,j,i), 1 ) )                          &
2472                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 20 )
2473!
2474!--          Special flag on v grid, former nzb_v_inner + 1, required   
2475!--          for disturb_field and initialization. Do not disturb directly at
2476!--          topography, as well as initialize v with zero one grid point outside
2477!--          of topography.
2478             IF ( BTEST( wall_flags_static_0(k-1,j,i), 2 )  .AND.                     &
2479                  BTEST( wall_flags_static_0(k,j,i),   2 )  .AND.                     &
2480                  BTEST( wall_flags_static_0(k+1,j,i), 2 ) )                          &
2481                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 21 )
2482!
2483!--          Special flag on scalar grid, former nzb_s_inner+1. Used for
2484!--          lpm_sgs_tke
2485             IF ( BTEST( wall_flags_static_0(k,j,i),   0 )  .AND.                     &
2486                  BTEST( wall_flags_static_0(k-1,j,i), 0 )  .AND.                     &
2487                  BTEST( wall_flags_static_0(k+1,j,i), 0 ) )                          &
2488                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 25 )
2489!
2490!--          Special flag on scalar grid, nzb_diff_s_outer - 1, required in
2491!--          in production_e
2492             IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
2493                IF ( BTEST( wall_flags_static_0(k,j,i),   24 )  .AND.                 &
2494                     BTEST( wall_flags_static_0(k-1,j,i), 24 )  .AND.                 &
2495                     BTEST( wall_flags_static_0(k+1,j,i), 0 ) )                       &
2496                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 29 )
2497             ELSE
2498                IF ( BTEST( wall_flags_static_0(k,j,i), 0 ) )                         &
2499                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 29 )
2500             ENDIF
2501!
2502!--          Special flag on scalar grid, nzb_diff_s_outer - 1, required in
2503!--          in production_e
2504             IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
2505                IF ( BTEST( wall_flags_static_0(k,j,i),   0 )  .AND.                  &
2506                     BTEST( wall_flags_static_0(k-1,j,i), 0 )  .AND.                  &
2507                     BTEST( wall_flags_static_0(k+1,j,i), 0 ) )                       &
2508                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 30 )
2509             ELSE
2510                IF ( BTEST( wall_flags_static_0(k,j,i), 0 ) )                         &
2511                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 30 )
2512             ENDIF
2513          ENDDO
2514!
2515!--       Flags indicating downward facing walls
2516          DO k = nzb+1, nzt+1
2517!
2518!--          Scalar grid
2519             IF ( BTEST( wall_flags_static_0(k-1,j,i), 0 )  .AND.                     &
2520            .NOT. BTEST( wall_flags_static_0(k,j,i), 0   ) )                          & 
2521                 wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 13 ) 
2522!
2523!--          Downward facing wall on u grid
2524             IF ( BTEST( wall_flags_static_0(k-1,j,i), 1 )  .AND.                     &
2525            .NOT. BTEST( wall_flags_static_0(k,j,i), 1   ) )                          & 
2526                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 15 )
2527!
2528!--          Downward facing wall on v grid
2529             IF ( BTEST( wall_flags_static_0(k-1,j,i), 2 )  .AND.                     &
2530            .NOT. BTEST( wall_flags_static_0(k,j,i), 2   ) )                          & 
2531                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 17 )
2532!
2533!--          Downward facing wall on w grid
2534             IF ( BTEST( wall_flags_static_0(k-1,j,i), 3 )  .AND.                     &
2535            .NOT. BTEST( wall_flags_static_0(k,j,i), 3 ) )                            & 
2536                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 19 )
2537          ENDDO
2538!
2539!--       Flags indicating upward facing walls
2540          DO k = nzb, nzt
2541!
2542!--          Upward facing wall on scalar grid
2543             IF ( .NOT. BTEST( wall_flags_static_0(k,j,i),   0 )  .AND.               &
2544                        BTEST( wall_flags_static_0(k+1,j,i), 0 ) )                    & 
2545                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 12 )
2546!
2547!--          Upward facing wall on u grid
2548             IF ( .NOT. BTEST( wall_flags_static_0(k,j,i),   1 )  .AND.               &
2549                        BTEST( wall_flags_static_0(k+1,j,i), 1 ) )                    & 
2550                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 14 )
2551
2552!   
2553!--          Upward facing wall on v grid
2554             IF ( .NOT. BTEST( wall_flags_static_0(k,j,i),   2 )  .AND.               &
2555                        BTEST( wall_flags_static_0(k+1,j,i), 2 ) )                    & 
2556                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 16 )
2557   
2558!
2559!--          Upward facing wall on w grid
2560             IF ( .NOT. BTEST( wall_flags_static_0(k,j,i),   3 )  .AND.               &
2561                        BTEST( wall_flags_static_0(k+1,j,i), 3 ) )                    & 
2562                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 18 )
2563!
2564!--          Special flag on scalar grid, former nzb_s_inner
2565             IF ( BTEST( wall_flags_static_0(k,j,i), 0 )  .OR.                        &
2566                  BTEST( wall_flags_static_0(k,j,i), 12 ) .OR.                        &
2567                  BTEST( wall_flags_static_0(k,j,i), 13 ) )                           &
2568                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 22 )
2569!
2570!--          Special flag on scalar grid, nzb_diff_s_inner - 1, required for
2571!--          flow_statistics
2572             IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
2573                IF ( BTEST( wall_flags_static_0(k,j,i),   0 )  .AND.                  &
2574                     BTEST( wall_flags_static_0(k+1,j,i), 0 ) )                       &
2575                  wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 23 )
2576             ELSE
2577                IF ( BTEST( wall_flags_static_0(k,j,i), 22 ) )                        &
2578                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 23 )
2579             ENDIF
2580   
2581
2582          ENDDO
2583          wall_flags_static_0(nzt+1,j,i) = IBSET( wall_flags_static_0(nzt+1,j,i), 22 )
2584          wall_flags_static_0(nzt+1,j,i) = IBSET( wall_flags_static_0(nzt+1,j,i), 23 )
2585!
2586!--       Set flags indicating that topography is close by in horizontal
2587!--       direction, i.e. flags that infold the topography. These will be used
2588!--       to set advection flags for passive scalars, where due to large
2589!--       gradients near buildings stationary numerical oscillations can produce
2590!--       unrealistically high concentrations. This is only necessary if
2591!--       WS-scheme is applied for scalar advection. Note, these flags will be
2592!--       only used for passive scalars such as chemical species or aerosols.
2593          IF ( scalar_advec == 'ws-scheme' )  THEN
2594             DO k = nzb, nzt
2595                IF ( BTEST( wall_flags_static_0(k,j,i), 0 )  .AND. (                   &
2596                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i-1), 0 ) )  .OR.&
2597                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i-2), 0 ) )  .OR.&
2598                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i-3), 0 ) )  .OR.&
2599                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i+1), 0 ) )  .OR.&
2600                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i+2), 0 ) )  .OR.&
2601                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3:j+3,i+3), 0 ) )  .OR.&
2602                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-1,i-3:i+3), 0 ) )  .OR.&
2603                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-2,i-3:i+3), 0 ) )  .OR.&
2604                     ANY( .NOT. BTEST( wall_flags_static_0(k,j-3,i-3:i+3), 0 ) )  .OR.&
2605                     ANY( .NOT. BTEST( wall_flags_static_0(k,j+1,i-3:i+3), 0 ) )  .OR.&
2606                     ANY( .NOT. BTEST( wall_flags_static_0(k,j+2,i-3:i+3), 0 ) )  .OR.&
2607                     ANY( .NOT. BTEST( wall_flags_static_0(k,j+3,i-3:i+3), 0 ) )      &
2608                                                            ) )                &
2609                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 31 )
2610                     
2611             ENDDO
2612          ENDIF
2613       ENDDO
2614    ENDDO
2615!
2616!-- Finally, set identification flags indicating natural terrain or buildings.
2617!-- Natural terrain grid points. Information on the type of the surface is
2618!-- stored in bit 1 of 3D Integer array topo. However, this bit is only set
2619!-- when topography is read from file. In order to run the land-surface model
2620!-- also without topography information, set bit 1 explicitely in this case.
2621!--
2622!-- Natural terrain grid points
2623!-- If no topography is initialized, the land-surface is at k = nzb.
2624    IF ( TRIM( topography ) /= 'read_from_file' )  THEN
2625       wall_flags_static_0(nzb,:,:) = IBSET( wall_flags_static_0(nzb,:,:), 5 )
2626    ELSE
2627       DO i = nxl, nxr
2628          DO j = nys, nyn
2629             DO k = nzb, nzt+1
2630!         
2631!--             Natural terrain grid point
2632                IF ( BTEST( topo(k,j,i), 1 ) )                                 &
2633                   wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 5 )
2634             ENDDO
2635          ENDDO
2636       ENDDO
2637    ENDIF
2638!
2639!-- Building grid points.
2640    DO i = nxl, nxr
2641       DO j = nys, nyn
2642          DO k = nzb, nzt+1
2643             IF ( BTEST( topo(k,j,i), 2 ) )                                    &
2644                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 6 )
2645          ENDDO
2646       ENDDO
2647    ENDDO
2648!
2649!-- Set flag 4, indicating new topography grid points due to filtering.
2650    DO i = nxl, nxr
2651       DO j = nys, nyn
2652          DO k = nzb, nzt+1
2653             IF ( BTEST( topo(k,j,i), 4 ) )                                    &
2654                wall_flags_static_0(k,j,i) = IBSET( wall_flags_static_0(k,j,i), 4 )
2655          ENDDO
2656       ENDDO
2657    ENDDO
2658!
2659!-- Exchange ghost points for wall flags
2660    CALL exchange_horiz_int( wall_flags_static_0, nys, nyn, nxl, nxr, nzt, nbgp )
2661!
2662!-- Set boundary conditions also for flags. Can be interpreted as Neumann
2663!-- boundary conditions for topography.
2664    IF ( .NOT. bc_ns_cyc )  THEN
2665       IF ( nys == 0  )  THEN
2666          DO  i = 1, nbgp     
2667             wall_flags_static_0(:,nys-i,:)   = wall_flags_static_0(:,nys,:)
2668          ENDDO
2669       ENDIF
2670       IF ( nyn == ny )  THEN
2671          DO  i = 1, nbgp 
2672             wall_flags_static_0(:,nyn+i,:) = wall_flags_static_0(:,nyn,:)
2673          ENDDO
2674       ENDIF
2675    ENDIF
2676    IF ( .NOT. bc_lr_cyc )  THEN
2677       IF ( nxl == 0  )  THEN
2678          DO  i = 1, nbgp   
2679             wall_flags_static_0(:,:,nxl-i)   = wall_flags_static_0(:,:,nxl)
2680          ENDDO
2681       ENDIF
2682       IF ( nxr == nx )  THEN
2683          DO  i = 1, nbgp   
2684             wall_flags_static_0(:,:,nxr+i) = wall_flags_static_0(:,:,nxr)     
2685          ENDDO
2686       ENDIF     
2687    ENDIF
2688!
2689!-- Pre-calculate topography top indices (former get_topography_top_index
2690!-- function)
2691    ALLOCATE( topo_top_ind(nysg:nyng,nxlg:nxrg,0:4) )
2692!
2693!-- Uppermost topography index on scalar grid
2694    ibit = 12
2695    topo_top_ind(:,:,0) = MAXLOC(                                              &
2696                                  MERGE( 1, 0,                                 &
2697                                          BTEST( wall_flags_static_0(:,:,:), ibit )   &
2698                                       ), DIM = 1                              &
2699                                ) - 1 
2700!
2701!-- Uppermost topography index on u grid
2702    ibit = 14
2703    topo_top_ind(:,:,1) = MAXLOC(                                              &
2704                                  MERGE( 1, 0,                                 &
2705                                          BTEST( wall_flags_static_0(:,:,:), ibit )   &
2706                                       ), DIM = 1                              &
2707                                ) - 1 
2708!
2709!-- Uppermost topography index on v grid
2710    ibit = 16
2711    topo_top_ind(:,:,2) = MAXLOC(                                              &
2712                                  MERGE( 1, 0,                                 &
2713                                          BTEST( wall_flags_static_0(:,:,:), ibit )   &
2714                                       ), DIM = 1                              &
2715                                ) - 1 
2716!
2717!-- Uppermost topography index on w grid
2718    ibit = 18
2719    topo_top_ind(:,:,3) = MAXLOC(                                              &
2720                                  MERGE( 1, 0,                                 &
2721                                          BTEST( wall_flags_static_0(:,:,:), ibit )   &
2722                                       ), DIM = 1                              &
2723                                ) - 1 
2724!
2725!-- Uppermost topography index on scalar outer grid
2726    ibit = 24
2727    topo_top_ind(:,:,4) = MAXLOC(                                              &
2728                                  MERGE( 1, 0,                                 &
2729                                          BTEST( wall_flags_static_0(:,:,:), ibit )   &
2730                                       ), DIM = 1                              &
2731                                ) - 1                           
2732
2733 END SUBROUTINE set_topo_flags
2734
2735
2736
Note: See TracBrowser for help on using the repository browser.