source: palm/trunk/SOURCE/nesting_offl_mod.f90 @ 4834

Last change on this file since 4834 was 4834, checked in by raasch, 3 years ago

file re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 173.2 KB
Line 
1!> @file nesting_offl_mod.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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2021 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! ------------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: nesting_offl_mod.f90 4834 2021-01-07 10:28:00Z raasch $
26! file re-formatted to follow the PALM coding standard
27!
28! 4828 2021-01-05 11:21:41Z Giersch
29! Bugfix in obtaining the correct timestamp in case of restart runs
30!
31! 4724 2020-10-06 17:20:39Z suehring $
32! - Enable LOD=1 input of boundary conditions
33! - Minor bugfix - add missing initialization of the top boundary
34!
35! 4582 2020-06-29 09:22:11Z suehring
36! Remove unused variable
37!
38! 4581 2020-06-29 08:49:58Z suehring
39! Omit explicit pressure forcing via geostrophic wind components in case of mesoscale nesting.
40!
41! 4561 2020-06-12 07:05:56Z suehring
42! Adapt mass-flux correction also for the anelastic approximation
43!
44! 4561 2020-06-12 07:05:56Z suehring
45! use statement for exchange horiz added
46!
47! 4360 2020-01-07 11:25:50Z suehring
48! Bugfix, time coordinate is relative to origin_time rather than to 00:00:00 UTC.
49!
50! 4346 2019-12-18 11:55:56Z motisi
51! Introduction of wall_flags_total_0, which currently sets bits based on static topography
52! information used in wall_flags_static_0
53!
54! 4329 2019-12-10 15:46:36Z motisi
55! Renamed wall_flags_0 to wall_flags_static_0
56!
57! 4286 2019-10-30 16:01:14Z resler
58! Fix wrong checks of time from dynamic driver in nesting_offl_mod
59!
60! 4273 2019-10-24 13:40:54Z monakurppa
61! Add a logical switch nesting_offline_chem
62!
63! 4270 2019-10-23 10:46:20Z monakurppa
64! Implement offline nesting for salsa variables.
65!
66! 4231 2019-09-12 11:22:00Z suehring
67! Bugfix in array deallocation
68!
69! 4230 2019-09-11 13:58:14Z suehring
70! Update mean chemistry profiles. These are also used for rayleigh damping.
71!
72! 4227 2019-09-10 18:04:34Z gronemeier
73! implement new palm_date_time_mod
74!
75! - Data input moved into nesting_offl_mod
76! - check rephrased
77! - time variable is now relative to time_utc_init
78! - Define module specific data type for offline nesting in nesting_offl_mod
79!
80! 4182 2019-08-22 15:20:23Z scharf
81! Corrected "Former revisions" section
82!
83! 4169 2019-08-19 13:54:35Z suehring
84! Additional check added.
85!
86! 4168 2019-08-16 13:50:17Z suehring
87! Replace function get_topography_top_index by topo_top_ind
88!
89! 4125 2019-07-29 13:31:44Z suehring
90! In order to enable netcdf parallel access, allocate dummy arrays for the lateral boundary data on
91! cores that actually do not belong to these boundaries.
92!
93! 4079 2019-07-09 18:04:41Z suehring
94! - Set boundary condition for w at nzt+1 at the lateral boundaries, even though these won't enter
95!   the numerical solution. However, due to the mass conservation these values might some up to very
96!   large values which will occur in the run-control file
97! - Bugfix in offline nesting of chemical species
98! - Do not set Neumann conditions for TKE and passive scalar
99!
100! 4022 2019-06-12 11:52:39Z suehring
101! Detection of boundary-layer depth in stable boundary layer on basis of boundary data improved
102! Routine for boundary-layer depth calculation renamed and made public
103!
104! 3987 2019-05-22 09:52:13Z kanani
105! Introduce alternative switch for debug output during timestepping
106!
107! 3964 2019-05-09 09:48:32Z suehring
108! Ensure that veloctiy term in calculation of bulk Richardson number does not become zero
109!
110! 3937 2019-04-29 15:09:07Z suehring
111! Set boundary conditon on upper-left and upper-south grid point for the u- and v-component,
112! respectively.
113!
114! 3891 2019-04-12 17:52:01Z suehring
115! Bugfix, do not overwrite lateral and top boundary data in case of restart runs.
116!
117! 3885 2019-04-11 11:29:34Z kanani
118! Changes related to global restructuring of location messages and introduction of additional debug
119! messages
120!
121!
122! Do local data exchange for chemistry variables only when boundary data is coming from dynamic file
123!
124! 3737 2019-02-12 16:57:06Z suehring
125! Introduce mesoscale nesting for chemical species
126!
127! 3705 2019-01-29 19:56:39Z suehring
128! Formatting adjustments
129!
130! 3704 2019-01-29 19:51:41Z suehring
131! Check implemented for offline nesting in child domain
132!
133! Initial Revision:
134! - separate offline nesting from large_scale_nudging_mod
135! - revise offline nesting, adjust for usage of synthetic turbulence generator
136! - adjust Rayleigh damping depending on the time-depending atmospheric conditions
137!
138!
139! Description:
140! ------------
141!> Offline nesting in larger-scale models. Boundary conditions for the simulation are read from
142!> NetCDF file and are prescribed onto the respective arrays.
143!> Further, a mass-flux correction is performed to maintain the mass balance.
144!--------------------------------------------------------------------------------------------------!
145 MODULE nesting_offl_mod
146
147    USE arrays_3d,                                                                                 &
148        ONLY:  diss,                                                                               &
149               drho_air_zw,                                                                        &
150               dzw,                                                                                &
151               e,                                                                                  &
152               pt,                                                                                 &
153               pt_init,                                                                            &
154               q,                                                                                  &
155               q_init,                                                                             &
156               rdf,                                                                                &
157               rdf_sc,                                                                             &
158               rho_air,                                                                            &
159               rho_air_zw,                                                                         &
160               s,                                                                                  &
161               u,                                                                                  &
162               u_init,                                                                             &
163               ug,                                                                                 &
164               v,                                                                                  &
165               v_init,                                                                             &
166               vg,                                                                                 &
167               w,                                                                                  &
168               zu,                                                                                 &
169               zw
170
171    USE basic_constants_and_equations_mod,                                                         &
172        ONLY:  g,                                                                                  &
173               pi
174
175    USE chem_modules,                                                                              &
176        ONLY:  chem_species, nesting_offline_chem
177
178    USE control_parameters,                                                                        &
179        ONLY:  air_chemistry,                                                                      &
180               bc_dirichlet_l,                                                                     &
181               bc_dirichlet_n,                                                                     &
182               bc_dirichlet_r,                                                                     &
183               bc_dirichlet_s,                                                                     &
184               coupling_char,                                                                      &
185               constant_diffusion,                                                                 &
186               child_domain,                                                                       &
187               debug_output_timestep,                                                              &
188               dt_3d,                                                                              &
189               dz,                                                                                 &
190               end_time,                                                                           &
191               humidity,                                                                           &
192               initializing_actions,                                                               &
193               message_string,                                                                     &
194               nesting_offline,                                                                    &
195               neutral,                                                                            &
196               passive_scalar,                                                                     &
197               rans_mode,                                                                          &
198               rans_tke_e,                                                                         &
199               rayleigh_damping_factor,                                                            &
200               rayleigh_damping_height,                                                            &
201               salsa,                                                                              &
202               spinup_time,                                                                        &
203               time_since_reference_point,                                                         &
204               volume_flow
205
206    USE cpulog,                                                                                    &
207        ONLY:  cpu_log,                                                                            &
208               log_point,                                                                          &
209               log_point_s
210
211    USE grid_variables
212
213    USE indices,                                                                                   &
214        ONLY:  nbgp, nx, nxl, nxlg, nxlu, nxr, nxrg, ny, nys, nysv, nysg, nyn, nyng, nzb, nz, nzt, &
215               topo_top_ind, wall_flags_total_0
216
217    USE kinds
218
219    USE netcdf_data_input_mod,                                                                     &
220        ONLY:  char_fill,                                                                          &
221               char_lod,                                                                           &
222               check_existence,                                                                    &
223               close_input_file,                                                                   &
224               get_attribute,                                                                      &
225               get_dimension_length,                                                               &
226               get_variable,                                                                       &
227               get_variable_pr,                                                                    &
228               input_pids_dynamic,                                                                 &
229               inquire_num_variables,                                                              &
230               inquire_variable_names,                                                             &
231               input_file_dynamic,                                                                 &
232               num_var_pids,                                                                       &
233               open_read_file,                                                                     &
234               pids_id
235
236    USE pegrid
237
238    USE salsa_mod,                                                                                 &
239        ONLY:  salsa_nesting_offl_bc,                                                              &
240               salsa_nesting_offl_init,                                                            &
241               salsa_nesting_offl_input
242
243    IMPLICIT NONE
244
245!
246!-- Define data type for nesting in larger-scale models like COSMO.
247!-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
248    TYPE nest_offl_type
249
250       CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'   !< leading substring for variables at left boundary
251       CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_'  !< leading substring for variables at north boundary
252       CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_'  !< leading substring for variables at right boundary
253       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_'  !< leading substring for variables at south boundary
254       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'    !< leading substring for variables at top boundary
255
256       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names         !< list of variable in dynamic input file
257       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_l  !< names of mesoscale nested chemistry variables at left
258                                                                           !< boundary
259       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_n  !< names of mesoscale nested chemistry variables at north
260                                                                           !< boundary
261       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_r  !< names of mesoscale nested chemistry variables at right
262                                                                           !< boundary
263       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_s  !< names of mesoscale nested chemistry variables at south
264                                                                           !< boundary
265       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_t  !< names of mesoscale nested chemistry variables at top
266                                                                           !< boundary
267
268       INTEGER(iwp) ::  lod_east_pt  = 2  !< level-of-detail of input data of potential temperature at the eastern boundary
269       INTEGER(iwp) ::  lod_east_qc  = 2  !< level-of-detail of input data of cloud-water mixture fraction at the eastern boundary
270       INTEGER(iwp) ::  lod_east_qv  = 2  !< level-of-detail of input data of specific humidity at the eastern boundary
271       INTEGER(iwp) ::  lod_east_u   = 2  !< level-of-detail of input data of the u-component at the eastern boundary
272       INTEGER(iwp) ::  lod_east_v   = 2  !< level-of-detail of input data of the v-component at the eastern boundary
273       INTEGER(iwp) ::  lod_east_w   = 2  !< level-of-detail of input data of the w-component at the eastern boundary
274       INTEGER(iwp) ::  lod_north_pt = 2  !< level-of-detail of input data of potential temperature at the northern boundary
275       INTEGER(iwp) ::  lod_north_qc = 2  !< level-of-detail of input data of cloud-water mixture fraction at the northern boundary
276       INTEGER(iwp) ::  lod_north_qv = 2  !< level-of-detail of input data of specific humidity at the northern boundary
277       INTEGER(iwp) ::  lod_north_u  = 2  !< level-of-detail of input data of the u-component at the northern boundary
278       INTEGER(iwp) ::  lod_north_v  = 2  !< level-of-detail of input data of the v-component at the northern boundary
279       INTEGER(iwp) ::  lod_north_w  = 2  !< level-of-detail of input data of the w-component at the northern boundary
280       INTEGER(iwp) ::  lod_south_pt = 2  !< level-of-detail of input data of potential temperature at the southern boundary
281       INTEGER(iwp) ::  lod_south_qc = 2  !< level-of-detail of input data of cloud-water mixture fraction at the southern boundary
282       INTEGER(iwp) ::  lod_south_qv = 2  !< level-of-detail of input data of specific humidity at the southern boundary
283       INTEGER(iwp) ::  lod_south_u  = 2  !< level-of-detail of input data of the u-component at the southern boundary
284       INTEGER(iwp) ::  lod_south_v  = 2  !< level-of-detail of input data of the v-component at the southern boundary
285       INTEGER(iwp) ::  lod_south_w  = 2  !< level-of-detail of input data of the w-component at the southern boundary
286       INTEGER(iwp) ::  lod_top_pt   = 2  !< level-of-detail of input data of potential temperature at the top boundary
287       INTEGER(iwp) ::  lod_top_qc   = 2  !< level-of-detail of input data of cloud-water mixture fraction at the top boundary
288       INTEGER(iwp) ::  lod_top_qv   = 2  !< level-of-detail of input data of specific humidity at the top boundary
289       INTEGER(iwp) ::  lod_top_u    = 2  !< level-of-detail of input data of the u-component at the top boundary
290       INTEGER(iwp) ::  lod_top_v    = 2  !< level-of-detail of input data of the v-component at the top boundary
291       INTEGER(iwp) ::  lod_top_w    = 2  !< level-of-detail of input data of the w-component at the top boundary
292       INTEGER(iwp) ::  lod_west_pt  = 2  !< level-of-detail of input data of potential temperature at the western boundary
293       INTEGER(iwp) ::  lod_west_qc  = 2  !< level-of-detail of input data of cloud-water mixture fraction at the western boundary
294       INTEGER(iwp) ::  lod_west_qv  = 2  !< level-of-detail of input data of specific humidity at the western boundary
295       INTEGER(iwp) ::  lod_west_u   = 2  !< level-of-detail of input data of the u-component at the western boundary
296       INTEGER(iwp) ::  lod_west_v   = 2  !< level-of-detail of input data of the v-component at the western boundary
297       INTEGER(iwp) ::  lod_west_w   = 2  !< level-of-detail of input data of the w-component at the western boundary
298       INTEGER(iwp) ::  nt                !< number of time levels in dynamic input file
299       INTEGER(iwp) ::  nzu               !< number of vertical levels on scalar grid in dynamic input file
300       INTEGER(iwp) ::  nzw               !< number of vertical levels on w grid in dynamic input file
301       INTEGER(iwp) ::  tind = 0          !< time index for reference time in mesoscale-offline nesting
302       INTEGER(iwp) ::  tind_p = 0        !< time index for following time in mesoscale-offline nesting
303
304       LOGICAL      ::  init = .FALSE.    !< flag indicating that offline nesting is already initialized
305
306       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l  !< flags inidicating whether left boundary data for chemistry is in
307                                                                !< dynamic input file
308       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_n  !< flags inidicating whether north boundary data for chemistry is in
309                                                                !< dynamic input file
310       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_r  !< flags inidicating whether right boundary data for chemistry is in
311                                                                !< dynamic input file
312       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_s  !< flags inidicating whether south boundary data for chemistry is in
313                                                                !< dynamic input file
314       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_t  !< flags inidicating whether top boundary data for chemistry is in
315                                                                !< dynamic input file
316
317       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure  !< time dependent surface pressure
318       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time              !< time levels in dynamic input file
319       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos          !< vertical levels at scalar grid in dynamic input file
320       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos          !< vertical levels at w grid in dynamic input file
321
322       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ug         !< domain-averaged geostrophic component
323       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vg         !< domain-averaged geostrophic component
324
325       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_l     !< potentital temperautre at left boundary
326       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_n     !< potentital temperautre at north boundary
327       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_r     !< potentital temperautre at right boundary
328       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_s     !< potentital temperautre at south boundary
329       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
330       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_l      !< mixing ratio at left boundary
331       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_n      !< mixing ratio at north boundary
332       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_r      !< mixing ratio at right boundary
333       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_s      !< mixing ratio at south boundary
334       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
335       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_l      !< u-component at left boundary
336       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_n      !< u-component at north boundary
337       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_r      !< u-component at right boundary
338       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_s      !< u-component at south boundary
339       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_top    !< u-component at top boundary
340       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_l      !< v-component at left boundary
341       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_n      !< v-component at north boundary
342       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_r      !< v-component at right boundary
343       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_s      !< v-component at south boundary
344       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_top    !< v-component at top boundary
345       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_l      !< w-component at left boundary
346       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_n      !< w-component at north boundary
347       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_r      !< w-component at right boundary
348       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_s      !< w-component at south boundary
349       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_top    !< w-component at top boundary
350
351       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_l   !< chemical species at left boundary
352       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_n   !< chemical species at north boundary
353       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_r   !< chemical species at right boundary
354       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_s   !< chemical species at south boundary
355       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top !< chemical species at left boundary
356
357    END TYPE nest_offl_type
358
359    INTEGER(iwp) ::  i_bound     !< boundary grid point in x-direction for scalars, v, and w
360    INTEGER(iwp) ::  i_bound_u   !< boundary grid point in x-direction for u
361    INTEGER(iwp) ::  i_end       !< end index for array allocation along x-direction at norther/southern boundary
362    INTEGER(iwp) ::  i_start     !< start index for array allocation along x-direction at norther/southern boundary (scalars, v, w)
363    INTEGER(iwp) ::  i_start_u   !< start index for array allocation along x-direction at norther/southern boundary (u)
364    INTEGER(iwp) ::  j_bound     !< boundary grid point in y-direction for scalars, u, and w
365    INTEGER(iwp) ::  j_bound_v   !< boundary grid point in y-direction for v
366    INTEGER(iwp) ::  j_end       !< end index for array allocation along y-direction at eastern/western boundary
367    INTEGER(iwp) ::  j_start     !< start index for array allocation along y-direction at eastern/western boundary (scalars, u, w)
368    INTEGER(iwp) ::  j_start_v   !< start index for array allocation along y-direction at eastern/western boundary (v)
369    INTEGER(iwp) ::  lod         !< level-of-detail of lateral input data
370
371    REAL(wp) ::  fac_dt              !< interpolation factor
372    REAL(wp) ::  zi_ribulk = 0.0_wp  !< boundary-layer depth according to bulk Richardson criterion, i.e. the height where Ri_bulk
373                                     !< exceeds the critical bulk Richardson number of 0.2
374
375    TYPE(nest_offl_type) ::  nest_offl  !< data structure for data input at lateral and top boundaries (provided by Inifor)
376
377    SAVE
378    PRIVATE
379!
380!-- Public subroutines
381    PUBLIC nesting_offl_bc,                                                                        &
382           nesting_offl_calc_zi,                                                                   &
383           nesting_offl_check_parameters,                                                          &
384           nesting_offl_geostrophic_wind,                                                          &
385           nesting_offl_header,                                                                    &
386           nesting_offl_init,                                                                      &
387           nesting_offl_input,                                                                     &
388           nesting_offl_interpolation_factor,                                                      &
389           nesting_offl_mass_conservation,                                                         &
390           nesting_offl_parin
391!
392!-- Public variables
393    PUBLIC zi_ribulk
394
395    INTERFACE nesting_offl_bc
396       MODULE PROCEDURE nesting_offl_bc
397    END INTERFACE nesting_offl_bc
398
399    INTERFACE nesting_offl_calc_zi
400       MODULE PROCEDURE nesting_offl_calc_zi
401    END INTERFACE nesting_offl_calc_zi
402
403    INTERFACE nesting_offl_check_parameters
404       MODULE PROCEDURE nesting_offl_check_parameters
405    END INTERFACE nesting_offl_check_parameters
406
407    INTERFACE nesting_offl_geostrophic_wind
408       MODULE PROCEDURE nesting_offl_geostrophic_wind
409    END INTERFACE nesting_offl_geostrophic_wind
410
411    INTERFACE nesting_offl_header
412       MODULE PROCEDURE nesting_offl_header
413    END INTERFACE nesting_offl_header
414
415    INTERFACE nesting_offl_init
416       MODULE PROCEDURE nesting_offl_init
417    END INTERFACE nesting_offl_init
418
419    INTERFACE nesting_offl_input
420       MODULE PROCEDURE nesting_offl_input
421    END INTERFACE nesting_offl_input
422
423    INTERFACE nesting_offl_interpolation_factor
424       MODULE PROCEDURE nesting_offl_interpolation_factor
425    END INTERFACE nesting_offl_interpolation_factor
426
427    INTERFACE nesting_offl_mass_conservation
428       MODULE PROCEDURE nesting_offl_mass_conservation
429    END INTERFACE nesting_offl_mass_conservation
430
431    INTERFACE nesting_offl_parin
432       MODULE PROCEDURE nesting_offl_parin
433    END INTERFACE nesting_offl_parin
434
435 CONTAINS
436
437!--------------------------------------------------------------------------------------------------!
438! Description:
439! ------------
440!> Reads data at lateral and top boundaries derived from larger-scale model.
441!--------------------------------------------------------------------------------------------------!
442 SUBROUTINE nesting_offl_input
443
444    INTEGER(iwp) ::  n   !< running index for chemistry variables
445
446!
447!-- Initialize INIFOR forcing in first call.
448    IF ( .NOT. nest_offl%init )  THEN
449#if defined ( __netcdf )
450!
451!--    Open file in read-only mode
452       CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), pids_id )
453!
454!--    At first, inquire all variable names.
455       CALL inquire_num_variables( pids_id, num_var_pids )
456!
457!--    Allocate memory to store variable names.
458       ALLOCATE( nest_offl%var_names(1:num_var_pids) )
459       CALL inquire_variable_names( pids_id, nest_offl%var_names )
460!
461!--    Read time dimension, allocate memory and finally read time array
462       CALL get_dimension_length( pids_id, nest_offl%nt, 'time' )
463
464       IF ( check_existence( nest_offl%var_names, 'time' ) )  THEN
465          ALLOCATE( nest_offl%time(0:nest_offl%nt-1) )
466          CALL get_variable( pids_id, 'time', nest_offl%time )
467       ENDIF
468!
469!--    Read vertical dimension of scalar und w grid
470       CALL get_dimension_length( pids_id, nest_offl%nzu, 'z' )
471       CALL get_dimension_length( pids_id, nest_offl%nzw, 'zw' )
472
473       IF ( check_existence( nest_offl%var_names, 'z' ) )  THEN
474          ALLOCATE( nest_offl%zu_atmos(1:nest_offl%nzu) )
475          CALL get_variable( pids_id, 'z', nest_offl%zu_atmos )
476       ENDIF
477       IF ( check_existence( nest_offl%var_names, 'zw' ) )  THEN
478          ALLOCATE( nest_offl%zw_atmos(1:nest_offl%nzw) )
479          CALL get_variable( pids_id, 'zw', nest_offl%zw_atmos )
480       ENDIF
481!
482!--    Read surface pressure
483       IF ( check_existence( nest_offl%var_names, 'surface_forcing_surface_pressure' ) )  THEN
484          ALLOCATE( nest_offl%surface_pressure(0:nest_offl%nt-1) )
485          CALL get_variable( pids_id, 'surface_forcing_surface_pressure',                          &
486                             nest_offl%surface_pressure )
487       ENDIF
488!
489!--    Close input file
490       CALL close_input_file( pids_id )
491#endif
492    ENDIF
493!
494!-- Check if dynamic driver data input is required.
495    IF ( nest_offl%time(nest_offl%tind_p) <= MAX( time_since_reference_point, 0.0_wp)  .OR.        &
496         .NOT.  nest_offl%init )  THEN
497       CONTINUE
498!
499!-- Return otherwise
500    ELSE
501       RETURN
502    ENDIF
503!
504!-- Start of CPU measurement
505    CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'start' )
506
507!
508!-- Obtain time index for current point in time. Note, the time coordinate in the input file is
509!-- always relative to the initial time in UTC, i.e. the time coordinate always starts at 0.0 even
510!-- if the initial UTC is e.g. 7200.0. Further, since time_since_reference_point is negativ here
511!-- when spinup is applied, use MAX function to obtain correct time index.
512    nest_offl%tind = MINLOC( ABS( nest_offl%time - MAX( time_since_reference_point, 0.0_wp ) ),    &
513                             DIM = 1 ) - 1
514!
515!--    Note, in case of restart runs, the time index for the boundary data may indicate a time in
516!--    the future. This needs to be checked and corrected.
517       IF ( TRIM( initializing_actions ) == 'read_restart_data'  .AND.                             &
518            nest_offl%time(nest_offl%tind) > time_since_reference_point )  THEN
519          nest_offl%tind = nest_offl%tind - 1
520       ENDIF
521    nest_offl%tind_p = nest_offl%tind + 1
522!
523!-- Open file in read-only mode
524#if defined ( __netcdf )
525    CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), pids_id )
526!
527!--    Read geostrophic wind components
528!        DO  t = nest_offl%tind, nest_offl%tind_p
529!           CALL get_variable_pr( pids_id, 'ls_forcing_ug', t+1,                 &
530!                                 nest_offl%ug(t-nest_offl%tind,nzb+1:nzt) )
531!           CALL get_variable_pr( pids_id, 'ls_forcing_vg', t+1,                 &
532!                                 nest_offl%vg(t-nest_offl%tind,nzb+1:nzt) )
533!        ENDDO
534!
535!-- Read data at lateral and top boundaries. Please note, at left and right domain boundary,
536!-- yz-layers are read for u, v, w, pt and q.
537!-- For the v-component, the data starts at nysv, while for the other quantities the data starts at
538!-- nys. This is equivalent at the north and south domain boundary for the u-component (nxlu).
539!-- Note, lateral data is also accessed by parallel IO, which is the reason why different arguments
540!-- are passed depending on the boundary control flags. Cores that do not belong to the respective
541!-- boundary only do a dummy read with count = 0, just in order to participate the collective
542!-- operation. This is because collective parallel access shows better performance than just a
543!-- conditional access.
544!-- Read data for LOD 2, i.e. time-dependent xz-, yz-, and xy-slices.
545    IF ( lod == 2 )  THEN
546       CALL get_variable( pids_id, 'ls_forcing_left_u',                                            &
547                          nest_offl%u_l,                                                           & ! array to be read
548                          MERGE( nys+1, 1, bc_dirichlet_l),                                        & ! start index y direction
549                          MERGE( nzb+1, 1, bc_dirichlet_l),                                        & ! start index z direction
550                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                             & ! start index time dimension
551                          MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                    & ! number of elements along y
552                          MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                                & ! number of elements alogn z
553                          MERGE( 2, 0, bc_dirichlet_l),                                            & ! number of time steps (2 or 0)
554                          .TRUE. )                                                                   ! parallel IO when compiled accordingly
555
556       CALL get_variable( pids_id, 'ls_forcing_left_v',                                            &
557                          nest_offl%v_l,                                                           &
558                          MERGE( nysv, 1, bc_dirichlet_l),                                         &
559                          MERGE( nzb+1, 1, bc_dirichlet_l),                                        &
560                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                             &
561                          MERGE( nyn-nysv+1, 0, bc_dirichlet_l),                                   &
562                          MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                                &
563                          MERGE( 2, 0, bc_dirichlet_l),                                            &
564                          .TRUE. )
565
566       CALL get_variable( pids_id, 'ls_forcing_left_w',                                            &
567                          nest_offl%w_l,                                                           &
568                          MERGE( nys+1, 1, bc_dirichlet_l),                                        &
569                          MERGE( nzb+1, 1, bc_dirichlet_l),                                        &
570                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                             &
571                          MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                    &
572                          MERGE( nest_offl%nzw, 0, bc_dirichlet_l),                                &
573                          MERGE( 2, 0, bc_dirichlet_l),                                            &
574                          .TRUE. )
575
576       IF ( .NOT. neutral )  THEN
577          CALL get_variable( pids_id, 'ls_forcing_left_pt',                                        &
578                             nest_offl%pt_l,                                                       &
579                             MERGE( nys+1, 1, bc_dirichlet_l),                                     &
580                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
581                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
582                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                 &
583                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             &
584                             MERGE( 2, 0, bc_dirichlet_l),                                         &
585                             .TRUE. )
586       ENDIF
587
588       IF ( humidity )  THEN
589          CALL get_variable( pids_id, 'ls_forcing_left_qv',                                        &
590                             nest_offl%q_l,                                                        &
591                             MERGE( nys+1, 1, bc_dirichlet_l),                                     &
592                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
593                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
594                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                 &
595                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             &
596                             MERGE( 2, 0, bc_dirichlet_l),                                         &
597                             .TRUE. )
598       ENDIF
599
600       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
601          DO  n = 1, UBOUND( nest_offl%var_names_chem_l, 1 )
602             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_l(n) ) )  THEN
603                CALL get_variable( pids_id,                                                        &
604                                   TRIM( nest_offl%var_names_chem_l(n) ),                          &
605                                   nest_offl%chem_l(:,:,:,n),                                      &
606                                   MERGE( nys+1, 1, bc_dirichlet_l),                               &
607                                   MERGE( nzb+1, 1, bc_dirichlet_l),                               &
608                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                    &
609                                   MERGE( nyn-nys+1, 0, bc_dirichlet_l),                           &
610                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                       &
611                                   MERGE( 2, 0, bc_dirichlet_l),                                   &
612                                   .TRUE. )
613                nest_offl%chem_from_file_l(n) = .TRUE.
614             ENDIF
615          ENDDO
616       ENDIF
617!
618!--    Read data for eastern boundary
619       CALL get_variable( pids_id, 'ls_forcing_right_u',                                           &
620                          nest_offl%u_r,                                                           &
621                          MERGE( nys+1, 1, bc_dirichlet_r),                                        &
622                          MERGE( nzb+1, 1, bc_dirichlet_r),                                        &
623                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                             &
624                          MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                    &
625                          MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                                &
626                          MERGE( 2, 0, bc_dirichlet_r),                                            &
627                          .TRUE. )
628
629       CALL get_variable( pids_id, 'ls_forcing_right_v',                                           &
630                          nest_offl%v_r,                                                           &
631                          MERGE( nysv, 1, bc_dirichlet_r),                                         &
632                          MERGE( nzb+1, 1, bc_dirichlet_r),                                        &
633                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                             &
634                          MERGE( nyn-nysv+1, 0, bc_dirichlet_r),                                   &
635                          MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                                &
636                          MERGE( 2, 0, bc_dirichlet_r),                                            &
637                          .TRUE. )
638
639       CALL get_variable( pids_id, 'ls_forcing_right_w',                                           &
640                          nest_offl%w_r,                                                           &
641                          MERGE( nys+1, 1, bc_dirichlet_r),                                        &
642                          MERGE( nzb+1, 1, bc_dirichlet_r),                                        &
643                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                             &
644                          MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                    &
645                          MERGE( nest_offl%nzw, 0, bc_dirichlet_r),                                &
646                          MERGE( 2, 0, bc_dirichlet_r),                                            &
647                          .TRUE. )
648
649       IF ( .NOT. neutral )  THEN
650          CALL get_variable( pids_id, 'ls_forcing_right_pt',                                       &
651                             nest_offl%pt_r,                                                       &
652                             MERGE( nys+1, 1, bc_dirichlet_r),                                     &
653                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
654                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
655                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                 &
656                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
657                             MERGE( 2, 0, bc_dirichlet_r),                                         &
658                             .TRUE. )
659       ENDIF
660
661       IF ( humidity )  THEN
662          CALL get_variable( pids_id, 'ls_forcing_right_qv',                                       &
663                             nest_offl%q_r,                                                        &
664                             MERGE( nys+1, 1, bc_dirichlet_r),                                     &
665                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
666                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
667                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                 &
668                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
669                             MERGE( 2, 0, bc_dirichlet_r),                                         &
670                             .TRUE. )
671       ENDIF
672
673       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
674          DO  n = 1, UBOUND( nest_offl%var_names_chem_r, 1 )
675             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_r(n) ) )  THEN
676                CALL get_variable( pids_id,                                                        &
677                                   TRIM( nest_offl%var_names_chem_r(n) ),                          &
678                                   nest_offl%chem_r(:,:,:,n),                                      &
679                                   MERGE( nys+1, 1, bc_dirichlet_r),                               &
680                                   MERGE( nzb+1, 1, bc_dirichlet_r),                               &
681                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                    &
682                                   MERGE( nyn-nys+1, 0, bc_dirichlet_r),                           &
683                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                       &
684                                   MERGE( 2, 0, bc_dirichlet_r),                                   &
685                                   .TRUE. )
686                nest_offl%chem_from_file_r(n) = .TRUE.
687             ENDIF
688          ENDDO
689       ENDIF
690!
691!--    Read data for northern boundary
692       CALL get_variable( pids_id, 'ls_forcing_north_u',                                           &
693                          nest_offl%u_n,                                                           &
694                          MERGE( nxlu, 1, bc_dirichlet_n ),                                        &
695                          MERGE( nzb+1, 1, bc_dirichlet_n ),                                       &
696                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                            &
697                          MERGE( nxr-nxlu+1, 0, bc_dirichlet_n ),                                  &
698                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                               &
699                          MERGE( 2, 0, bc_dirichlet_n ),                                           &
700                          .TRUE. )
701
702       CALL get_variable( pids_id, 'ls_forcing_north_v',                                           &
703                          nest_offl%v_n,                                                           &
704                          MERGE( nxl+1, 1, bc_dirichlet_n ),                                       &
705                          MERGE( nzb+1, 1, bc_dirichlet_n ),                                       &
706                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                            &
707                          MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                   &
708                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                               &
709                          MERGE( 2, 0, bc_dirichlet_n ),                                           &
710                          .TRUE. )
711
712       CALL get_variable( pids_id, 'ls_forcing_north_w',                                           &
713                          nest_offl%w_n,                                                           &
714                          MERGE( nxl+1, 1, bc_dirichlet_n ),                                       &
715                          MERGE( nzb+1, 1, bc_dirichlet_n ),                                       &
716                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                            &
717                          MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                   &
718                          MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),                               &
719                          MERGE( 2, 0, bc_dirichlet_n ),                                           &
720                          .TRUE. )
721
722       IF ( .NOT. neutral )  THEN
723          CALL get_variable( pids_id, 'ls_forcing_north_pt',                                       &
724                             nest_offl%pt_n,                                                       &
725                             MERGE( nxl+1, 1, bc_dirichlet_n ),                                    &
726                             MERGE( nzb+1, 1, bc_dirichlet_n ),                                    &
727                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                         &
728                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                &
729                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                            &
730                             MERGE( 2, 0, bc_dirichlet_n ),                                        &
731                             .TRUE. )
732       ENDIF
733       IF ( humidity )  THEN
734          CALL get_variable( pids_id, 'ls_forcing_north_qv',                                       &
735                             nest_offl%q_n,                                                        &
736                             MERGE( nxl+1, 1, bc_dirichlet_n ),                                    &
737                             MERGE( nzb+1, 1, bc_dirichlet_n ),                                    &
738                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                         &
739                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                &
740                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                            &
741                             MERGE( 2, 0, bc_dirichlet_n ),                                        &
742                             .TRUE. )
743       ENDIF
744
745       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
746          DO  n = 1, UBOUND( nest_offl%var_names_chem_n, 1 )
747             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_n(n) ) )  THEN
748                CALL get_variable( pids_id,                                                        &
749                                   TRIM( nest_offl%var_names_chem_n(n) ),                          &
750                                   nest_offl%chem_n(:,:,:,n),                                      &
751                                   MERGE( nxl+1, 1, bc_dirichlet_n ),                              &
752                                   MERGE( nzb+1, 1, bc_dirichlet_n ),                              &
753                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                   &
754                                   MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                          &
755                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                      &
756                                   MERGE( 2, 0, bc_dirichlet_n ),                                  &
757                                   .TRUE. )
758                nest_offl%chem_from_file_n(n) = .TRUE.
759             ENDIF
760          ENDDO
761       ENDIF
762!
763!--    Read data for southern boundary
764       CALL get_variable( pids_id, 'ls_forcing_south_u',                                           &
765                          nest_offl%u_s,                                                           &
766                          MERGE( nxlu, 1, bc_dirichlet_s ),                                        &
767                          MERGE( nzb+1, 1, bc_dirichlet_s ),                                       &
768                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                            &
769                          MERGE( nxr-nxlu+1, 0, bc_dirichlet_s ),                                  &
770                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                               &
771                          MERGE( 2, 0, bc_dirichlet_s ),                                           &
772                          .TRUE. )
773
774       CALL get_variable( pids_id, 'ls_forcing_south_v',                                           &
775                          nest_offl%v_s,                                                           &
776                          MERGE( nxl+1, 1, bc_dirichlet_s ),                                       &
777                          MERGE( nzb+1, 1, bc_dirichlet_s ),                                       &
778                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                            &
779                          MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                   &
780                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                               &
781                          MERGE( 2, 0, bc_dirichlet_s ),                                           &
782                          .TRUE. )
783
784       CALL get_variable( pids_id, 'ls_forcing_south_w',                                           &
785                          nest_offl%w_s,                                                           &
786                          MERGE( nxl+1, 1, bc_dirichlet_s ),                                       &
787                          MERGE( nzb+1, 1, bc_dirichlet_s ),                                       &
788                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                            &
789                          MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                   &
790                          MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),                               &
791                          MERGE( 2, 0, bc_dirichlet_s ),                                           &
792                          .TRUE. )
793
794       IF ( .NOT. neutral )  THEN
795          CALL get_variable( pids_id, 'ls_forcing_south_pt',                                       &
796                             nest_offl%pt_s,                                                       &
797                             MERGE( nxl+1, 1, bc_dirichlet_s ),                                    &
798                             MERGE( nzb+1, 1, bc_dirichlet_s ),                                    &
799                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                         &
800                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                &
801                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                            &
802                             MERGE( 2, 0, bc_dirichlet_s ),                                        &
803                             .TRUE. )
804       ENDIF
805       IF ( humidity )  THEN
806          CALL get_variable( pids_id, 'ls_forcing_south_qv',                                       &
807                             nest_offl%q_s,                                                        &
808                             MERGE( nxl+1, 1, bc_dirichlet_s ),                                    &
809                             MERGE( nzb+1, 1, bc_dirichlet_s ),                                    &
810                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                         &
811                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                &
812                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                            &
813                             MERGE( 2, 0, bc_dirichlet_s ),                                        &
814                             .TRUE. )
815       ENDIF
816
817       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
818          DO  n = 1, UBOUND( nest_offl%var_names_chem_s, 1 )
819             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_s(n) ) )  THEN
820                CALL get_variable( pids_id,                                                        &
821                                   TRIM( nest_offl%var_names_chem_s(n) ),                          &
822                                   nest_offl%chem_s(:,:,:,n),                                      &
823                                   MERGE( nxl+1, 1, bc_dirichlet_s ),                              &
824                                   MERGE( nzb+1, 1, bc_dirichlet_s ),                              &
825                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                   &
826                                   MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                          &
827                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                      &
828                                   MERGE( 2, 0, bc_dirichlet_s ),                                  &
829                                   .TRUE. )
830                nest_offl%chem_from_file_s(n) = .TRUE.
831             ENDIF
832          ENDDO
833       ENDIF
834!
835!--    Top boundary
836       CALL get_variable( pids_id, 'ls_forcing_top_u',                                             &
837                          nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),                                   &
838                          nxlu, nys+1, nest_offl%tind+1,                                           &
839                          nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
840
841       CALL get_variable( pids_id, 'ls_forcing_top_v',                                             &
842                          nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),                                   &
843                          nxl+1, nysv, nest_offl%tind+1,                                           &
844                          nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
845
846       CALL get_variable( pids_id, 'ls_forcing_top_w',                                             &
847                          nest_offl%w_top(0:1,nys:nyn,nxl:nxr),                                    &
848                          nxl+1, nys+1, nest_offl%tind+1,                                          &
849                          nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
850
851       IF ( .NOT. neutral )  THEN
852          CALL get_variable( pids_id, 'ls_forcing_top_pt',                                         &
853                             nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),                                &
854                             nxl+1, nys+1, nest_offl%tind+1,                                       &
855                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
856       ENDIF
857       IF ( humidity )  THEN
858          CALL get_variable( pids_id, 'ls_forcing_top_qv',                                         &
859                             nest_offl%q_top(0:1,nys:nyn,nxl:nxr),                                 &
860                             nxl+1, nys+1, nest_offl%tind+1,                                       &
861                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
862       ENDIF
863
864       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
865          DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
866             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
867                CALL get_variable( pids_id,                                                        &
868                                   TRIM( nest_offl%var_names_chem_t(n) ),                          &
869                                   nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),                      &
870                                   nxl+1, nys+1, nest_offl%tind+1,                                 &
871                                   nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
872                nest_offl%chem_from_file_t(n) = .TRUE.
873             ENDIF
874          ENDDO
875       ENDIF
876!
877!-- Read data for LOD 1, i.e. time-dependent profiles. In constrast to LOD 2 where the amount of IO
878!-- is larger, only the respective boundary processes read the data.
879    ELSE
880       IF ( bc_dirichlet_l )  THEN
881          CALL get_variable( pids_id, 'ls_forcing_left_u',                                         &
882                             nest_offl%u_l(0:1,:,1:1),                                             & ! array to be read
883                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     & ! start index z direction
884                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          & ! start index time dimension
885                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             & ! number of elements along z
886                             MERGE( 2, 0, bc_dirichlet_l) )                                          ! number of time steps (2 or 0)
887          CALL get_variable( pids_id, 'ls_forcing_left_v',                                         &
888                             nest_offl%v_l(0:1,:,1:1),                                             &
889                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
890                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
891                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             &
892                             MERGE( 2, 0, bc_dirichlet_l) )
893          CALL get_variable( pids_id, 'ls_forcing_left_w',                                         &
894                             nest_offl%w_l(0:1,:,1:1),                                             &
895                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
896                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
897                             MERGE( nest_offl%nzw, 0, bc_dirichlet_l),                             &
898                             MERGE( 2, 0, bc_dirichlet_l) )
899          IF ( .NOT. neutral )  THEN
900             CALL get_variable( pids_id, 'ls_forcing_left_pt',                                     &
901                                nest_offl%pt_l(0:1,:,1:1),                                         &
902                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
903                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
904                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          &
905                                MERGE( 2, 0, bc_dirichlet_l) )
906          ENDIF
907          IF ( humidity )  THEN
908             CALL get_variable( pids_id, 'ls_forcing_left_qv',                                     &
909                                nest_offl%q_l(0:1,:,1:1),                                          &
910                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
911                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
912                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          &
913                                MERGE( 2, 0, bc_dirichlet_l) )
914          ENDIF
915          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
916             DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
917                IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
918                   CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),              &
919                                      nest_offl%chem_l(0:1,:,1:1,n),                               &
920                                      MERGE( nzb+1, 1, bc_dirichlet_l),                            &
921                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                 &
922                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                    &
923                                      MERGE( 2, 0, bc_dirichlet_l) )
924                   nest_offl%chem_from_file_l(n) = .TRUE.
925                ENDIF
926             ENDDO
927          ENDIF
928       ENDIF
929       IF ( bc_dirichlet_r )  THEN
930          CALL get_variable( pids_id, 'ls_forcing_right_u',                                        &
931                             nest_offl%u_r(0:1,:,1:1),                                             &
932                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
933                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
934                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
935                             MERGE( 2, 0, bc_dirichlet_r) )
936          CALL get_variable( pids_id, 'ls_forcing_right_v',                                        &
937                             nest_offl%v_r(0:1,:,1:1),                                             &
938                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
939                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
940                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
941                             MERGE( 2, 0, bc_dirichlet_r) )
942          CALL get_variable( pids_id, 'ls_forcing_right_w',                                        &
943                             nest_offl%w_r(0:1,:,1:1),                                             &
944                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
945                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
946                             MERGE( nest_offl%nzw, 0, bc_dirichlet_r),                             &
947                             MERGE( 2, 0, bc_dirichlet_r) )
948          IF ( .NOT. neutral )  THEN
949             CALL get_variable( pids_id, 'ls_forcing_right_pt',                                    &
950                                nest_offl%pt_r(0:1,:,1:1),                                         &
951                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
952                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
953                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
954                                MERGE( 2, 0, bc_dirichlet_r) )
955          ENDIF
956          IF ( humidity )  THEN
957             CALL get_variable( pids_id, 'ls_forcing_right_qv',                                    &
958                                nest_offl%q_r(0:1,:,1:1),                                          &
959                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
960                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
961                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
962                                MERGE( 2, 0, bc_dirichlet_r) )
963          ENDIF
964          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
965             DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
966                IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
967                   CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),              &
968                                      nest_offl%chem_r(0:1,:,1:1,n),                               &
969                                      MERGE( nzb+1, 1, bc_dirichlet_r),                            &
970                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                 &
971                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                    &
972                                      MERGE( 2, 0, bc_dirichlet_r) )
973                   nest_offl%chem_from_file_r(n) = .TRUE.
974                ENDIF
975             ENDDO
976          ENDIF
977       ENDIF
978       IF ( bc_dirichlet_n )  THEN
979          CALL get_variable( pids_id, 'ls_forcing_north_u',                                        &
980                             nest_offl%u_n(0:1,:,1:1),                                             &
981                             MERGE( nzb+1, 1, bc_dirichlet_n),                                     &
982                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                          &
983                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                             &
984                             MERGE( 2, 0, bc_dirichlet_n) )
985          CALL get_variable( pids_id, 'ls_forcing_north_v',                                        &
986                             nest_offl%v_n(0:1,:,1:1),                                             &
987                             MERGE( nzb+1, 1, bc_dirichlet_n),                                     &
988                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                          &
989                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                             &
990                             MERGE( 2, 0, bc_dirichlet_n) )
991          CALL get_variable( pids_id, 'ls_forcing_north_w',                                        &
992                             nest_offl%w_n(0:1,:,1:1),                                             &
993                             MERGE( nzb+1, 1, bc_dirichlet_n),                                     &
994                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                          &
995                             MERGE( nest_offl%nzw, 0, bc_dirichlet_n),                             &
996                             MERGE( 2, 0, bc_dirichlet_n) )
997          IF ( .NOT. neutral )  THEN
998             CALL get_variable( pids_id, 'ls_forcing_north_pt',                                    &
999                                nest_offl%pt_n(0:1,:,1:1),                                         &
1000                                MERGE( nzb+1, 1, bc_dirichlet_n),                                  &
1001                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                       &
1002                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                          &
1003                                MERGE( 2, 0, bc_dirichlet_n) )
1004          ENDIF
1005          IF ( humidity )  THEN
1006             CALL get_variable( pids_id, 'ls_forcing_north_qv',                                    &
1007                                nest_offl%q_n(0:1,:,1:1),                                          &
1008                                MERGE( nzb+1, 1, bc_dirichlet_n),                                  &
1009                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                       &
1010                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                          &
1011                                MERGE( 2, 0, bc_dirichlet_n) )
1012          ENDIF
1013          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1014             DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
1015                IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
1016                   CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),              &
1017                                      nest_offl%chem_n(0:1,:,1:1,n),                               &
1018                                      MERGE( nzb+1, 1, bc_dirichlet_n),                            &
1019                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                 &
1020                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                    &
1021                                      MERGE( 2, 0, bc_dirichlet_n) )
1022                   nest_offl%chem_from_file_n(n) = .TRUE.
1023                ENDIF
1024             ENDDO
1025          ENDIF
1026       ENDIF
1027       IF ( bc_dirichlet_s )  THEN
1028          CALL get_variable( pids_id, 'ls_forcing_south_u',                                        &
1029                             nest_offl%u_s(0:1,:,1:1),                                             &
1030                             MERGE( nzb+1, 1, bc_dirichlet_s),                                     &
1031                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                          &
1032                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                             &
1033                             MERGE( 2, 0, bc_dirichlet_s) )
1034          CALL get_variable( pids_id, 'ls_forcing_south_v',                                        &
1035                             nest_offl%v_s(0:1,:,1:1),                                             &
1036                             MERGE( nzb+1, 1, bc_dirichlet_s),                                     &
1037                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                          &
1038                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                             &
1039                             MERGE( 2, 0, bc_dirichlet_s) )
1040          CALL get_variable( pids_id, 'ls_forcing_south_w',                                        &
1041                             nest_offl%w_s(0:1,:,1:1),                                             &
1042                             MERGE( nzb+1, 1, bc_dirichlet_s),                                     &
1043                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                          &
1044                             MERGE( nest_offl%nzw, 0, bc_dirichlet_s),                             &
1045                             MERGE( 2, 0, bc_dirichlet_s) )
1046          IF ( .NOT. neutral )  THEN
1047             CALL get_variable( pids_id, 'ls_forcing_south_pt',                                    &
1048                                nest_offl%pt_s(0:1,:,1:1),                                         &
1049                                MERGE( nzb+1, 1, bc_dirichlet_s),                                  &
1050                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                       &
1051                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                          &
1052                                MERGE( 2, 0, bc_dirichlet_s) )
1053          ENDIF
1054          IF ( humidity )  THEN
1055             CALL get_variable( pids_id, 'ls_forcing_south_qv',                                    &
1056                                nest_offl%q_s(0:1,:,1:1),                                          &
1057                                MERGE( nzb+1, 1, bc_dirichlet_s),                                  &
1058                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                       &
1059                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                          &
1060                                MERGE( 2, 0, bc_dirichlet_s) )
1061          ENDIF
1062          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1063             DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
1064                IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
1065                   CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),              &
1066                                      nest_offl%chem_s(0:1,:,1:1,n),                               &
1067                                      MERGE( nzb+1, 1, bc_dirichlet_s),                            &
1068                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                 &
1069                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                    &
1070                                      MERGE( 2, 0, bc_dirichlet_s) )
1071                   nest_offl%chem_from_file_s(n) = .TRUE.
1072                ENDIF
1073             ENDDO
1074          ENDIF
1075       ENDIF
1076!
1077!--    Read top boundary data, which is actually only a scalar value in the LOD 1 case.
1078       CALL get_variable( pids_id, 'ls_forcing_top_u',                                             &
1079                          nest_offl%u_top(0:1,1,1),                                                & ! array to be read
1080                          nest_offl%tind+1,                                                        & ! start index in time
1081                          2 )                                                                        ! number of elements to be read
1082       CALL get_variable( pids_id, 'ls_forcing_top_v',                                             &
1083                          nest_offl%v_top(0:1,1,1),                                                &
1084                          nest_offl%tind+1,                                                        &
1085                          2 )
1086       CALL get_variable( pids_id, 'ls_forcing_top_w',                                             &
1087                          nest_offl%w_top(0:1,1,1),                                                &
1088                          nest_offl%tind+1,                                                        &
1089                          2 )
1090       IF ( .NOT. neutral )  THEN
1091          CALL get_variable( pids_id, 'ls_forcing_top_pt',                                         &
1092                             nest_offl%pt_top(0:1,1,1),                                            &
1093                             nest_offl%tind+1,                                                     &
1094                             2 )
1095       ENDIF
1096       IF ( humidity )  THEN
1097          CALL get_variable( pids_id, 'ls_forcing_top_qv',                                         &
1098                             nest_offl%q_top(0:1,1,1),                                             &
1099                             nest_offl%tind+1,                                                     &
1100                             2 )
1101       ENDIF
1102       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1103          DO  n = 1, UBOUND( nest_offl%var_names_chem_t, 1 )
1104             IF ( check_existence( nest_offl%var_names, nest_offl%var_names_chem_t(n) ) )  THEN
1105                CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),                 &
1106                                   nest_offl%chem_top(0:1,1,1,n),                                  &
1107                                   nest_offl%tind+1,                                               &
1108                                   2 )
1109                nest_offl%chem_from_file_t(n) = .TRUE.
1110             ENDIF
1111          ENDDO
1112       ENDIF
1113    ENDIF
1114
1115
1116!
1117!-- Close input file
1118    CALL close_input_file( pids_id )
1119#endif
1120!
1121!-- Set control flag to indicate that boundary data has been initially input.
1122    nest_offl%init = .TRUE.
1123!
1124!-- Call offline nesting for salsa
1125    IF ( salsa )  CALL salsa_nesting_offl_input
1126!
1127!-- End of CPU measurement
1128    CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
1129
1130 END SUBROUTINE nesting_offl_input
1131
1132
1133!--------------------------------------------------------------------------------------------------!
1134! Description:
1135! ------------
1136!> In this subroutine a constant mass within the model domain is guaranteed.
1137!> Larger-scale models may be based on a compressible equation system, which is not consistent with
1138!> PALMs incompressible equation system. In order to avoid a decrease or increase of mass during the
1139!> simulation, non-divergent flow through the lateral and top boundaries is compensated by the
1140!> vertical wind component at the top boundary.
1141!--------------------------------------------------------------------------------------------------!
1142 SUBROUTINE nesting_offl_mass_conservation
1143
1144    INTEGER(iwp) ::  i  !< grid index in x-direction
1145    INTEGER(iwp) ::  j  !< grid index in y-direction
1146    INTEGER(iwp) ::  k  !< grid index in z-direction
1147
1148    REAL(wp) ::  d_area_t   !< inverse of the total area of the horizontal model domain
1149    REAL(wp) ::  w_correct  !< vertical velocity increment required to compensate non-divergent flow through the boundaries
1150
1151    REAL(wp), DIMENSION(1:3) ::  volume_flow_l   !< local volume flow
1152
1153
1154    IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_mass_conservation', 'start' )
1155
1156    CALL  cpu_log( log_point(58), 'offline nesting', 'start' )
1157
1158    volume_flow   = 0.0_wp
1159    volume_flow_l = 0.0_wp
1160
1161    d_area_t = 1.0_wp / ( ( nx + 1 ) * dx * ( ny + 1 ) * dy )
1162
1163    IF ( bc_dirichlet_l )  THEN
1164       i = nxl
1165       DO  j = nys, nyn
1166          DO  k = nzb+1, nzt
1167             volume_flow_l(1) = volume_flow_l(1) + u(k,j,i) * dzw(k) * dy * rho_air(k)             &
1168                                * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 1 ) )
1169          ENDDO
1170       ENDDO
1171    ENDIF
1172    IF ( bc_dirichlet_r )  THEN
1173       i = nxr+1
1174       DO  j = nys, nyn
1175          DO  k = nzb+1, nzt
1176             volume_flow_l(1) = volume_flow_l(1) - u(k,j,i) * dzw(k) * dy * rho_air(k)             &
1177                                * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 1 ) )
1178          ENDDO
1179       ENDDO
1180    ENDIF
1181    IF ( bc_dirichlet_s )  THEN
1182       j = nys
1183       DO  i = nxl, nxr
1184          DO  k = nzb+1, nzt
1185             volume_flow_l(2) = volume_flow_l(2) + v(k,j,i) * dzw(k) * dx * rho_air(k)             &
1186                                * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 2 ) )
1187          ENDDO
1188       ENDDO
1189    ENDIF
1190    IF ( bc_dirichlet_n )  THEN
1191       j = nyn+1
1192       DO  i = nxl, nxr
1193          DO  k = nzb+1, nzt
1194             volume_flow_l(2) = volume_flow_l(2) - v(k,j,i) * dzw(k) * dx * rho_air(k)             &
1195                                * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 2 ) )
1196          ENDDO
1197       ENDDO
1198    ENDIF
1199!
1200!-- Top boundary
1201    k = nzt
1202    DO  i = nxl, nxr
1203       DO  j = nys, nyn
1204          volume_flow_l(3) = volume_flow_l(3) - rho_air_zw(k) * w(k,j,i) * dx * dy
1205       ENDDO
1206    ENDDO
1207
1208#if defined( __parallel )
1209    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1210    CALL MPI_ALLREDUCE( volume_flow_l, volume_flow, 3, MPI_REAL, MPI_SUM, comm2d, ierr )
1211#else
1212    volume_flow = volume_flow_l
1213#endif
1214
1215    w_correct = SUM( volume_flow ) * d_area_t * drho_air_zw(nzt)
1216
1217    DO  i = nxl, nxr
1218       DO  j = nys, nyn
1219          DO  k = nzt, nzt + 1
1220             w(k,j,i) = w(k,j,i) + w_correct                                                       &
1221                                   * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 3 ) )
1222          ENDDO
1223       ENDDO
1224    ENDDO
1225
1226    CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
1227
1228    IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_mass_conservation', 'end' )
1229
1230 END SUBROUTINE nesting_offl_mass_conservation
1231
1232
1233!--------------------------------------------------------------------------------------------------!
1234! Description:
1235! ------------
1236!> Set the lateral and top boundary conditions in case the PALM domain is nested offline in a
1237!> mesoscale model. Further, average boundary data and determine mean profiles, further used for
1238!> correct damping in the sponge layer.
1239!--------------------------------------------------------------------------------------------------!
1240 SUBROUTINE nesting_offl_bc
1241
1242    USE exchange_horiz_mod,                                                                        &
1243        ONLY:  exchange_horiz
1244
1245    INTEGER(iwp) ::  i  !< running index x-direction
1246    INTEGER(iwp) ::  j  !< running index y-direction
1247    INTEGER(iwp) ::  k  !< running index z-direction
1248    INTEGER(iwp) ::  n  !< running index for chemical species
1249
1250    REAL(wp), DIMENSION(nzb:nzt+1) ::  pt_ref    !< reference profile for potential temperature
1251    REAL(wp), DIMENSION(nzb:nzt+1) ::  pt_ref_l  !< reference profile for potential temperature on subdomain
1252    REAL(wp), DIMENSION(nzb:nzt+1) ::  q_ref     !< reference profile for mixing ratio
1253    REAL(wp), DIMENSION(nzb:nzt+1) ::  q_ref_l   !< reference profile for mixing ratio on subdomain
1254    REAL(wp), DIMENSION(nzb:nzt+1) ::  u_ref     !< reference profile for u-component
1255    REAL(wp), DIMENSION(nzb:nzt+1) ::  u_ref_l   !< reference profile for u-component on subdomain
1256    REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref     !< reference profile for v-component
1257    REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref_l   !< reference profile for v-component on subdomain
1258    REAL(wp), DIMENSION(nzb:nzt+1) ::  var_1d    !< pre-interpolated profile for LOD1 mode
1259
1260    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_chem    !< reference profile for chemical species
1261    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_chem_l  !< reference profile for chemical species on subdomain
1262
1263    IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'start' )
1264
1265    CALL  cpu_log( log_point(58), 'offline nesting', 'start' )
1266!
1267!-- Initialize mean profiles, derived from boundary data, to zero.
1268    pt_ref   = 0.0_wp
1269    q_ref    = 0.0_wp
1270    u_ref    = 0.0_wp
1271    v_ref    = 0.0_wp
1272
1273    pt_ref_l = 0.0_wp
1274    q_ref_l  = 0.0_wp
1275    u_ref_l  = 0.0_wp
1276    v_ref_l  = 0.0_wp
1277!
1278!-- If required, allocate temporary arrays to compute chemistry mean profiles
1279    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1280       ALLOCATE( ref_chem(nzb:nzt+1,1:UBOUND( chem_species, 1 ) )   )
1281       ALLOCATE( ref_chem_l(nzb:nzt+1,1:UBOUND( chem_species, 1 ) ) )
1282       ref_chem   = 0.0_wp
1283       ref_chem_l = 0.0_wp
1284    ENDIF
1285!
1286!-- Set boundary conditions of u-, v-, w-component, as well as q, and pt.
1287!-- Note, boundary values at the left boundary: i=-1 (v,w,pt,q) and i=0 (u), at the right boundary:
1288!-- i=nxr+1 (all), at the south boundary: j=-1 (u,w,pt,q) and j=0 (v), at the north boundary:
1289!-- j=nyn+1 (all).
1290!-- Please note, at the left (for u) and south (for v) boundary, values for u and v are set also at
1291!-- i/j=-1, since these values are used in boundary_conditions() to restore prognostic values.
1292!-- Further, sum up data to calculate mean profiles from boundary data, used for Rayleigh damping.
1293    IF ( bc_dirichlet_l  )  THEN
1294!
1295!--    u-component
1296       IF ( lod == 2 )  THEN
1297          DO  j = nys, nyn
1298             DO  k = nzb+1, nzt
1299                u(k,j,i_bound_u) = interpolate_in_time( nest_offl%u_l(0,k,j),                      &
1300                                                        nest_offl%u_l(1,k,j),                      &
1301                                                        fac_dt ) *                                 &
1302                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1303                                          BTEST( wall_flags_total_0(k,j,i_bound_u), 1 ) )
1304             ENDDO
1305             u(:,j,i_bound_u-1) = u(:,j,i_bound_u)
1306             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
1307          ENDDO
1308       ELSE
1309!
1310!--       Pre-interpolate profile before mapping onto the boundaries.
1311          DO  k = nzb+1, nzt
1312             var_1d(k) = interpolate_in_time( nest_offl%u_l(0,k,1),                                &
1313                                              nest_offl%u_l(1,k,1),                                &
1314                                              fac_dt )
1315          ENDDO
1316          DO  j = nys, nyn
1317             u(nzb+1:nzt,j,i_bound_u) = var_1d(nzb+1:nzt) *                                        &
1318                                     MERGE( 1.0_wp, 0.0_wp,                                        &
1319                                            BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound_u), 1 ) )
1320             u(:,j,i_bound_u-1) = u(:,j,i_bound_u)
1321             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
1322          ENDDO
1323       ENDIF
1324!
1325!--    w-component
1326       IF ( lod == 2 )  THEN
1327          DO  j = nys, nyn
1328             DO  k = nzb+1, nzt-1
1329                w(k,j,i_bound) = interpolate_in_time( nest_offl%w_l(0,k,j),                        &
1330                                                      nest_offl%w_l(1,k,j),                        &
1331                                                      fac_dt ) *                                   &
1332                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1333                                        BTEST( wall_flags_total_0(k,j,i_bound), 3 ) )
1334             ENDDO
1335             w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
1336          ENDDO
1337       ELSE
1338          DO  k = nzb+1, nzt-1
1339             var_1d(k) = interpolate_in_time( nest_offl%w_l(0,k,1),                                &
1340                                              nest_offl%w_l(1,k,1),                                &
1341                                              fac_dt )
1342          ENDDO
1343          DO  j = nys, nyn
1344             w(nzb+1:nzt-1,j,i_bound) = var_1d(nzb+1:nzt-1) *                                      &
1345                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1346                                             BTEST( wall_flags_total_0(nzb+1:nzt-1,j,i_bound), 3 ) )
1347             w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
1348          ENDDO
1349       ENDIF
1350!
1351!--    v-component
1352       IF ( lod == 2 )  THEN
1353          DO  j = nysv, nyn
1354             DO  k = nzb+1, nzt
1355                v(k,j,i_bound) = interpolate_in_time( nest_offl%v_l(0,k,j),                        &
1356                                                      nest_offl%v_l(1,k,j),                        &
1357                                                      fac_dt ) *                                   &
1358                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1359                                        BTEST( wall_flags_total_0(k,j,i_bound), 2 ) )
1360             ENDDO
1361             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
1362          ENDDO
1363       ELSE
1364          DO  k = nzb+1, nzt
1365             var_1d(k) = interpolate_in_time( nest_offl%v_l(0,k,1),                                &
1366                                              nest_offl%v_l(1,k,1),                                &
1367                                              fac_dt )
1368          ENDDO
1369          DO  j = nysv, nyn
1370             v(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt) *                                          &
1371                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1372                                             BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound), 2 ) )
1373             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
1374          ENDDO
1375       ENDIF
1376!
1377!--    Potential temperature
1378       IF ( .NOT. neutral )  THEN
1379          IF ( lod == 2 )  THEN
1380             DO  j = nys, nyn
1381                DO  k = nzb+1, nzt
1382                   pt(k,j,i_bound) = interpolate_in_time( nest_offl%pt_l(0,k,j),                   &
1383                                                          nest_offl%pt_l(1,k,j),                   &
1384                                                          fac_dt )
1385                ENDDO
1386                pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
1387             ENDDO
1388          ELSE
1389             DO  k = nzb+1, nzt
1390                var_1d(k) = interpolate_in_time( nest_offl%pt_l(0,k,1),                            &
1391                                                 nest_offl%pt_l(1,k,1),                            &
1392                                                 fac_dt )
1393             ENDDO
1394             DO  j = nys, nyn
1395                pt(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1396                pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
1397             ENDDO
1398          ENDIF
1399       ENDIF
1400!
1401!--    Humidity
1402       IF ( humidity )  THEN
1403          IF ( lod == 2 )  THEN
1404             DO  j = nys, nyn
1405                DO  k = nzb+1, nzt
1406                   q(k,j,i_bound) = interpolate_in_time( nest_offl%q_l(0,k,j),                     &
1407                                                         nest_offl%q_l(1,k,j),                     &
1408                                                         fac_dt )
1409                ENDDO
1410                q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
1411             ENDDO
1412          ELSE
1413             DO  k = nzb+1, nzt
1414                var_1d(k) = interpolate_in_time( nest_offl%q_l(0,k,1),                             &
1415                                                 nest_offl%q_l(1,k,1),                             &
1416                                                 fac_dt )
1417             ENDDO
1418             DO  j = nys, nyn
1419                q(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1420                q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
1421             ENDDO
1422          ENDIF
1423       ENDIF
1424!
1425!--    Chemistry
1426       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1427          DO  n = 1, UBOUND( chem_species, 1 )
1428             IF ( nest_offl%chem_from_file_l(n) )  THEN
1429                IF ( lod == 2 )  THEN
1430                   DO  j = nys, nyn
1431                      DO  k = nzb+1, nzt
1432                         chem_species(n)%conc(k,j,i_bound) = interpolate_in_time(                  &
1433                                                                        nest_offl%chem_l(0,k,j,n), &
1434                                                                        nest_offl%chem_l(1,k,j,n), &
1435                                                                        fac_dt                   )
1436                      ENDDO
1437                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1438                                                + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
1439                   ENDDO
1440                ELSE
1441                   DO  k = nzb+1, nzt
1442                      var_1d(k) = interpolate_in_time( nest_offl%chem_l(0,k,1,n),                  &
1443                                                       nest_offl%chem_l(1,k,1,n),                  &
1444                                                       fac_dt )
1445                   ENDDO
1446                   DO  j = nys, nyn
1447                      chem_species(n)%conc(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1448                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1449                                                + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
1450                   ENDDO
1451                ENDIF
1452             ENDIF
1453          ENDDO
1454       ENDIF
1455
1456    ENDIF
1457
1458    IF ( bc_dirichlet_r  )  THEN
1459!
1460!--    u-component
1461       IF ( lod == 2 )  THEN
1462          DO  j = nys, nyn
1463             DO  k = nzb+1, nzt
1464                u(k,j,i_bound_u) = interpolate_in_time( nest_offl%u_r(0,k,j),                      &
1465                                                        nest_offl%u_r(1,k,j),                      &
1466                                                        fac_dt ) *                                 &
1467                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1468                                          BTEST( wall_flags_total_0(k,j,i_bound_u), 1 ) )
1469             ENDDO
1470             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
1471          ENDDO
1472       ELSE
1473          DO  k = nzb+1, nzt
1474             var_1d(k) = interpolate_in_time( nest_offl%u_r(0,k,1),                                &
1475                                              nest_offl%u_r(1,k,1),                                &
1476                                              fac_dt )
1477          ENDDO
1478          DO  j = nys, nyn
1479             u(nzb+1:nzt,j,i_bound_u) = var_1d(nzb+1:nzt) *                                        &
1480                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1481                                             BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound_u), 1 ) )
1482             u_ref_l(nzb+1:nzt)       = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
1483          ENDDO
1484       ENDIF
1485!
1486!--    w-component
1487       IF ( lod == 2 )  THEN
1488          DO  j = nys, nyn
1489             DO  k = nzb+1, nzt-1
1490                w(k,j,i_bound) = interpolate_in_time( nest_offl%w_r(0,k,j),                        &
1491                                                      nest_offl%w_r(1,k,j),                        &
1492                                                      fac_dt ) *                                   &
1493                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1494                                        BTEST( wall_flags_total_0(k,j,i_bound), 3 ) )
1495             ENDDO
1496             w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
1497          ENDDO
1498       ELSE
1499          DO  k = nzb+1, nzt-1
1500             var_1d(k) = interpolate_in_time( nest_offl%w_r(0,k,1),                                &
1501                                              nest_offl%w_r(1,k,1),                                &
1502                                              fac_dt )
1503          ENDDO
1504          DO  j = nys, nyn
1505             w(nzb+1:nzt-1,j,i_bound) = var_1d(nzb+1:nzt-1) *                                      &
1506                                  MERGE( 1.0_wp, 0.0_wp,                                           &
1507                                         BTEST( wall_flags_total_0(nzb+1:nzt-1,j,i_bound), 3 ) )
1508             w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
1509          ENDDO
1510       ENDIF
1511!
1512!--    v-component
1513       IF ( lod == 2 )  THEN
1514          DO  j = nysv, nyn
1515             DO  k = nzb+1, nzt
1516                v(k,j,i_bound) = interpolate_in_time( nest_offl%v_r(0,k,j),                        &
1517                                                      nest_offl%v_r(1,k,j),                        &
1518                                                      fac_dt ) *                                   &
1519                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1520                                        BTEST( wall_flags_total_0(k,j,i_bound), 2 ) )
1521             ENDDO
1522             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
1523          ENDDO
1524       ELSE
1525          DO  k = nzb+1, nzt
1526             var_1d(k) = interpolate_in_time( nest_offl%v_r(0,k,1),                                &
1527                                              nest_offl%v_r(1,k,1),                                &
1528                                              fac_dt )
1529          ENDDO
1530          DO  j = nysv, nyn
1531             v(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt) *                                          &
1532                                    MERGE( 1.0_wp, 0.0_wp,                                         &
1533                                           BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound), 2 ) )
1534             v_ref_l(nzb+1:nzt)     = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
1535          ENDDO
1536       ENDIF
1537!
1538!--    Potential temperature
1539       IF ( .NOT. neutral )  THEN
1540          IF ( lod == 2 )  THEN
1541             DO  j = nys, nyn
1542                DO  k = nzb+1, nzt
1543                   pt(k,j,i_bound) = interpolate_in_time( nest_offl%pt_r(0,k,j),                   &
1544                                                          nest_offl%pt_r(1,k,j),                   &
1545                                                          fac_dt )
1546                ENDDO
1547                pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
1548             ENDDO
1549          ELSE
1550             DO  k = nzb+1, nzt
1551                var_1d(k) = interpolate_in_time( nest_offl%pt_r(0,k,1),                            &
1552                                                 nest_offl%pt_r(1,k,1),                            &
1553                                                 fac_dt )
1554             ENDDO
1555             DO  j = nys, nyn
1556                pt(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1557                pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
1558             ENDDO
1559          ENDIF
1560       ENDIF
1561!
1562!--    Humidity
1563       IF ( humidity )  THEN
1564          IF ( lod == 2 )  THEN
1565             DO  j = nys, nyn
1566                DO  k = nzb+1, nzt
1567                   q(k,j,i_bound) = interpolate_in_time( nest_offl%q_r(0,k,j),                     &
1568                                                         nest_offl%q_r(1,k,j),                     &
1569                                                         fac_dt )
1570                ENDDO
1571                q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
1572             ENDDO
1573          ELSE
1574             DO  k = nzb+1, nzt
1575                var_1d(k) = interpolate_in_time( nest_offl%q_r(0,k,1),                             &
1576                                                 nest_offl%q_r(1,k,1),                             &
1577                                                 fac_dt )
1578             ENDDO
1579             DO  j = nys, nyn
1580                q(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1581                q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
1582             ENDDO
1583          ENDIF
1584       ENDIF
1585!
1586!--    Chemistry
1587       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1588          DO  n = 1, UBOUND( chem_species, 1 )
1589             IF ( nest_offl%chem_from_file_r(n) )  THEN
1590                IF ( lod == 2 )  THEN
1591                   DO  j = nys, nyn
1592                      DO  k = nzb+1, nzt
1593                         chem_species(n)%conc(k,j,i_bound) = interpolate_in_time(                  &
1594                                                                        nest_offl%chem_r(0,k,j,n), &
1595                                                                        nest_offl%chem_r(1,k,j,n), &
1596                                                                        fac_dt                   )
1597                      ENDDO
1598                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1599                                                + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
1600                   ENDDO
1601                ELSE
1602                   DO  k = nzb+1, nzt
1603                      var_1d(k) = interpolate_in_time( nest_offl%chem_r(0,k,1,n),                  &
1604                                                       nest_offl%chem_r(1,k,1,n),                  &
1605                                                       fac_dt )
1606                   ENDDO
1607                   DO  j = nys, nyn
1608                      chem_species(n)%conc(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
1609                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1610                                                + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
1611                   ENDDO
1612                ENDIF
1613             ENDIF
1614          ENDDO
1615       ENDIF
1616
1617    ENDIF
1618
1619    IF ( bc_dirichlet_n )  THEN
1620!
1621!--    v-component
1622       IF ( lod == 2 )  THEN
1623          DO  i = nxl, nxr
1624             DO  k = nzb+1, nzt
1625                v(k,j_bound_v,i) = interpolate_in_time( nest_offl%v_n(0,k,i),                      &
1626                                                        nest_offl%v_n(1,k,i),                      &
1627                                                        fac_dt ) *                                 &
1628                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1629                                          BTEST( wall_flags_total_0(k,j_bound_v,i), 2 ) )
1630             ENDDO
1631             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
1632          ENDDO
1633       ELSE
1634          DO  k = nzb+1, nzt
1635             var_1d(k) = interpolate_in_time( nest_offl%v_n(0,k,1),                                &
1636                                              nest_offl%v_n(1,k,1),                                &
1637                                              fac_dt )
1638          ENDDO
1639          DO  i = nxl, nxr
1640             v(nzb+1:nzt,j_bound_v,i) = var_1d(nzb+1:nzt) *                                        &
1641                                  MERGE( 1.0_wp, 0.0_wp,                                           &
1642                                         BTEST( wall_flags_total_0(nzb+1:nzt,j_bound_v,i), 2 ) )
1643             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
1644          ENDDO
1645       ENDIF
1646!
1647!--    w-component
1648       IF ( lod == 2 )  THEN
1649          DO  i = nxl, nxr
1650             DO  k = nzb+1, nzt-1
1651                w(k,j_bound,i) = interpolate_in_time( nest_offl%w_n(0,k,i),                        &
1652                                                      nest_offl%w_n(1,k,i),                        &
1653                                                      fac_dt ) *                                   &
1654                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1655                                        BTEST( wall_flags_total_0(k,j_bound,i), 3 ) )
1656             ENDDO
1657             w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
1658          ENDDO
1659       ELSE
1660          DO  k = nzb+1, nzt-1
1661             var_1d(k) = interpolate_in_time( nest_offl%w_n(0,k,1),                                &
1662                                              nest_offl%w_n(1,k,1),                                &
1663                                              fac_dt )
1664          ENDDO
1665          DO  i = nxl, nxr
1666             w(nzb+1:nzt-1,j_bound,i) = var_1d(nzb+1:nzt-1) *                                      &
1667                                  MERGE( 1.0_wp, 0.0_wp,                                           &
1668                                         BTEST( wall_flags_total_0(nzb+1:nzt-1,j_bound,i), 3 ) )
1669             w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
1670          ENDDO
1671       ENDIF
1672!
1673!--    u-component
1674       IF ( lod == 2 )  THEN
1675          DO  i = nxlu, nxr
1676             DO  k = nzb+1, nzt
1677                u(k,j_bound,i) = interpolate_in_time( nest_offl%u_n(0,k,i),                        &
1678                                                      nest_offl%u_n(1,k,i),                        &
1679                                                      fac_dt ) *                                   &
1680                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1681                                        BTEST( wall_flags_total_0(k,j_bound,i), 1 ) )
1682             ENDDO
1683             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
1684          ENDDO
1685       ELSE
1686          DO  k = nzb+1, nzt
1687             var_1d(k) = interpolate_in_time( nest_offl%u_n(0,k,1),                                &
1688                                              nest_offl%u_n(1,k,1),                                &
1689                                              fac_dt )
1690          ENDDO
1691          DO  i = nxlu, nxr
1692             u(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt) *                                          &
1693                                    MERGE( 1.0_wp, 0.0_wp,                                         &
1694                                           BTEST( wall_flags_total_0(nzb+1:nzt,j_bound,i), 1 ) )
1695             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
1696          ENDDO
1697       ENDIF
1698!
1699!--    Potential temperature
1700       IF ( .NOT. neutral )  THEN
1701          IF ( lod == 2 )  THEN
1702             DO  i = nxl, nxr
1703                DO  k = nzb+1, nzt
1704                   pt(k,j_bound,i) = interpolate_in_time( nest_offl%pt_n(0,k,i),                   &
1705                                                          nest_offl%pt_n(1,k,i),                   &
1706                                                          fac_dt )
1707                ENDDO
1708                pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
1709             ENDDO
1710          ELSE
1711             DO  k = nzb+1, nzt
1712                var_1d(k) = interpolate_in_time( nest_offl%pt_n(0,k,1),                            &
1713                                                 nest_offl%pt_n(1,k,1),                            &
1714                                                 fac_dt )
1715             ENDDO
1716             DO  i = nxl, nxr
1717                pt(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1718                pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
1719             ENDDO
1720          ENDIF
1721       ENDIF
1722!
1723!--    Humidity
1724       IF ( humidity )  THEN
1725          IF ( lod == 2 )  THEN
1726             DO  i = nxl, nxr
1727                DO  k = nzb+1, nzt
1728                   q(k,j_bound,i) = interpolate_in_time( nest_offl%q_n(0,k,i),                     &
1729                                                         nest_offl%q_n(1,k,i),                     &
1730                                                         fac_dt )
1731                ENDDO
1732                q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
1733             ENDDO
1734          ELSE
1735             DO  k = nzb+1, nzt
1736                var_1d(k) = interpolate_in_time( nest_offl%q_n(0,k,1),                             &
1737                                                 nest_offl%q_n(1,k,1),                             &
1738                                                 fac_dt )
1739             ENDDO
1740             DO  i = nxl, nxr
1741                q(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1742                q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
1743             ENDDO
1744          ENDIF
1745       ENDIF
1746!
1747!--    Chemistry
1748       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1749          DO  n = 1, UBOUND( chem_species, 1 )
1750             IF ( nest_offl%chem_from_file_n(n) )  THEN
1751                IF ( lod == 2 )  THEN
1752                   DO  i = nxl, nxr
1753                      DO  k = nzb+1, nzt
1754                         chem_species(n)%conc(k,j_bound,i) = interpolate_in_time(                  &
1755                                                                     nest_offl%chem_n(0,k,i,n),    &
1756                                                                     nest_offl%chem_n(1,k,i,n),    &
1757                                                                     fac_dt                    )
1758                      ENDDO
1759                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1760                                                + chem_species(n)%conc(nzb+1:nzt,j_bound,i)
1761                   ENDDO
1762                ELSE
1763                   DO  k = nzb+1, nzt
1764                      var_1d(k) = interpolate_in_time( nest_offl%chem_n(0,k,1,n),                  &
1765                                                       nest_offl%chem_n(1,k,1,n),                  &
1766                                                       fac_dt )
1767                   ENDDO
1768                   DO  i = nxl, nxr
1769                      chem_species(n)%conc(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1770                      ref_chem_l(nzb+1:nzt,n)                   = ref_chem_l(nzb+1:nzt,n) +        &
1771                                                                  chem_species(n)                  &
1772                                                                  %conc(nzb+1:nzt,j_bound,i)
1773                   ENDDO
1774                ENDIF
1775             ENDIF
1776          ENDDO
1777       ENDIF
1778    ENDIF
1779
1780    IF ( bc_dirichlet_s )  THEN
1781!
1782!--    v-component
1783       IF ( lod == 2 )  THEN
1784          DO  i = nxl, nxr
1785             DO  k = nzb+1, nzt
1786                v(k,j_bound_v,i) = interpolate_in_time( nest_offl%v_s(0,k,i),                      &
1787                                                        nest_offl%v_s(1,k,i),                      &
1788                                                        fac_dt ) *                                 &
1789                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1790                                          BTEST( wall_flags_total_0(k,j_bound_v,i), 2 ) )
1791             ENDDO
1792             v(:,j_bound_v-1,i) = v(:,j_bound_v,i)
1793             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
1794          ENDDO
1795       ELSE
1796          DO  k = nzb+1, nzt
1797             var_1d(k) = interpolate_in_time( nest_offl%v_s(0,k,1),                                &
1798                                              nest_offl%v_s(1,k,1),                                &
1799                                              fac_dt )
1800          ENDDO
1801          DO  i = nxl, nxr
1802             v(nzb+1:nzt,j_bound_v,i) = var_1d(nzb+1:nzt) *                                        &
1803                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1804                                             BTEST( wall_flags_total_0(nzb+1:nzt,j_bound_v,i), 2 ) )
1805             v(:,j_bound_v-1,i) = v(:,j_bound_v,i)
1806             v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
1807          ENDDO
1808       ENDIF
1809!
1810!--    w-component
1811       IF ( lod == 2 )  THEN
1812          DO  i = nxl, nxr
1813             DO  k = nzb+1, nzt-1
1814                w(k,j_bound,i) = interpolate_in_time( nest_offl%w_s(0,k,i),                        &
1815                                                      nest_offl%w_s(1,k,i),                        &
1816                                                      fac_dt ) *                                   &
1817                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1818                                        BTEST( wall_flags_total_0(k,j_bound,i), 3 ) )
1819             ENDDO
1820             w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
1821          ENDDO
1822       ELSE
1823          DO  k = nzb+1, nzt-1
1824             var_1d(k) = interpolate_in_time( nest_offl%w_s(0,k,1),                                &
1825                                              nest_offl%w_s(1,k,1),                                &
1826                                              fac_dt )
1827          ENDDO
1828          DO  i = nxl, nxr
1829             w(nzb+1:nzt-1,j_bound,i) = var_1d(nzb+1:nzt-1) *                                      &
1830                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1831                                             BTEST( wall_flags_total_0(nzb+1:nzt-1,j_bound,i), 3 ) )
1832             w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
1833          ENDDO
1834       ENDIF
1835!
1836!--    u-component
1837       IF ( lod == 2 )  THEN
1838          DO  i = nxlu, nxr
1839             DO  k = nzb+1, nzt
1840                u(k,j_bound,i) = interpolate_in_time( nest_offl%u_s(0,k,i),                        &
1841                                                      nest_offl%u_s(1,k,i),                        &
1842                                                      fac_dt ) *                                   &
1843                                 MERGE( 1.0_wp, 0.0_wp,                                            &
1844                                        BTEST( wall_flags_total_0(k,j_bound,i), 1 ) )
1845             ENDDO
1846             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
1847          ENDDO
1848       ELSE
1849          DO  k = nzb+1, nzt
1850             var_1d(k) = interpolate_in_time( nest_offl%u_s(0,k,1),                                &
1851                                              nest_offl%u_s(1,k,1),                                &
1852                                              fac_dt )
1853          ENDDO
1854          DO  i = nxlu, nxr
1855             u(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt) *                                          &
1856                                      MERGE( 1.0_wp, 0.0_wp,                                       &
1857                                             BTEST( wall_flags_total_0(nzb+1:nzt,j_bound,i), 1 ) )
1858             u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
1859          ENDDO
1860       ENDIF
1861!
1862!--    Potential temperature
1863       IF ( .NOT. neutral )  THEN
1864          IF ( lod == 2 )  THEN
1865             DO  i = nxl, nxr
1866                DO  k = nzb+1, nzt
1867                   pt(k,j_bound,i) = interpolate_in_time( nest_offl%pt_s(0,k,i),                   &
1868                                                          nest_offl%pt_s(1,k,i),                   &
1869                                                          fac_dt )
1870                ENDDO
1871                pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
1872             ENDDO
1873          ELSE
1874             DO  k = nzb+1, nzt
1875                var_1d(k) = interpolate_in_time( nest_offl%pt_s(0,k,1),                            &
1876                                                 nest_offl%pt_s(1,k,1),                            &
1877                                                 fac_dt )
1878             ENDDO
1879             DO  i = nxl, nxr
1880                pt(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1881                pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
1882             ENDDO
1883          ENDIF
1884       ENDIF
1885!
1886!--    Humidity
1887       IF ( humidity )  THEN
1888          IF ( lod == 2 )  THEN
1889             DO  i = nxl, nxr
1890                DO  k = nzb+1, nzt
1891                   q(k,j_bound,i) = interpolate_in_time( nest_offl%q_s(0,k,i),                     &
1892                                                         nest_offl%q_s(1,k,i),                     &
1893                                                         fac_dt )
1894                ENDDO
1895                q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
1896             ENDDO
1897          ELSE
1898             DO  k = nzb+1, nzt
1899                var_1d(k) = interpolate_in_time( nest_offl%q_s(0,k,1),                             &
1900                                                 nest_offl%q_s(1,k,1),                             &
1901                                                 fac_dt )
1902             ENDDO
1903             DO  i = nxl, nxr
1904                q(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1905                q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
1906             ENDDO
1907          ENDIF
1908       ENDIF
1909!
1910!--    Chemistry
1911       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
1912          DO  n = 1, UBOUND( chem_species, 1 )
1913             IF ( nest_offl%chem_from_file_s(n) )  THEN
1914                IF ( lod == 2 )  THEN
1915                   DO  i = nxl, nxr
1916                      DO  k = nzb+1, nzt
1917                         chem_species(n)%conc(k,j_bound,i) = interpolate_in_time(                  &
1918                                                                        nest_offl%chem_s(0,k,i,n), &
1919                                                                        nest_offl%chem_s(1,k,i,n), &
1920                                                                        fac_dt  )
1921                      ENDDO
1922                      ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                            &
1923                                                + chem_species(n)%conc(nzb+1:nzt,j_bound,i)
1924                   ENDDO
1925                ELSE
1926                   DO  k = nzb+1, nzt
1927                      var_1d(k) = interpolate_in_time( nest_offl%chem_s(0,k,1,n),                  &
1928                                                       nest_offl%chem_s(1,k,1,n),                  &
1929                                                       fac_dt )
1930                   ENDDO
1931                   DO  i = nxl, nxr
1932                      chem_species(n)%conc(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
1933                      ref_chem_l(nzb+1:nzt,n)                   = ref_chem_l(nzb+1:nzt,n) +        &
1934                                                                  chem_species(n)                  &
1935                                                                  %conc(nzb+1:nzt,j_bound,i)
1936                   ENDDO
1937                ENDIF
1938             ENDIF
1939          ENDDO
1940       ENDIF
1941    ENDIF
1942!
1943!-- Top boundary
1944!-- u-component
1945    IF ( lod == 2 )  THEN
1946       DO  i = nxlu, nxr
1947          DO  j = nys, nyn
1948             u(nzt+1,j,i) = interpolate_in_time( nest_offl%u_top(0,j,i),                           &
1949                                                 nest_offl%u_top(1,j,i),                           &
1950                                                 fac_dt ) *                                        &
1951                            MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt+1,j,i), 1 ) )
1952             u_ref_l(nzt+1) = u_ref_l(nzt+1) + u(nzt+1,j,i)
1953          ENDDO
1954       ENDDO
1955    ELSE
1956       var_1d(nzt+1) = interpolate_in_time( nest_offl%u_top(0,1,1),                                &
1957                                            nest_offl%u_top(1,1,1),                                &
1958                                            fac_dt )
1959       u(nzt+1,nys:nyn,nxlu:nxr) = var_1d(nzt+1) *                                                 &
1960                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1961                                          BTEST( wall_flags_total_0(nzt+1,nys:nyn,nxlu:nxr), 1 ) )
1962       u_ref_l(nzt+1) = u_ref_l(nzt+1) + SUM( u(nzt+1,nys:nyn,nxlu:nxr) )
1963    ENDIF
1964!
1965!--    For left boundary set boundary condition for u-component also at top grid point.
1966!--    Note, this has no effect on the numeric solution, only for data output.
1967    IF ( bc_dirichlet_l )  u(nzt+1,:,nxl) = u(nzt+1,:,nxlu)
1968!
1969!-- v-component
1970    IF ( lod == 2 )  THEN
1971       DO  i = nxl, nxr
1972          DO  j = nysv, nyn
1973             v(nzt+1,j,i) = interpolate_in_time( nest_offl%v_top(0,j,i),                           &
1974                                                 nest_offl%v_top(1,j,i),                           &
1975                                                 fac_dt ) *                                        &
1976                            MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt+1,j,i), 2 ) )
1977             v_ref_l(nzt+1) = v_ref_l(nzt+1) + v(nzt+1,j,i)
1978          ENDDO
1979       ENDDO
1980    ELSE
1981       var_1d(nzt+1) = interpolate_in_time( nest_offl%v_top(0,1,1),                                &
1982                                            nest_offl%v_top(1,1,1),                                &
1983                                            fac_dt )
1984       v(nzt+1,nysv:nyn,nxl:nxr) = var_1d(nzt+1) *                                                 &
1985                                   MERGE( 1.0_wp, 0.0_wp,                                          &
1986                                          BTEST( wall_flags_total_0(nzt+1,nysv:nyn,nxl:nxr), 2 ) )
1987       v_ref_l(nzt+1) = v_ref_l(nzt+1) + SUM( v(nzt+1,nysv:nyn,nxl:nxr) )
1988    ENDIF
1989!
1990!-- For south boundary set boundary condition for v-component also at top grid point.
1991!-- Note, this has no effect on the numeric solution, only for data output.
1992    IF ( bc_dirichlet_s )  v(nzt+1,nys,:) = v(nzt+1,nysv,:)
1993!
1994!-- w-component
1995    IF ( lod == 2 )  THEN
1996       DO  i = nxl, nxr
1997          DO  j = nys, nyn
1998             w(nzt,j,i) = interpolate_in_time( nest_offl%w_top(0,j,i),                             &
1999                                               nest_offl%w_top(1,j,i),                             &
2000                                               fac_dt ) *                                          &
2001                          MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt,j,i), 3 ) )
2002             w(nzt+1,j,i) = w(nzt,j,i)
2003          ENDDO
2004       ENDDO
2005    ELSE
2006       var_1d(nzt) = interpolate_in_time( nest_offl%w_top(0,1,1),                                  &
2007                                          nest_offl%w_top(1,1,1),                                  &
2008                                          fac_dt )
2009       w(nzt,nys:nyn,nxl:nxr) = var_1d(nzt) *                                                      &
2010                                MERGE( 1.0_wp, 0.0_wp,                                             &
2011                                       BTEST( wall_flags_total_0(nzt,nys:nyn,nxl:nxr), 3 ) )
2012       w(nzt+1,nys:nyn,nxl:nxr) = w(nzt,nys:nyn,nxl:nxr)
2013    ENDIF
2014!
2015!-- Potential temperture
2016    IF ( .NOT. neutral )  THEN
2017       IF ( lod == 2 )  THEN
2018          DO  i = nxl, nxr
2019             DO  j = nys, nyn
2020                pt(nzt+1,j,i) = interpolate_in_time( nest_offl%pt_top(0,j,i),                      &
2021                                                     nest_offl%pt_top(1,j,i),                      &
2022                                                     fac_dt )
2023                pt_ref_l(nzt+1) = pt_ref_l(nzt+1) + pt(nzt+1,j,i)
2024             ENDDO
2025          ENDDO
2026       ELSE
2027          var_1d(nzt+1) = interpolate_in_time( nest_offl%pt_top(0,1,1),                            &
2028                                               nest_offl%pt_top(1,1,1),                            &
2029                                               fac_dt )
2030          pt(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
2031          pt_ref_l(nzt+1) = pt_ref_l(nzt+1) + SUM( pt(nzt+1,nys:nyn,nxl:nxr) )
2032       ENDIF
2033    ENDIF
2034!
2035!--    humidity
2036    IF ( humidity )  THEN
2037       IF ( lod == 2 )  THEN
2038          DO  i = nxl, nxr
2039             DO  j = nys, nyn
2040                q(nzt+1,j,i) = interpolate_in_time( nest_offl%q_top(0,j,i),                        &
2041                                                    nest_offl%q_top(1,j,i),                        &
2042                                                    fac_dt )
2043                q_ref_l(nzt+1) = q_ref_l(nzt+1) + q(nzt+1,j,i)
2044             ENDDO
2045          ENDDO
2046       ELSE
2047          var_1d(nzt+1) = interpolate_in_time( nest_offl%q_top(0,1,1),                             &
2048                                               nest_offl%q_top(1,1,1),                             &
2049                                               fac_dt )
2050          q(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
2051          q_ref_l(nzt+1) = q_ref_l(nzt+1) + SUM( q(nzt+1,nys:nyn,nxl:nxr) )
2052       ENDIF
2053    ENDIF
2054
2055    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2056       DO  n = 1, UBOUND( chem_species, 1 )
2057          IF ( nest_offl%chem_from_file_t(n) )  THEN
2058             IF ( lod == 2 )  THEN
2059                DO  i = nxl, nxr
2060                   DO  j = nys, nyn
2061                      chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time(                       &
2062                                                           nest_offl%chem_top(0,j,i,n),            &
2063                                                           nest_offl%chem_top(1,j,i,n),            &
2064                                                           fac_dt          )
2065                      ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) + chem_species(n)%conc(nzt+1,j,i)
2066                   ENDDO
2067                ENDDO
2068             ELSE
2069                var_1d(nzt+1) = interpolate_in_time( nest_offl%chem_top(0,1,1,n),                  &
2070                                                     nest_offl%chem_top(1,1,1,n),                  &
2071                                                     fac_dt )
2072                chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
2073                ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) +                                        &
2074                                      SUM( chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) )
2075             ENDIF
2076          ENDIF
2077       ENDDO
2078    ENDIF
2079!
2080!-- Moreover, set Neumann boundary condition for subgrid-scale TKE, passive scalar, dissipation, and
2081!-- chemical species if required.
2082    IF ( rans_mode  .AND.  rans_tke_e )  THEN
2083       IF (  bc_dirichlet_l )  diss(:,:,nxl-1) = diss(:,:,nxl)
2084       IF (  bc_dirichlet_r )  diss(:,:,nxr+1) = diss(:,:,nxr)
2085       IF (  bc_dirichlet_s )  diss(:,nys-1,:) = diss(:,nys,:)
2086       IF (  bc_dirichlet_n )  diss(:,nyn+1,:) = diss(:,nyn,:)
2087    ENDIF
2088!        IF ( .NOT. constant_diffusion )  THEN
2089!           IF (  bc_dirichlet_l )  e(:,:,nxl-1) = e(:,:,nxl)
2090!           IF (  bc_dirichlet_r )  e(:,:,nxr+1) = e(:,:,nxr)
2091!           IF (  bc_dirichlet_s )  e(:,nys-1,:) = e(:,nys,:)
2092!           IF (  bc_dirichlet_n )  e(:,nyn+1,:) = e(:,nyn,:)
2093!           e(nzt+1,:,:) = e(nzt,:,:)
2094!        ENDIF
2095!        IF ( passive_scalar )  THEN
2096!           IF (  bc_dirichlet_l )  s(:,:,nxl-1) = s(:,:,nxl)
2097!           IF (  bc_dirichlet_r )  s(:,:,nxr+1) = s(:,:,nxr)
2098!           IF (  bc_dirichlet_s )  s(:,nys-1,:) = s(:,nys,:)
2099!           IF (  bc_dirichlet_n )  s(:,nyn+1,:) = s(:,nyn,:)
2100!        ENDIF
2101
2102    CALL exchange_horiz( u, nbgp )
2103    CALL exchange_horiz( v, nbgp )
2104    CALL exchange_horiz( w, nbgp )
2105    IF ( .NOT. neutral )  CALL exchange_horiz( pt, nbgp )
2106    IF ( humidity      )  CALL exchange_horiz( q,  nbgp )
2107    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2108       DO  n = 1, UBOUND( chem_species, 1 )
2109!
2110!--       Do local exchange only when necessary, i.e. when data is coming from dynamic file.
2111          IF ( nest_offl%chem_from_file_t(n) )  CALL exchange_horiz( chem_species(n)%conc, nbgp )
2112       ENDDO
2113    ENDIF
2114!
2115!-- Set top boundary condition at all horizontal grid points, also at the lateral boundary grid
2116!-- points.
2117    w(nzt+1,:,:) = w(nzt,:,:)
2118!
2119!-- Offline nesting for salsa
2120    IF ( salsa )  CALL salsa_nesting_offl_bc
2121!
2122!-- Calculate the mean profiles. These are later stored on u_init, v_init, etc., in order to adjust
2123!-- the Rayleigh damping under time-evolving atmospheric conditions accordingly - damping against
2124!-- the representative mean profiles, not against the initial profiles. Note, in LOD = 1 case no
2125!-- averaging is required.
2126#if defined( __parallel )
2127    CALL MPI_ALLREDUCE( u_ref_l, u_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
2128    CALL MPI_ALLREDUCE( v_ref_l, v_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
2129    IF ( humidity )  THEN
2130       CALL MPI_ALLREDUCE( q_ref_l, q_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
2131    ENDIF
2132    IF ( .NOT. neutral )  THEN
2133       CALL MPI_ALLREDUCE( pt_ref_l, pt_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
2134    ENDIF
2135    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2136       CALL MPI_ALLREDUCE( ref_chem_l, ref_chem, ( nzt+1-nzb+1 ) * SIZE( ref_chem(nzb,:) ),        &
2137                           MPI_REAL, MPI_SUM, comm2d, ierr )
2138    ENDIF
2139#else
2140    u_ref  = u_ref_l
2141    v_ref  = v_ref_l
2142    IF ( humidity )       q_ref    = q_ref_l
2143    IF ( .NOT. neutral )  pt_ref   = pt_ref_l
2144    IF ( air_chemistry  .AND.  nesting_offline_chem )  ref_chem = ref_chem_l
2145#endif
2146!
2147!-- Average data. Note, reference profiles up to nzt are derived from lateral boundaries, at the
2148!-- model top it is derived from the top boundary. Thus, number of input data is different from
2149!-- nzb:nzt compared to nzt+1.
2150!-- Derived from lateral boundaries.
2151    u_ref(nzb:nzt) = u_ref(nzb:nzt) / REAL( 2.0_wp * ( ny + 1 + nx     ), KIND = wp )
2152    v_ref(nzb:nzt) = v_ref(nzb:nzt) / REAL( 2.0_wp * ( ny   + nx + 1   ), KIND = wp )
2153    IF ( humidity )                                                                                &
2154       q_ref(nzb:nzt) = q_ref(nzb:nzt)   / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
2155    IF ( .NOT. neutral )                                                                           &
2156       pt_ref(nzb:nzt) = pt_ref(nzb:nzt) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
2157    IF ( air_chemistry  .AND.  nesting_offline_chem )                                              &
2158       ref_chem(nzb:nzt,:) = ref_chem(nzb:nzt,:) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
2159!
2160!-- Derived from top boundary.
2161    u_ref(nzt+1) = u_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx     ), KIND = wp )
2162    v_ref(nzt+1) = v_ref(nzt+1) / REAL( ( ny     ) * ( nx + 1 ), KIND = wp )
2163    IF ( humidity )                                                                                &
2164       q_ref(nzt+1) = q_ref(nzt+1)   / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
2165    IF ( .NOT. neutral )                                                                           &
2166       pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
2167    IF ( air_chemistry  .AND.  nesting_offline_chem )                                              &
2168       ref_chem(nzt+1,:) = ref_chem(nzt+1,:) / REAL( ( ny + 1 ) * ( nx + 1 ),KIND = wp )
2169!
2170!-- Write onto init profiles, which are used for damping. Also set lower boundary condition for
2171!-- scalars (not required for u and v as these are zero at k=nzb).
2172    u_init = u_ref
2173    v_init = v_ref
2174    IF ( humidity      )  THEN
2175       q_init      = q_ref
2176       q_init(nzb) = q_init(nzb+1)
2177    ENDIF
2178    IF ( .NOT. neutral )  THEN
2179       pt_init      = pt_ref
2180       pt_init(nzb) = pt_init(nzb+1)
2181    ENDIF
2182
2183    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2184       DO  n = 1, UBOUND( chem_species, 1 )
2185          IF ( nest_offl%chem_from_file_t(n) )  THEN
2186             chem_species(n)%conc_pr_init(:)   = ref_chem(:,n)
2187             chem_species(n)%conc_pr_init(nzb) = chem_species(n)%conc_pr_init(nzb+1)
2188          ENDIF
2189       ENDDO
2190    ENDIF
2191    IF ( ALLOCATED( ref_chem   ) )  DEALLOCATE( ref_chem   )
2192    IF ( ALLOCATED( ref_chem_l ) )  DEALLOCATE( ref_chem_l )
2193!
2194!-- Further, adjust Rayleigh damping height in case of time-changing conditions.
2195!-- Therefore, calculate boundary-layer depth first.
2196    CALL nesting_offl_calc_zi
2197    CALL adjust_sponge_layer
2198
2199    CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
2200
2201    IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'end' )
2202
2203
2204 END SUBROUTINE nesting_offl_bc
2205
2206!--------------------------------------------------------------------------------------------------!
2207! Description:
2208!--------------------------------------------------------------------------------------------------!
2209!>  Update of the geostrophic wind components. Note, currently this routine is not invoked.
2210!--------------------------------------------------------------------------------------------------!
2211 SUBROUTINE nesting_offl_geostrophic_wind
2212
2213    INTEGER(iwp) ::  k
2214!
2215!--    Update geostrophic wind components from dynamic input file.
2216    DO  k = nzb+1, nzt
2217       ug(k) = interpolate_in_time( nest_offl%ug(0,k), nest_offl%ug(1,k), fac_dt )
2218       vg(k) = interpolate_in_time( nest_offl%vg(0,k), nest_offl%vg(1,k), fac_dt )
2219    ENDDO
2220    ug(nzt+1) = ug(nzt)
2221    vg(nzt+1) = vg(nzt)
2222
2223 END SUBROUTINE nesting_offl_geostrophic_wind
2224
2225!--------------------------------------------------------------------------------------------------!
2226! Description:
2227!--------------------------------------------------------------------------------------------------!
2228!>  Determine the interpolation constant for time interpolation. The calculation is separated from
2229!>  the nesting_offl_bc and nesting_offl_geostrophic_wind in order to be independent on the order of
2230!> calls.
2231!--------------------------------------------------------------------------------------------------!
2232 SUBROUTINE nesting_offl_interpolation_factor
2233!
2234!-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed
2235!-- time(tind_p) before boundary data is updated again.
2236    fac_dt = ( time_since_reference_point - nest_offl%time(nest_offl%tind) + dt_3d ) /             &
2237             ( nest_offl%time(nest_offl%tind_p) - nest_offl%time(nest_offl%tind) )
2238
2239    fac_dt = MIN( 1.0_wp, fac_dt )
2240
2241 END SUBROUTINE nesting_offl_interpolation_factor
2242
2243!--------------------------------------------------------------------------------------------------!
2244! Description:
2245!--------------------------------------------------------------------------------------------------!
2246!> Calculates the boundary-layer depth from the boundary data, according to bulk-Richardson
2247!> criterion.
2248!--------------------------------------------------------------------------------------------------!
2249 SUBROUTINE nesting_offl_calc_zi
2250
2251    INTEGER(iwp) :: i                             !< loop index in x-direction
2252    INTEGER(iwp) :: j                             !< loop index in y-direction
2253    INTEGER(iwp) :: k                             !< loop index in z-direction
2254    INTEGER(iwp) :: k_max_loc                     !< index of maximum wind speed along z-direction
2255    INTEGER(iwp) :: k_surface                     !< topography top index in z-direction
2256    INTEGER(iwp) :: num_boundary_gp_non_cyclic    !< number of non-cyclic boundaries, used for averaging ABL depth
2257    INTEGER(iwp) :: num_boundary_gp_non_cyclic_l  !< number of non-cyclic boundaries, used for averaging ABL depth
2258
2259    REAL(wp) ::  ri_bulk                 !< bulk Richardson number
2260    REAL(wp) ::  ri_bulk_crit = 0.25_wp  !< critical bulk Richardson number
2261    REAL(wp) ::  topo_max                !< maximum topography level in model domain
2262    REAL(wp) ::  topo_max_l              !< maximum topography level in subdomain
2263    REAL(wp) ::  vpt_surface             !< near-surface virtual potential temperature
2264    REAL(wp) ::  zi_l                    !< mean boundary-layer depth on subdomain
2265    REAL(wp) ::  zi_local                !< local boundary-layer depth
2266
2267    REAL(wp), DIMENSION(nzb:nzt+1) ::  vpt_col  !< vertical profile of virtual potential temperature at (j,i)-grid point
2268    REAL(wp), DIMENSION(nzb:nzt+1) ::  uv_abs   !< vertical profile of horizontal wind speed at (j,i)-grid point
2269
2270
2271!
2272!-- Calculate mean boundary-layer height from boundary data.
2273!-- Start with the left and right boundaries.
2274    zi_l      = 0.0_wp
2275    num_boundary_gp_non_cyclic_l = 0
2276    IF ( bc_dirichlet_l  .OR.  bc_dirichlet_r )  THEN
2277!
2278!--    Sum-up and store number of boundary grid points used for averaging ABL depth
2279       num_boundary_gp_non_cyclic_l = num_boundary_gp_non_cyclic_l + nxr - nxl + 1
2280!
2281!--    Determine index along x. Please note, index indicates boundary grid point for scalars.
2282       i = MERGE( -1, nxr + 1, bc_dirichlet_l )
2283
2284       DO  j = nys, nyn
2285!
2286!--       Determine topography top index at current (j,i) index
2287          k_surface = topo_top_ind(j,i,0)
2288!
2289!--       Pre-compute surface virtual temperature. Therefore, use 2nd prognostic level according to
2290!--       Heinze et al. (2017).
2291          IF ( humidity )  THEN
2292             vpt_surface = pt(k_surface+2,j,i) * ( 1.0_wp + 0.61_wp * q(k_surface+2,j,i) )
2293             vpt_col     = pt(:,j,i) * ( 1.0_wp + 0.61_wp * q(:,j,i) )
2294          ELSE
2295             vpt_surface = pt(k_surface+2,j,i)
2296             vpt_col     = pt(:,j,i)
2297          ENDIF
2298!
2299!--       Calculate local boundary layer height from bulk Richardson number, i.e. the height where
2300!--       the bulk Richardson number exceeds its critical value of 0.25
2301!--       (according to Heinze et al., 2017).
2302!--       Note, no interpolation of u- and v-component is made, as both are mainly mean inflow
2303!--       profiles with very small spatial variation.
2304!--       Add a safety factor in case the velocity term becomes zero. This may happen if overhanging
2305!--       3D structures are directly located at the boundary, where velocity inside the building is
2306!--       zero (k_surface is the index of the lowest upward-facing surface).
2307          uv_abs(:) = SQRT( MERGE( u(:,j,i+1), u(:,j,i), bc_dirichlet_l )**2 + v(:,j,i)**2 )
2308!
2309!--       Determine index of the maximum wind speed
2310          k_max_loc = MAXLOC( uv_abs(:), DIM = 1 ) - 1
2311
2312          zi_local = 0.0_wp
2313          DO  k = k_surface+1, nzt
2314             ri_bulk = zu(k) * g / vpt_surface *                                                   &
2315                       ( vpt_col(k) - vpt_surface ) / ( uv_abs(k) + 1E-5_wp )
2316!
2317!--          Check if critical Richardson number is exceeded. Further, check if there is a maxium in
2318!--          the wind profile in order to detect also ABL heights in the stable boundary layer.
2319             IF ( zi_local == 0.0_wp  .AND.  ( ri_bulk > ri_bulk_crit .OR. k == k_max_loc ) )      &
2320                zi_local = zu(k)
2321          ENDDO
2322!
2323!--       Assure that the minimum local boundary-layer depth is at least at the second vertical grid
2324!--       level.
2325          zi_l = zi_l + MAX( zi_local, zu(k_surface+2) )
2326
2327       ENDDO
2328
2329    ENDIF
2330!
2331!-- Do the same at the north and south boundaries.
2332    IF ( bc_dirichlet_s  .OR.  bc_dirichlet_n )  THEN
2333
2334       num_boundary_gp_non_cyclic_l = num_boundary_gp_non_cyclic_l + nxr - nxl + 1
2335
2336       j = MERGE( -1, nyn + 1, bc_dirichlet_s )
2337
2338       DO  i = nxl, nxr
2339          k_surface = topo_top_ind(j,i,0)
2340
2341          IF ( humidity )  THEN
2342             vpt_surface = pt(k_surface+2,j,i) * ( 1.0_wp + 0.61_wp * q(k_surface+2,j,i) )
2343             vpt_col     = pt(:,j,i) * ( 1.0_wp + 0.61_wp * q(:,j,i) )
2344          ELSE
2345             vpt_surface = pt(k_surface+2,j,i)
2346             vpt_col  = pt(:,j,i)
2347          ENDIF
2348
2349          uv_abs(:) = SQRT( u(:,j,i)**2 + MERGE( v(:,j+1,i), v(:,j,i), bc_dirichlet_s )**2 )
2350!
2351!--       Determine index of the maximum wind speed
2352          k_max_loc = MAXLOC( uv_abs(:), DIM = 1 ) - 1
2353
2354          zi_local = 0.0_wp
2355          DO  k = k_surface+1, nzt
2356             ri_bulk = zu(k) * g / vpt_surface *                                                   &
2357                       ( vpt_col(k) - vpt_surface ) / ( uv_abs(k) + 1E-5_wp )
2358!
2359!--          Check if critical Richardson number is exceeded. Further, check if there is a maxium in
2360!--          the wind profile in order to detect also ABL heights in the stable boundary layer.
2361             IF ( zi_local == 0.0_wp  .AND.  ( ri_bulk > ri_bulk_crit .OR. k == k_max_loc ) )      &
2362                zi_local = zu(k)
2363          ENDDO
2364          zi_l = zi_l + MAX( zi_local, zu(k_surface+2) )
2365
2366       ENDDO
2367
2368    ENDIF
2369
2370#if defined( __parallel )
2371    CALL MPI_ALLREDUCE( zi_l, zi_ribulk, 1, MPI_REAL, MPI_SUM, comm2d, ierr )
2372    CALL MPI_ALLREDUCE( num_boundary_gp_non_cyclic_l, num_boundary_gp_non_cyclic,                  &
2373                        1, MPI_INTEGER, MPI_SUM, comm2d, ierr )
2374#else
2375    zi_ribulk = zi_l
2376    num_boundary_gp_non_cyclic = num_boundary_gp_non_cyclic_l
2377#endif
2378    zi_ribulk = zi_ribulk / REAL( num_boundary_gp_non_cyclic, KIND = wp )
2379!
2380!-- Finally, check if boundary layer depth is not below the any topography.
2381!-- zi_ribulk will be used to adjust rayleigh damping height, i.e. the lower level of the sponge
2382!-- layer, as well as to adjust the synthetic turbulence generator accordingly. If Rayleigh damping
2383!-- would be applied near buildings, etc., this would spoil the simulation results.
2384    topo_max_l = zw(MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ))
2385
2386#if defined( __parallel )
2387    CALL MPI_ALLREDUCE( topo_max_l, topo_max, 1, MPI_REAL, MPI_MAX, comm2d, ierr )
2388#else
2389    topo_max     = topo_max_l
2390#endif
2391!        zi_ribulk = MAX( zi_ribulk, topo_max )
2392
2393 END SUBROUTINE nesting_offl_calc_zi
2394
2395
2396!--------------------------------------------------------------------------------------------------!
2397! Description:
2398!--------------------------------------------------------------------------------------------------!
2399!> Adjust the height where the rayleigh damping starts, i.e. the lower level of the sponge layer.
2400!--------------------------------------------------------------------------------------------------!
2401 SUBROUTINE adjust_sponge_layer
2402
2403    INTEGER(iwp) :: k   !< loop index in z-direction
2404
2405    REAL(wp) ::  rdh    !< updated Rayleigh damping height
2406
2407
2408    IF ( rayleigh_damping_height > 0.0_wp  .AND.  rayleigh_damping_factor > 0.0_wp )  THEN
2409!
2410!--    Update Rayleigh-damping height and re-calculate height-depending damping coefficients.
2411!--    Assure that rayleigh damping starts well above the boundary layer.
2412       rdh = MIN( MAX( zi_ribulk * 1.3_wp, 10.0_wp * dz(1) ),                                      &
2413                  0.8_wp * zu(nzt), rayleigh_damping_height )
2414!
2415!--       Update Rayleigh damping factor
2416       DO  k = nzb+1, nzt
2417          IF ( zu(k) >= rdh )  THEN
2418             rdf(k) = rayleigh_damping_factor *                                                    &
2419                      ( SIN( pi * 0.5_wp * ( zu(k) - rdh ) / ( zu(nzt) - rdh ) ) )**2
2420          ENDIF
2421       ENDDO
2422       rdf_sc = rdf
2423
2424    ENDIF
2425
2426 END SUBROUTINE adjust_sponge_layer
2427
2428!--------------------------------------------------------------------------------------------------!
2429! Description:
2430! ------------
2431!> Performs consistency checks
2432!--------------------------------------------------------------------------------------------------!
2433 SUBROUTINE nesting_offl_check_parameters
2434!
2435!-- Check if offline nesting is applied in nested child domain.
2436    IF ( nesting_offline  .AND.  child_domain )  THEN
2437       message_string = 'Offline nesting is only applicable in root model.'
2438       CALL message( 'offline_nesting_check_parameters', 'PA0622', 1, 2, 0, 6, 0 )
2439    ENDIF
2440
2441 END SUBROUTINE nesting_offl_check_parameters
2442
2443!--------------------------------------------------------------------------------------------------!
2444! Description:
2445! ------------
2446!> Reads the parameter list nesting_offl_parameters
2447!--------------------------------------------------------------------------------------------------!
2448 SUBROUTINE nesting_offl_parin
2449
2450    CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
2451
2452
2453    NAMELIST /nesting_offl_parameters/   nesting_offline
2454
2455    line = ' '
2456
2457!
2458!-- Try to find stg package
2459    REWIND ( 11 )
2460    line = ' '
2461    DO WHILE ( INDEX( line, '&nesting_offl_parameters' ) == 0 )
2462       READ ( 11, '(A)', END=20 )  line
2463    ENDDO
2464    BACKSPACE ( 11 )
2465
2466!
2467!-- Read namelist
2468    READ ( 11, nesting_offl_parameters, ERR = 10, END = 20 )
2469
2470    GOTO 20
2471
247210    BACKSPACE( 11 )
2473    READ( 11 , '(A)') line
2474    CALL parin_fail_message( 'nesting_offl_parameters', line )
2475
247620    CONTINUE
2477
2478
2479 END SUBROUTINE nesting_offl_parin
2480
2481!--------------------------------------------------------------------------------------------------!
2482! Description:
2483! ------------
2484!> Writes information about offline nesting into HEADER file
2485!--------------------------------------------------------------------------------------------------!
2486 SUBROUTINE nesting_offl_header ( io )
2487
2488    INTEGER(iwp), INTENT(IN) ::  io  !< Unit of the output file
2489
2490    WRITE ( io, 1 )
2491    IF ( nesting_offline )  THEN
2492       WRITE ( io, 3 )
2493    ELSE
2494       WRITE ( io, 2 )
2495    ENDIF
2496
24971 FORMAT (//' Offline nesting in COSMO model:'/' -------------------------------'/)
24982 FORMAT (' --> No offlince nesting is used (default) ')
24993 FORMAT (' --> Offlince nesting is used. Boundary data is read from dynamic input file ')
2500
2501 END SUBROUTINE nesting_offl_header
2502
2503!--------------------------------------------------------------------------------------------------!
2504! Description:
2505! ------------
2506!> Allocate arrays used to read boundary data from NetCDF file and initialize boundary data.
2507!--------------------------------------------------------------------------------------------------!
2508 SUBROUTINE nesting_offl_init
2509
2510    INTEGER(iwp) ::  i   !< loop index for x-direction
2511    INTEGER(iwp) ::  j   !< loop index for y-direction
2512    INTEGER(iwp) ::  n   !< running index for chemical species
2513
2514!
2515!-- Before arrays for the boundary data are allocated, the LOD of the dynamic input data at the
2516!-- boundaries is read.
2517#if defined ( __netcdf )
2518!
2519!-- Open file in read-only mode
2520    CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), pids_id )
2521!
2522!-- Read attributes for LOD. In order to gurantee that also older drivers, where attribute is not
2523!-- given, are working, do not abort the run but assume LOD2 forcing.
2524    CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_pt,  .FALSE., 'ls_forcing_left_pt', .FALSE. )
2525    CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_qv,  .FALSE., 'ls_forcing_left_qv', .FALSE. )
2526    CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_u,   .FALSE., 'ls_forcing_left_u',  .FALSE. )
2527    CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_v,   .FALSE., 'ls_forcing_left_v',  .FALSE. )
2528    CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_w,   .FALSE., 'ls_forcing_left_w',  .FALSE. )
2529
2530    CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_pt, .FALSE., 'ls_forcing_north_pt', .FALSE. )
2531    CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_qv, .FALSE., 'ls_forcing_north_qv', .FALSE. )
2532    CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_u,  .FALSE., 'ls_forcing_north_u',  .FALSE. )
2533    CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_v,  .FALSE., 'ls_forcing_north_v',  .FALSE. )
2534    CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_w,  .FALSE., 'ls_forcing_north_w',  .FALSE. )
2535
2536    CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_pt, .FALSE., 'ls_forcing_south_pt', .FALSE. )
2537    CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_qv, .FALSE., 'ls_forcing_south_qv', .FALSE. )
2538    CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_u,  .FALSE., 'ls_forcing_south_u',  .FALSE. )
2539    CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_v,  .FALSE., 'ls_forcing_south_v',  .FALSE. )
2540    CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_w,  .FALSE., 'ls_forcing_south_w',  .FALSE. )
2541
2542    CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_pt,  .FALSE., 'ls_forcing_right_pt', .FALSE. )
2543    CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_qv,  .FALSE., 'ls_forcing_right_qv', .FALSE. )
2544    CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_u,   .FALSE., 'ls_forcing_right_u',  .FALSE. )
2545    CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_v,   .FALSE., 'ls_forcing_right_v',  .FALSE. )
2546    CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_w,   .FALSE., 'ls_forcing_right_w',  .FALSE. )
2547
2548    CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_pt,   .FALSE., 'ls_forcing_top_pt', .FALSE. )
2549    CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_qv,   .FALSE., 'ls_forcing_top_qv', .FALSE. )
2550    CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_u,    .FALSE., 'ls_forcing_top_u',  .FALSE. )
2551    CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_v,    .FALSE., 'ls_forcing_top_v',  .FALSE. )
2552    CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_w,    .FALSE., 'ls_forcing_top_w',  .FALSE. )
2553
2554    CALL close_input_file( pids_id )
2555#endif
2556!
2557!-- Temporary workaround until most of the dynamic drivers contain a LOD attribute. So far INIFOR
2558!-- did not provide the LOD attribute. In order to still use these older dynamic drivers, provide a
2559!-- temporary workaround. If the LOD is not given, a NetCDF interal error will occur but the
2560!-- simulation will not be aborted since the no_abort flag is passed. However, the respective
2561!-- attribute value might be given an arbitrary number. Hence, check for valid LOD's and manually
2562!-- set them to LOD 2 (as assumed so far). Note, this workaround should be removed later (date of
2563!-- reference: 6. Oct. 2020).
2564    IF ( nest_offl%lod_east_pt /= 1  .AND.  nest_offl%lod_east_pt /= 2 )  nest_offl%lod_east_pt = 2
2565    IF ( nest_offl%lod_east_qv /= 1  .AND.  nest_offl%lod_east_qv /= 2 )  nest_offl%lod_east_qv = 2
2566    IF ( nest_offl%lod_east_u  /= 1  .AND.  nest_offl%lod_east_u  /= 2 )  nest_offl%lod_east_u  = 2
2567    IF ( nest_offl%lod_east_v  /= 1  .AND.  nest_offl%lod_east_v  /= 2 )  nest_offl%lod_east_v  = 2
2568    IF ( nest_offl%lod_east_w  /= 1  .AND.  nest_offl%lod_east_w  /= 2 )  nest_offl%lod_east_w  = 2
2569
2570    IF ( nest_offl%lod_north_pt /= 1  .AND.  nest_offl%lod_north_pt /= 2 )  nest_offl%lod_north_pt = 2
2571    IF ( nest_offl%lod_north_qv /= 1  .AND.  nest_offl%lod_north_qv /= 2 )  nest_offl%lod_north_qv = 2
2572    IF ( nest_offl%lod_north_u  /= 1  .AND.  nest_offl%lod_north_u  /= 2 )  nest_offl%lod_north_u  = 2
2573    IF ( nest_offl%lod_north_v  /= 1  .AND.  nest_offl%lod_north_v  /= 2 )  nest_offl%lod_north_v  = 2
2574    IF ( nest_offl%lod_north_w  /= 1  .AND.  nest_offl%lod_north_w  /= 2 )  nest_offl%lod_north_w  = 2
2575
2576    IF ( nest_offl%lod_south_pt /= 1  .AND.  nest_offl%lod_south_pt /= 2 )  nest_offl%lod_south_pt = 2
2577    IF ( nest_offl%lod_south_qv /= 1  .AND.  nest_offl%lod_south_qv /= 2 )  nest_offl%lod_south_qv = 2
2578    IF ( nest_offl%lod_south_u  /= 1  .AND.  nest_offl%lod_south_u  /= 2 )  nest_offl%lod_south_u  = 2
2579    IF ( nest_offl%lod_south_v  /= 1  .AND.  nest_offl%lod_south_v  /= 2 )  nest_offl%lod_south_v  = 2
2580    IF ( nest_offl%lod_south_w  /= 1  .AND.  nest_offl%lod_south_w  /= 2 )  nest_offl%lod_south_w  = 2
2581
2582    IF ( nest_offl%lod_west_pt /= 1  .AND.  nest_offl%lod_west_pt /= 2 )  nest_offl%lod_west_pt = 2
2583    IF ( nest_offl%lod_west_qv /= 1  .AND.  nest_offl%lod_west_qv /= 2 )  nest_offl%lod_west_qv = 2
2584    IF ( nest_offl%lod_west_u  /= 1  .AND.  nest_offl%lod_west_u  /= 2 )  nest_offl%lod_west_u  = 2
2585    IF ( nest_offl%lod_west_v  /= 1  .AND.  nest_offl%lod_west_v  /= 2 )  nest_offl%lod_west_v  = 2
2586    IF ( nest_offl%lod_west_w  /= 1  .AND.  nest_offl%lod_west_w  /= 2 )  nest_offl%lod_west_w  = 2
2587
2588    IF ( nest_offl%lod_top_pt /= 1  .AND.  nest_offl%lod_top_pt /= 2 )  nest_offl%lod_top_pt = 2
2589    IF ( nest_offl%lod_top_qv /= 1  .AND.  nest_offl%lod_top_qv /= 2 )  nest_offl%lod_top_qv = 2
2590    IF ( nest_offl%lod_top_u  /= 1  .AND.  nest_offl%lod_top_u  /= 2 )  nest_offl%lod_top_u  = 2
2591    IF ( nest_offl%lod_top_v  /= 1  .AND.  nest_offl%lod_top_v  /= 2 )  nest_offl%lod_top_v  = 2
2592    IF ( nest_offl%lod_top_w  /= 1  .AND.  nest_offl%lod_top_w  /= 2 )  nest_offl%lod_top_w  = 2
2593!
2594!-- For consistency, check if all boundary input variables have the same LOD.
2595    IF ( MAX( nest_offl%lod_east_pt,  nest_offl%lod_east_qv,  nest_offl%lod_east_u,                &
2596              nest_offl%lod_east_v,   nest_offl%lod_east_w,                                        &
2597              nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,               &
2598              nest_offl%lod_north_v,  nest_offl%lod_north_w,                                       &
2599              nest_offl%lod_south_pt, nest_offl%lod_south_qv, nest_offl%lod_south_u,               &
2600              nest_offl%lod_south_v,  nest_offl%lod_south_w,                                       &
2601              nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,               &
2602              nest_offl%lod_north_v,  nest_offl%lod_north_w,                                       &
2603              nest_offl%lod_top_pt,   nest_offl%lod_top_qv,   nest_offl%lod_top_u,                 &
2604              nest_offl%lod_top_v,    nest_offl%lod_top_w )                                        &
2605            /=                                                                                     &
2606         MIN( nest_offl%lod_east_pt,  nest_offl%lod_east_qv,  nest_offl%lod_east_u,                &
2607              nest_offl%lod_east_v,   nest_offl%lod_east_w,                                        &
2608              nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,               &
2609              nest_offl%lod_north_v,  nest_offl%lod_north_w,                                       &
2610              nest_offl%lod_south_pt, nest_offl%lod_south_qv, nest_offl%lod_south_u,               &
2611              nest_offl%lod_south_v,  nest_offl%lod_south_w,                                       &
2612              nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,               &
2613              nest_offl%lod_north_v,  nest_offl%lod_north_w,                                       &
2614              nest_offl%lod_top_pt,   nest_offl%lod_top_qv,   nest_offl%lod_top_u,                 &
2615              nest_offl%lod_top_v,    nest_offl%lod_top_w ) )  THEN
2616       message_string = 'A mixture of different LOD for the provided boundary data is not ' //     &
2617                        'possible.'
2618       CALL message( 'nesting_offl_init', 'PA0504', 1, 2, 0, 6, 0 )
2619    ENDIF
2620!
2621!-- As all LODs are the same, store it.
2622    lod = nest_offl%lod_east_u
2623!
2624!-- Allocate arrays for geostrophic wind components. Arrays will incorporate 2 time levels in order
2625!-- to interpolate in between.
2626    ALLOCATE( nest_offl%ug(0:1,1:nzt) )
2627    ALLOCATE( nest_offl%vg(0:1,1:nzt) )
2628!
2629!-- Set index range according to the given LOD in order to allocate the input arrays.
2630    IF ( bc_dirichlet_l  .OR.  bc_dirichlet_r  )  THEN
2631       IF ( lod == 2 )  THEN
2632          j_start   = nys
2633          j_start_v = nysv
2634          j_end     = nyn
2635       ELSE
2636          j_start   = 1
2637          j_start_v = 1
2638          j_end     = 1
2639       ENDIF
2640    ENDIF
2641
2642    IF ( bc_dirichlet_n  .OR.  bc_dirichlet_s )  THEN
2643       IF( lod == 2 )  THEN
2644          i_start   = nxl
2645          i_start_u = nxlu
2646          i_end     = nxr
2647       ELSE
2648          i_start   = 1
2649          i_start_u = 1
2650          i_end     = 1
2651       ENDIF
2652    ENDIF
2653!
2654!-- Allocate arrays for reading left/right boundary values. Arrays will incorporate 2 time levels in
2655!-- order to interpolate in between. Depending on the given LOD, the x-, or y-dimension will be
2656!-- either nxl:nxr, or nys:nyn (for LOD=2), or it reduces to one element for LOD=1. If the core has
2657!-- no lateral boundary, allocate a dummy array as well, in order to enable netcdf parallel access.
2658!-- Dummy arrays will be allocated with dimension length zero.
2659    IF ( bc_dirichlet_l )  THEN
2660       ALLOCATE( nest_offl%u_l(0:1,nzb+1:nzt,j_start:j_end)  )
2661       ALLOCATE( nest_offl%v_l(0:1,nzb+1:nzt,j_start_v:j_end) )
2662       ALLOCATE( nest_offl%w_l(0:1,nzb+1:nzt-1,j_start:j_end) )
2663       IF ( humidity )       ALLOCATE( nest_offl%q_l(0:1,nzb+1:nzt,j_start:j_end)  )
2664       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_l(0:1,nzb+1:nzt,j_start:j_end) )
2665       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2666          ALLOCATE( nest_offl%chem_l(0:1,nzb+1:nzt,j_start:j_end,1:UBOUND( chem_species, 1 )) )
2667    ELSE
2668       ALLOCATE( nest_offl%u_l(1:1,1:1,1:1)  )
2669       ALLOCATE( nest_offl%v_l(1:1,1:1,1:1)  )
2670       ALLOCATE( nest_offl%w_l(1:1,1:1,1:1)  )
2671       IF ( humidity )       ALLOCATE( nest_offl%q_l(1:1,1:1,1:1)  )
2672       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_l(1:1,1:1,1:1)  )
2673       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2674          ALLOCATE( nest_offl%chem_l(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
2675    ENDIF
2676    IF ( bc_dirichlet_r )  THEN
2677       ALLOCATE( nest_offl%u_r(0:1,nzb+1:nzt,j_start:j_end)  )
2678       ALLOCATE( nest_offl%v_r(0:1,nzb+1:nzt,j_start_v:j_end) )
2679       ALLOCATE( nest_offl%w_r(0:1,nzb+1:nzt-1,j_start:j_end) )
2680       IF ( humidity )       ALLOCATE( nest_offl%q_r(0:1,nzb+1:nzt,j_start:j_end)  )
2681       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_r(0:1,nzb+1:nzt,j_start:j_end) )
2682       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2683          ALLOCATE( nest_offl%chem_r(0:1,nzb+1:nzt,j_start:j_end,1:UBOUND( chem_species, 1 )) )
2684    ELSE
2685       ALLOCATE( nest_offl%u_r(1:1,1:1,1:1)  )
2686       ALLOCATE( nest_offl%v_r(1:1,1:1,1:1)  )
2687       ALLOCATE( nest_offl%w_r(1:1,1:1,1:1)  )
2688       IF ( humidity )       ALLOCATE( nest_offl%q_r(1:1,1:1,1:1)  )
2689       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_r(1:1,1:1,1:1)  )
2690       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2691          ALLOCATE( nest_offl%chem_r(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
2692    ENDIF
2693!
2694!-- Allocate arrays for reading north/south boundary values. Arrays will incorporate 2 time levels
2695!-- in order to interpolate in between. If the core has no boundary, allocate a dummy array, in
2696!-- order to enable netcdf parallel access. Dummy arrays will be allocated with dimension length
2697!-- zero.
2698    IF ( bc_dirichlet_n )  THEN
2699       ALLOCATE( nest_offl%u_n(0:1,nzb+1:nzt,i_start_u:i_end) )
2700       ALLOCATE( nest_offl%v_n(0:1,nzb+1:nzt,i_start:i_end)  )
2701       ALLOCATE( nest_offl%w_n(0:1,nzb+1:nzt-1,i_start:i_end) )
2702       IF ( humidity )       ALLOCATE( nest_offl%q_n(0:1,nzb+1:nzt,i_start:i_end)  )
2703       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_n(0:1,nzb+1:nzt,i_start:i_end) )
2704       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2705          ALLOCATE( nest_offl%chem_n(0:1,nzb+1:nzt,i_start:i_end,1:UBOUND( chem_species, 1 )) )
2706    ELSE
2707       ALLOCATE( nest_offl%u_n(1:1,1:1,1:1)  )
2708       ALLOCATE( nest_offl%v_n(1:1,1:1,1:1)  )
2709       ALLOCATE( nest_offl%w_n(1:1,1:1,1:1)  )
2710       IF ( humidity )       ALLOCATE( nest_offl%q_n(1:1,1:1,1:1)  )
2711       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_n(1:1,1:1,1:1)  )
2712       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2713          ALLOCATE( nest_offl%chem_n(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
2714    ENDIF
2715    IF ( bc_dirichlet_s )  THEN
2716       ALLOCATE( nest_offl%u_s(0:1,nzb+1:nzt,i_start_u:i_end) )
2717       ALLOCATE( nest_offl%v_s(0:1,nzb+1:nzt,i_start:i_end)  )
2718       ALLOCATE( nest_offl%w_s(0:1,nzb+1:nzt-1,i_start:i_end) )
2719       IF ( humidity )       ALLOCATE( nest_offl%q_s(0:1,nzb+1:nzt,i_start:i_end)  )
2720       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_s(0:1,nzb+1:nzt,i_start:i_end) )
2721       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2722          ALLOCATE( nest_offl%chem_s(0:1,nzb+1:nzt,i_start:i_end,1:UBOUND( chem_species, 1 )) )
2723    ELSE
2724       ALLOCATE( nest_offl%u_s(1:1,1:1,1:1)  )
2725       ALLOCATE( nest_offl%v_s(1:1,1:1,1:1)  )
2726       ALLOCATE( nest_offl%w_s(1:1,1:1,1:1)  )
2727       IF ( humidity )       ALLOCATE( nest_offl%q_s(1:1,1:1,1:1)  )
2728       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_s(1:1,1:1,1:1)  )
2729       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2730          ALLOCATE( nest_offl%chem_s(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
2731    ENDIF
2732!
2733!-- Allocate arrays for reading data at the top boundary. In contrast to the lateral boundaries,
2734!-- each core reads these data so that no dummy arrays need to be allocated.
2735    IF ( lod == 2 )  THEN
2736       ALLOCATE( nest_offl%u_top(0:1,nys:nyn,nxlu:nxr) )
2737       ALLOCATE( nest_offl%v_top(0:1,nysv:nyn,nxl:nxr) )
2738       ALLOCATE( nest_offl%w_top(0:1,nys:nyn,nxl:nxr)  )
2739       IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,nys:nyn,nxl:nxr)  )
2740       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,nys:nyn,nxl:nxr) )
2741       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2742          ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,1:UBOUND( chem_species, 1 )) )
2743    ELSE
2744       ALLOCATE( nest_offl%u_top(0:1,1:1,1:1) )
2745       ALLOCATE( nest_offl%v_top(0:1,1:1,1:1) )
2746       ALLOCATE( nest_offl%w_top(0:1,1:1,1:1)  )
2747       IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,1:1,1:1)  )
2748       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,1:1,1:1) )
2749       IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
2750          ALLOCATE( nest_offl%chem_top(0:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
2751    ENDIF
2752!
2753!-- For chemical species, create the names of the variables. This is necessary to identify the
2754!-- respective variable and write it onto the correct array in the chem_species datatype.
2755    IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2756       ALLOCATE( nest_offl%chem_from_file_l(1:UBOUND( chem_species, 1 )) )
2757       ALLOCATE( nest_offl%chem_from_file_n(1:UBOUND( chem_species, 1 )) )
2758       ALLOCATE( nest_offl%chem_from_file_r(1:UBOUND( chem_species, 1 )) )
2759       ALLOCATE( nest_offl%chem_from_file_s(1:UBOUND( chem_species, 1 )) )
2760       ALLOCATE( nest_offl%chem_from_file_t(1:UBOUND( chem_species, 1 )) )
2761
2762       ALLOCATE( nest_offl%var_names_chem_l(1:UBOUND( chem_species, 1 )) )
2763       ALLOCATE( nest_offl%var_names_chem_n(1:UBOUND( chem_species, 1 )) )
2764       ALLOCATE( nest_offl%var_names_chem_r(1:UBOUND( chem_species, 1 )) )
2765       ALLOCATE( nest_offl%var_names_chem_s(1:UBOUND( chem_species, 1 )) )
2766       ALLOCATE( nest_offl%var_names_chem_t(1:UBOUND( chem_species, 1 )) )
2767!
2768!--    Initialize flags that indicate whether the variable is on file or not. Please note, this is
2769!--    only necessary for chemistry variables.
2770       nest_offl%chem_from_file_l(:) = .FALSE.
2771       nest_offl%chem_from_file_n(:) = .FALSE.
2772       nest_offl%chem_from_file_r(:) = .FALSE.
2773       nest_offl%chem_from_file_s(:) = .FALSE.
2774       nest_offl%chem_from_file_t(:) = .FALSE.
2775
2776       DO  n = 1, UBOUND( chem_species, 1 )
2777          nest_offl%var_names_chem_l(n) = nest_offl%char_l // TRIM(chem_species(n)%name)
2778          nest_offl%var_names_chem_n(n) = nest_offl%char_n // TRIM(chem_species(n)%name)
2779          nest_offl%var_names_chem_r(n) = nest_offl%char_r // TRIM(chem_species(n)%name)
2780          nest_offl%var_names_chem_s(n) = nest_offl%char_s // TRIM(chem_species(n)%name)
2781          nest_offl%var_names_chem_t(n) = nest_offl%char_t // TRIM(chem_species(n)%name)
2782       ENDDO
2783    ENDIF
2784!
2785!-- Offline nesting for salsa
2786    IF ( salsa )  CALL salsa_nesting_offl_init
2787!
2788!-- Before initial data input is initiated, check if dynamic input file is present.
2789    IF ( .NOT. input_pids_dynamic )  THEN
2790       message_string = 'nesting_offline = .TRUE. requires dynamic '  //                           &
2791                         'input file ' // TRIM( input_file_dynamic ) // TRIM( coupling_char )
2792       CALL message( 'nesting_offl_init', 'PA0546', 1, 2, 0, 6, 0 )
2793    ENDIF
2794!
2795!-- Read COSMO data at lateral and top boundaries
2796    CALL nesting_offl_input
2797!
2798!-- Check if sufficient time steps are provided to cover the entire simulation. Note, dynamic input
2799!-- is only required for the 3D simulation, not for the soil/wall spinup. However, as the spinup
2800!-- time is added to the end_time, this must be considered here.
2801    IF ( end_time - spinup_time > nest_offl%time(nest_offl%nt-1) )  THEN
2802       message_string = 'end_time of the simulation exceeds the ' //                               &
2803                        'time dimension in the dynamic input file.'
2804       CALL message( 'nesting_offl_init', 'PA0183', 1, 2, 0, 6, 0 )
2805    ENDIF
2806!
2807!-- Set indicies for boundary grid points
2808    IF ( bc_dirichlet_l  .OR.  bc_dirichlet_r )  THEN
2809       i_bound   = MERGE( nxl  - 1, nxr + 1, bc_dirichlet_l )
2810       i_bound_u = MERGE( nxlu - 1, nxr + 1, bc_dirichlet_l )
2811    ENDIF
2812    IF ( bc_dirichlet_n  .OR.  bc_dirichlet_s )  THEN
2813       j_bound   = MERGE( nys  - 1, nyn + 1, bc_dirichlet_s )
2814       j_bound_v = MERGE( nysv - 1, nyn + 1, bc_dirichlet_s )
2815    ENDIF
2816!
2817!-- Initialize boundary data. Please note, do not initialize boundaries in case of restart runs.
2818!-- This case the boundaries are already initialized and the boundary data from file would be on the
2819!-- wrong time level.
2820    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
2821!
2822!--    Distinguish between LOD = 1 and LOD = 2 inititialization
2823       IF ( lod == 2 )  THEN
2824          IF ( bc_dirichlet_l )  THEN
2825             u(nzb+1:nzt,nys:nyn,i_bound_u) = nest_offl%u_l(0,nzb+1:nzt,nys:nyn)
2826             v(nzb+1:nzt,nysv:nyn,i_bound)  = nest_offl%v_l(0,nzb+1:nzt,nysv:nyn)
2827             w(nzb+1:nzt-1,nys:nyn,i_bound) = nest_offl%w_l(0,nzb+1:nzt-1,nys:nyn)
2828             IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%pt_l(0,nzb+1:nzt,nys:nyn)
2829             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,i_bound)  = nest_offl%q_l(0,nzb+1:nzt,nys:nyn)
2830             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2831                DO  n = 1, UBOUND( chem_species, 1 )
2832                   IF( nest_offl%chem_from_file_l(n) )  THEN
2833                      chem_species(n)%conc(nzb+1:nzt,nys:nyn,i_bound) =                            &
2834                                                             nest_offl%chem_l(0,nzb+1:nzt,nys:nyn,n)
2835                   ENDIF
2836                ENDDO
2837             ENDIF
2838          ENDIF
2839          IF ( bc_dirichlet_r )  THEN
2840             u(nzb+1:nzt,nys:nyn,i_bound_u) = nest_offl%u_r(0,nzb+1:nzt,nys:nyn)
2841             v(nzb+1:nzt,nysv:nyn,i_bound)  = nest_offl%v_r(0,nzb+1:nzt,nysv:nyn)
2842             w(nzb+1:nzt-1,nys:nyn,i_bound) = nest_offl%w_r(0,nzb+1:nzt-1,nys:nyn)
2843             IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%pt_r(0,nzb+1:nzt,nys:nyn)
2844             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,i_bound)  = nest_offl%q_r(0,nzb+1:nzt,nys:nyn)
2845             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2846                DO  n = 1, UBOUND( chem_species, 1 )
2847                   IF( nest_offl%chem_from_file_r(n) )  THEN
2848                      chem_species(n)%conc(nzb+1:nzt,nys:nyn,i_bound) =                            &
2849                                                             nest_offl%chem_r(0,nzb+1:nzt,nys:nyn,n)
2850                   ENDIF
2851                ENDDO
2852             ENDIF
2853          ENDIF
2854
2855          IF ( bc_dirichlet_n)  THEN
2856             u(nzb+1:nzt,j_bound,nxlu:nxr)  = nest_offl%u_n(0,nzb+1:nzt,nxlu:nxr)
2857             v(nzb+1:nzt,j_bound_v,nxl:nxr) = nest_offl%v_n(0,nzb+1:nzt,nxl:nxr)
2858             w(nzb+1:nzt-1,j_bound,nxl:nxr) = nest_offl%w_n(0,nzb+1:nzt-1,nxl:nxr)
2859             IF ( .NOT. neutral )  pt(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%pt_n(0,nzb+1:nzt,nxl:nxr)
2860             IF ( humidity      )  q(nzb+1:nzt,j_bound,nxl:nxr)  = nest_offl%q_n(0,nzb+1:nzt,nxl:nxr)
2861             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2862                DO  n = 1, UBOUND( chem_species, 1 )
2863                   IF( nest_offl%chem_from_file_n(n) )  THEN
2864                      chem_species(n)%conc(nzb+1:nzt,j_bound,nxl:nxr) =                            &
2865                                                             nest_offl%chem_n(0,nzb+1:nzt,nxl:nxr,n)
2866                   ENDIF
2867                ENDDO
2868             ENDIF
2869          ENDIF
2870          IF ( bc_dirichlet_s)  THEN
2871             u(nzb+1:nzt,j_bound,nxlu:nxr)  = nest_offl%u_s(0,nzb+1:nzt,nxlu:nxr)
2872             v(nzb+1:nzt,j_bound_v,nxl:nxr) = nest_offl%v_s(0,nzb+1:nzt,nxl:nxr)
2873             w(nzb+1:nzt-1,j_bound,nxl:nxr) = nest_offl%w_s(0,nzb+1:nzt-1,nxl:nxr)
2874             IF ( .NOT. neutral )  pt(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%pt_s(0,nzb+1:nzt,nxl:nxr)
2875             IF ( humidity      )  q(nzb+1:nzt,j_bound,nxl:nxr)  = nest_offl%q_s(0,nzb+1:nzt,nxl:nxr)
2876             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2877                DO  n = 1, UBOUND( chem_species, 1 )
2878                   IF( nest_offl%chem_from_file_s(n) )  THEN
2879                      chem_species(n)%conc(nzb+1:nzt,j_bound,nxl:nxr) =                            &
2880                                                             nest_offl%chem_s(0,nzb+1:nzt,nxl:nxr,n)
2881                   ENDIF
2882                ENDDO
2883             ENDIF
2884          ENDIF
2885
2886          u(nzt+1,nys:nyn,nxlu:nxr) = nest_offl%u_top(0,nys:nyn,nxlu:nxr)
2887          v(nzt+1,nysv:nyn,nxl:nxr) = nest_offl%v_top(0,nysv:nyn,nxl:nxr)
2888          w(nzt,nys:nyn,nxl:nxr)    = nest_offl%w_top(0,nys:nyn,nxl:nxr)
2889          w(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%w_top(0,nys:nyn,nxl:nxr)
2890          IF ( .NOT. neutral )  pt(nzt+1,nys:nyn,nxl:nxr) = nest_offl%pt_top(0,nys:nyn,nxl:nxr)
2891          IF ( humidity )       q(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%q_top(0,nys:nyn,nxl:nxr)
2892          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2893             DO  n = 1, UBOUND( chem_species, 1 )
2894                IF( nest_offl%chem_from_file_t(n) )  THEN
2895                   chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) =                                   &
2896                                                             nest_offl%chem_top(0,nys:nyn,nxl:nxr,n)
2897                ENDIF
2898             ENDDO
2899          ENDIF
2900!
2901!--    LOD 1
2902       ELSE
2903          IF ( bc_dirichlet_l )  THEN
2904             DO  j = nys, nyn
2905                u(nzb+1:nzt,j,i_bound_u) = nest_offl%u_l(0,nzb+1:nzt,1)
2906                w(nzb+1:nzt-1,j,i_bound) = nest_offl%w_l(0,nzb+1:nzt-1,1)
2907             ENDDO
2908             DO  j = nysv, nyn
2909                v(nzb+1:nzt,j,i_bound)  = nest_offl%v_l(0,nzb+1:nzt,1)
2910             ENDDO
2911             IF ( .NOT. neutral )  THEN
2912                DO  j = nys, nyn
2913                   pt(nzb+1:nzt,j,i_bound) = nest_offl%pt_l(0,nzb+1:nzt,1)
2914                ENDDO
2915             ENDIF
2916             IF ( humidity      )  THEN
2917                DO  j = nys, nyn
2918                   q(nzb+1:nzt,j,i_bound)  = nest_offl%q_l(0,nzb+1:nzt,1)
2919                ENDDO
2920             ENDIF
2921             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2922                DO  n = 1, UBOUND( chem_species, 1 )
2923                   IF( nest_offl%chem_from_file_l(n) )  THEN
2924                      DO  j = nys, nyn
2925                         chem_species(n)%conc(nzb+1:nzt,j,i_bound) =                               &
2926                                                                   nest_offl%chem_l(0,nzb+1:nzt,1,n)
2927                      ENDDO
2928                   ENDIF
2929                ENDDO
2930             ENDIF
2931          ENDIF
2932          IF ( bc_dirichlet_r )  THEN
2933             DO  j = nys, nyn
2934                u(nzb+1:nzt,j,i_bound_u) = nest_offl%u_r(0,nzb+1:nzt,1)
2935                w(nzb+1:nzt-1,j,i_bound) = nest_offl%w_r(0,nzb+1:nzt-1,1)
2936             ENDDO
2937             DO  j = nysv, nyn
2938                v(nzb+1:nzt,j,i_bound)  = nest_offl%v_r(0,nzb+1:nzt,1)
2939             ENDDO
2940             IF ( .NOT. neutral )  THEN
2941                DO  j = nys, nyn
2942                   pt(nzb+1:nzt,j,i_bound) = nest_offl%pt_r(0,nzb+1:nzt,1)
2943                ENDDO
2944             ENDIF
2945             IF ( humidity      )  THEN
2946                DO  j = nys, nyn
2947                   q(nzb+1:nzt,j,i_bound)  = nest_offl%q_r(0,nzb+1:nzt,1)
2948                ENDDO
2949             ENDIF
2950             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2951                DO  n = 1, UBOUND( chem_species, 1 )
2952                   IF( nest_offl%chem_from_file_r(n) )  THEN
2953                      DO  j = nys, nyn
2954                         chem_species(n)%conc(nzb+1:nzt,j,i_bound) =                               &
2955                                                                   nest_offl%chem_r(0,nzb+1:nzt,1,n)
2956                      ENDDO
2957                   ENDIF
2958                ENDDO
2959             ENDIF
2960          ENDIF
2961          IF ( bc_dirichlet_n )  THEN
2962             DO  i = nxlu, nxr
2963                u(nzb+1:nzt,j_bound,i)  = nest_offl%u_n(0,nzb+1:nzt,1)
2964             ENDDO
2965             DO  i = nxl, nxr
2966                v(nzb+1:nzt,j_bound_v,i) = nest_offl%v_n(0,nzb+1:nzt,1)
2967                w(nzb+1:nzt-1,j_bound,i) = nest_offl%w_n(0,nzb+1:nzt-1,1)
2968             ENDDO
2969             IF ( .NOT. neutral )  THEN
2970                DO  i = nxl, nxr
2971                   pt(nzb+1:nzt,j_bound,i) = nest_offl%pt_n(0,nzb+1:nzt,1)
2972                ENDDO
2973             ENDIF
2974             IF ( humidity      )  THEN
2975                DO  i = nxl, nxr
2976                   q(nzb+1:nzt,j_bound,i)  = nest_offl%q_n(0,nzb+1:nzt,1)
2977                ENDDO
2978             ENDIF
2979             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
2980                DO  n = 1, UBOUND( chem_species, 1 )
2981                   IF( nest_offl%chem_from_file_n(n) )  THEN
2982                      DO  i = nxl, nxr
2983                         chem_species(n)%conc(nzb+1:nzt,j_bound,i) =                               &
2984                                                                   nest_offl%chem_n(0,nzb+1:nzt,1,n)
2985                      ENDDO
2986                   ENDIF
2987                ENDDO
2988             ENDIF
2989          ENDIF
2990          IF ( bc_dirichlet_s )  THEN
2991             DO  i = nxlu, nxr
2992                u(nzb+1:nzt,j_bound,i)  = nest_offl%u_s(0,nzb+1:nzt,1)
2993             ENDDO
2994             DO  i = nxl, nxr
2995                v(nzb+1:nzt,j_bound_v,i) = nest_offl%v_s(0,nzb+1:nzt,1)
2996                w(nzb+1:nzt-1,j_bound,i) = nest_offl%w_s(0,nzb+1:nzt-1,1)
2997             ENDDO
2998             IF ( .NOT. neutral )  THEN
2999                DO  i = nxl, nxr
3000                   pt(nzb+1:nzt,j_bound,i) = nest_offl%pt_s(0,nzb+1:nzt,1)
3001                ENDDO
3002             ENDIF
3003             IF ( humidity      )  THEN
3004                DO  i = nxl, nxr
3005                   q(nzb+1:nzt,j_bound,i)  = nest_offl%q_s(0,nzb+1:nzt,1)
3006                ENDDO
3007             ENDIF
3008             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
3009                DO  n = 1, UBOUND( chem_species, 1 )
3010                   IF( nest_offl%chem_from_file_s(n) )  THEN
3011                      DO  i = nxl, nxr
3012                         chem_species(n)%conc(nzb+1:nzt,j_bound,i) =                               &
3013                                                                   nest_offl%chem_s(0,nzb+1:nzt,1,n)
3014                      ENDDO
3015                   ENDIF
3016                ENDDO
3017             ENDIF
3018          ENDIF
3019
3020          u(nzt+1,nys:nyn,nxlu:nxr) = nest_offl%u_top(0,1,1)
3021          v(nzt+1,nysv:nyn,nxl:nxr) = nest_offl%v_top(0,1,1)
3022          w(nzt,nys:nyn,nxl:nxr)    = nest_offl%w_top(0,1,1)
3023          w(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%w_top(0,1,1)
3024          IF ( .NOT. neutral )  pt(nzt+1,nys:nyn,nxl:nxr) = nest_offl%pt_top(0,1,1)
3025          IF ( humidity )       q(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%q_top(0,1,1)
3026          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
3027             DO  n = 1, UBOUND( chem_species, 1 )
3028                IF( nest_offl%chem_from_file_t(n) )  THEN
3029                   chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) = nest_offl%chem_top(0,1,1,n)
3030                ENDIF
3031             ENDDO
3032          ENDIF
3033       ENDIF
3034!
3035!--    In case of offline nesting the pressure forms itself based on the prescribed lateral
3036!--    boundary conditions. Hence, explicit forcing by pressure gradients via geostrophic wind
3037!--    components is not necessary and would be canceled out by the perturbation pressure otherwise.
3038!--    For this reason, set geostrophic wind components to zero.
3039       ug(nzb+1:nzt) = 0.0_wp
3040       vg(nzb+1:nzt) = 0.0_wp
3041
3042    ENDIF
3043!
3044!-- After boundary data is initialized, mask topography at the boundaries for the velocity
3045!-- components.
3046    u = MERGE( u, 0.0_wp, BTEST( wall_flags_total_0, 1 ) )
3047    v = MERGE( v, 0.0_wp, BTEST( wall_flags_total_0, 2 ) )
3048    w = MERGE( w, 0.0_wp, BTEST( wall_flags_total_0, 3 ) )
3049!
3050!-- Initial calculation of the boundary layer depth from the prescribed boundary data. This is
3051!-- required for initialize the synthetic turbulence generator correctly.
3052    CALL nesting_offl_calc_zi
3053!
3054!-- After boundary data is initialized, ensure mass conservation. Not necessary in restart runs.
3055    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
3056       CALL nesting_offl_mass_conservation
3057    ENDIF
3058
3059 END SUBROUTINE nesting_offl_init
3060
3061!--------------------------------------------------------------------------------------------------!
3062! Description:
3063!--------------------------------------------------------------------------------------------------!
3064!> Interpolation function, used to interpolate boundary data in time.
3065!--------------------------------------------------------------------------------------------------!
3066 FUNCTION interpolate_in_time( var_t1, var_t2, fac  )
3067
3068    REAL(wp)            :: fac                  !< interpolation factor
3069    REAL(wp)            :: interpolate_in_time  !< time-interpolated boundary value
3070    REAL(wp)            :: var_t1               !< boundary value at t1
3071    REAL(wp)            :: var_t2               !< boundary value at t2
3072
3073    interpolate_in_time = ( 1.0_wp - fac ) * var_t1 + fac * var_t2
3074
3075 END FUNCTION interpolate_in_time
3076
3077
3078
3079 END MODULE nesting_offl_mod
Note: See TracBrowser for help on using the repository browser.