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

Last change on this file since 4724 was 4724, checked in by suehring, 4 years ago

Mesoscale offline nesting: enable LOD 1 (homogeneous) input of lateral and top boundary conditions; add new generic subroutines to read time-dependent profile data from dynamic input file; minor bugfix - add missing initialization of the top boundary

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