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

Last change on this file since 4795 was 4795, checked in by suehring, 3 years ago

mesoscale nesting: bugfix in obtaining the correct timestamp in case of restart runs; virtual measurements: add missing control flags

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