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

Last change on this file since 4331 was 4329, checked in by motisi, 4 years ago

Renamed wall_flags_0 to wall_flags_static_0

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