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

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

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more, deprecated namelists removed

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