Changeset 4724 for palm/trunk


Ignore:
Timestamp:
Oct 6, 2020 5:20:39 PM (4 years ago)
Author:
suehring
Message:

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

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/nesting_offl_mod.f90

    r4582 r4724  
    2020! Current revisions:
    2121! ------------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! - Enable LOD=1 input of boundary conditions
     28! - Minor bugfix - add missing initialization of the top boundary
     29!
     30! 4582 2020-06-29 09:22:11Z suehring
    2731! Remove unused variable
    2832!
     
    220224
    221225    USE netcdf_data_input_mod,                                                 &
    222         ONLY:  check_existence,                                                &
     226        ONLY:  char_fill,                                                      &
     227               char_lod,                                                       &
     228               check_existence,                                                &
    223229               close_input_file,                                               &
     230               get_attribute,                                                  &
    224231               get_dimension_length,                                           &
    225232               get_variable,                                                   &
     
    260267       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_t  !< names of mesoscale nested chemistry variables at top boundary
    261268
    262        INTEGER(iwp) ::  nt     !< number of time levels in dynamic input file
    263        INTEGER(iwp) ::  nzu    !< number of vertical levels on scalar grid in dynamic input file
    264        INTEGER(iwp) ::  nzw    !< number of vertical levels on w grid in dynamic input file
    265        INTEGER(iwp) ::  tind   !< time index for reference time in mesoscale-offline nesting
    266        INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
    267 
    268        LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
     269       INTEGER(iwp) ::  lod_east_pt  = 2  !< level-of-detail of input data of potential temperature at the eastern boundary
     270       INTEGER(iwp) ::  lod_east_qc  = 2  !< level-of-detail of input data of cloud-water mixture fraction at the eastern boundary
     271       INTEGER(iwp) ::  lod_east_qv  = 2  !< level-of-detail of input data of specific humidity at the eastern boundary
     272       INTEGER(iwp) ::  lod_east_u   = 2  !< level-of-detail of input data of the u-component at the eastern boundary
     273       INTEGER(iwp) ::  lod_east_v   = 2  !< level-of-detail of input data of the v-component at the eastern boundary
     274       INTEGER(iwp) ::  lod_east_w   = 2  !< level-of-detail of input data of the w-component at the eastern boundary
     275       INTEGER(iwp) ::  lod_north_pt = 2  !< level-of-detail of input data of potential temperature at the northern boundary
     276       INTEGER(iwp) ::  lod_north_qc = 2  !< level-of-detail of input data of cloud-water mixture fraction at the northern boundary
     277       INTEGER(iwp) ::  lod_north_qv = 2  !< level-of-detail of input data of specific humidity at the northern boundary
     278       INTEGER(iwp) ::  lod_north_u  = 2  !< level-of-detail of input data of the u-component at the northern boundary
     279       INTEGER(iwp) ::  lod_north_v  = 2  !< level-of-detail of input data of the v-component at the northern boundary
     280       INTEGER(iwp) ::  lod_north_w  = 2  !< level-of-detail of input data of the w-component at the northern boundary
     281       INTEGER(iwp) ::  lod_south_pt = 2  !< level-of-detail of input data of potential temperature at the southern boundary
     282       INTEGER(iwp) ::  lod_south_qc = 2  !< level-of-detail of input data of cloud-water mixture fraction at the southern boundary
     283       INTEGER(iwp) ::  lod_south_qv = 2  !< level-of-detail of input data of specific humidity at the southern boundary
     284       INTEGER(iwp) ::  lod_south_u  = 2  !< level-of-detail of input data of the u-component at the southern boundary
     285       INTEGER(iwp) ::  lod_south_v  = 2  !< level-of-detail of input data of the v-component at the southern boundary
     286       INTEGER(iwp) ::  lod_south_w  = 2  !< level-of-detail of input data of the w-component at the southern boundary
     287       INTEGER(iwp) ::  lod_top_pt   = 2  !< level-of-detail of input data of potential temperature at the top boundary
     288       INTEGER(iwp) ::  lod_top_qc   = 2  !< level-of-detail of input data of cloud-water mixture fraction at the top boundary
     289       INTEGER(iwp) ::  lod_top_qv   = 2  !< level-of-detail of input data of specific humidity at the top boundary
     290       INTEGER(iwp) ::  lod_top_u    = 2  !< level-of-detail of input data of the u-component at the top boundary
     291       INTEGER(iwp) ::  lod_top_v    = 2  !< level-of-detail of input data of the v-component at the top boundary
     292       INTEGER(iwp) ::  lod_top_w    = 2  !< level-of-detail of input data of the w-component at the top boundary
     293       INTEGER(iwp) ::  lod_west_pt  = 2  !< level-of-detail of input data of potential temperature at the western boundary
     294       INTEGER(iwp) ::  lod_west_qc  = 2  !< level-of-detail of input data of cloud-water mixture fraction at the western boundary
     295       INTEGER(iwp) ::  lod_west_qv  = 2  !< level-of-detail of input data of specific humidity at the western boundary
     296       INTEGER(iwp) ::  lod_west_u   = 2  !< level-of-detail of input data of the u-component at the western boundary
     297       INTEGER(iwp) ::  lod_west_v   = 2  !< level-of-detail of input data of the v-component at the western boundary
     298       INTEGER(iwp) ::  lod_west_w   = 2  !< level-of-detail of input data of the w-component at the western boundary
     299       INTEGER(iwp) ::  nt                !< number of time levels in dynamic input file
     300       INTEGER(iwp) ::  nzu               !< number of vertical levels on scalar grid in dynamic input file
     301       INTEGER(iwp) ::  nzw               !< number of vertical levels on w grid in dynamic input file
     302       INTEGER(iwp) ::  tind              !< time index for reference time in mesoscale-offline nesting
     303       INTEGER(iwp) ::  tind_p            !< time index for following time in mesoscale-offline nesting
     304
     305       LOGICAL      ::  init = .FALSE.    !< flag indicating that offline nesting is already initialized
    269306
    270307       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 
     
    282319       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vg         !< domain-averaged geostrophic component
    283320
    284        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_left   !< u-component at left boundary
    285        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_left   !< v-component at left boundary
    286        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_left   !< w-component at left boundary
    287        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_left   !< mixing ratio at left boundary
    288        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_left  !< potentital temperautre at left boundary
    289 
    290        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_north  !< u-component at north boundary
    291        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_north  !< v-component at north boundary
    292        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_north  !< w-component at north boundary
    293        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_north  !< mixing ratio at north boundary
    294        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_north !< potentital temperautre at north boundary
    295 
    296        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_right  !< u-component at right boundary
    297        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_right  !< v-component at right boundary
    298        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_right  !< w-component at right boundary
    299        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_right  !< mixing ratio at right boundary
    300        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_right !< potentital temperautre at right boundary
    301 
    302        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_south  !< u-component at south boundary
    303        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_south  !< v-component at south boundary
    304        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_south  !< w-component at south boundary
    305        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_south  !< mixing ratio at south boundary
    306        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_south !< potentital temperautre at south boundary
    307 
     321       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_l      !< mixing ratio at left boundary
     322       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_n      !< mixing ratio at north boundary
     323       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_r      !< mixing ratio at right boundary
     324       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_s      !< mixing ratio at south boundary
     325       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
     326       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_l     !< potentital temperautre at left boundary
     327       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_n     !< potentital temperautre at north boundary
     328       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_r     !< potentital temperautre at right boundary
     329       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_s     !< potentital temperautre at south boundary
     330       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
     331       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_l      !< u-component at left boundary
     332       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_n      !< u-component at north boundary
     333       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_r      !< u-component at right boundary
     334       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_s      !< u-component at south boundary
    308335       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_top    !< u-component at top boundary
     336       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_l      !< v-component at left boundary
     337       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_n      !< v-component at north boundary
     338       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_r      !< v-component at right boundary
     339       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_s      !< v-component at south boundary
    309340       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_top    !< v-component at top boundary
     341       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_l      !< w-component at left boundary
     342       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_n      !< w-component at north boundary
     343       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_r      !< w-component at right boundary
     344       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_s      !< w-component at south boundary
    310345       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_top    !< w-component at top boundary
    311        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
    312        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
    313        
    314        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_left   !< chemical species at left boundary
    315        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_north  !< chemical species at left boundary
    316        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_right  !< chemical species at left boundary
    317        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_south  !< chemical species at left boundary
    318        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top    !< chemical species at left boundary
     346
     347       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_l   !< chemical species at left boundary
     348       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_n   !< chemical species at north boundary
     349       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_r   !< chemical species at right boundary
     350       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_s   !< chemical species at south boundary
     351       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top !< chemical species at left boundary
    319352
    320353    END TYPE nest_offl_type
     354
     355    INTEGER(iwp) ::  i_bound     !< boundary grid point in x-direction for scalars, v, and w
     356    INTEGER(iwp) ::  i_bound_u   !< boundary grid point in x-direction for u
     357    INTEGER(iwp) ::  i_start     !< start index for array allocation along x-direction at norther/southern boundary (scalars, v, w)
     358    INTEGER(iwp) ::  i_start_u   !< start index for array allocation along x-direction at norther/southern boundary (u)
     359    INTEGER(iwp) ::  i_end       !< end index for array allocation along x-direction at norther/southern boundary
     360    INTEGER(iwp) ::  j_bound     !< boundary grid point in y-direction for scalars, u, and w
     361    INTEGER(iwp) ::  j_bound_v   !< boundary grid point in y-direction for v
     362    INTEGER(iwp) ::  j_start     !< start index for array allocation along y-direction at eastern/western boundary (scalars, u, w)
     363    INTEGER(iwp) ::  j_start_v   !< start index for array allocation along y-direction at eastern/western boundary (v)
     364    INTEGER(iwp) ::  j_end       !< end index for array allocation along y-direction at eastern/western boundary
     365    INTEGER(iwp) ::  lod         !< level-of-detail of lateral input data
    321366
    322367    REAL(wp) ::  fac_dt              !< interpolation factor
     
    466511!--    7200.0. Further, since time_since_reference_point is negativ here when
    467512!--    spinup is applied, use MAX function to obtain correct time index.
    468        nest_offl%tind = MINLOC( ABS( nest_offl%time -                          &
    469                                      MAX( time_since_reference_point, 0.0_wp)  &
     513       nest_offl%tind = MINLOC( ABS( nest_offl%time -                                              &
     514                                     MAX( time_since_reference_point, 0.0_wp)                      &
    470515                                   ), DIM = 1 ) - 1
    471516       nest_offl%tind_p = nest_offl%tind + 1
     
    473518!--    Open file in read-only mode
    474519#if defined ( __netcdf )
    475        CALL open_read_file( TRIM( input_file_dynamic ) //                      &
     520       CALL open_read_file( TRIM( input_file_dynamic ) //                                          &
    476521                            TRIM( coupling_char ), pids_id )
    477522!
     
    488533!--    For the v-component, the data starts at nysv, while for the other
    489534!--    quantities the data starts at nys. This is equivalent at the north
    490 !--    and south domain boundary for the u-component.
     535!--    and south domain boundary for the u-component (nxlu).
    491536!--    Note, lateral data is also accessed by parallel IO, which is the reason
    492537!--    why different arguments are passed depending on the boundary control
    493 !--    flags. Cores that do not belong to the respective boundary just make
     538!--    flags. Cores that do not belong to the respective boundary only do
    494539!--    a dummy read with count = 0, just in order to participate the collective
    495 !--    operation.
    496 !--    Read data for western boundary   
    497        CALL get_variable( pids_id, 'ls_forcing_left_u',                        &
    498                           nest_offl%u_left,                                    & ! array to be read
    499                           MERGE( nys+1, 1, bc_dirichlet_l),                    & ! start index y direction
    500                           MERGE( nzb+1, 1, bc_dirichlet_l),                    & ! start index z direction
    501                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         & ! start index time dimension
    502                           MERGE( nyn-nys+1, 0, bc_dirichlet_l),                & ! number of elements along y
    503                           MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            & ! number of elements alogn z
    504                           MERGE( 2, 0, bc_dirichlet_l),                        & ! number of time steps (2 or 0)
    505                           .TRUE. )                                               ! parallel IO when compiled accordingly
    506      
    507        CALL get_variable( pids_id, 'ls_forcing_left_v',                        &
    508                           nest_offl%v_left,                                    &
    509                           MERGE( nysv, 1, bc_dirichlet_l),                     &
    510                           MERGE( nzb+1, 1, bc_dirichlet_l),                    &
    511                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
    512                           MERGE( nyn-nysv+1, 0, bc_dirichlet_l),               &
    513                           MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            &
    514                           MERGE( 2, 0, bc_dirichlet_l),                        &
    515                           .TRUE. )                                       
    516 
    517        CALL get_variable( pids_id, 'ls_forcing_left_w',                        &
    518                           nest_offl%w_left,                                    &
    519                           MERGE( nys+1, 1, bc_dirichlet_l),                    &
    520                           MERGE( nzb+1, 1, bc_dirichlet_l),                    &
    521                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
    522                           MERGE( nyn-nys+1, 0, bc_dirichlet_l),                &
    523                           MERGE( nest_offl%nzw, 0, bc_dirichlet_l),            &
    524                           MERGE( 2, 0, bc_dirichlet_l),                        &
    525                           .TRUE. )   
    526 
    527        IF ( .NOT. neutral )  THEN
    528           CALL get_variable( pids_id, 'ls_forcing_left_pt',                    &
    529                              nest_offl%pt_left,                                &
    530                              MERGE( nys+1, 1, bc_dirichlet_l),                 &
    531                              MERGE( nzb+1, 1, bc_dirichlet_l),                 &
    532                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
    533                              MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
    534                              MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
    535                              MERGE( 2, 0, bc_dirichlet_l),                     &
     540!--    operation. This is because collective parallel access shows better
     541!--    performance than just a conditional access.
     542!--    Read data for LOD 2, i.e. time-dependent xz-, yz-, and xy-slices.
     543       IF ( lod == 2 )  THEN
     544          CALL get_variable( pids_id, 'ls_forcing_left_u',                                         &
     545                             nest_offl%u_l,                                                        & ! array to be read
     546                             MERGE( nys+1, 1, bc_dirichlet_l),                                     & ! start index y direction
     547                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     & ! start index z direction
     548                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          & ! start index time dimension
     549                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                 & ! number of elements along y
     550                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             & ! number of elements alogn z
     551                             MERGE( 2, 0, bc_dirichlet_l),                                         & ! number of time steps (2 or 0)
     552                             .TRUE. )                                                                ! parallel IO when compiled accordingly
     553
     554          CALL get_variable( pids_id, 'ls_forcing_left_v',                                         &
     555                             nest_offl%v_l,                                                        &
     556                             MERGE( nysv, 1, bc_dirichlet_l),                                      &
     557                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
     558                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
     559                             MERGE( nyn-nysv+1, 0, bc_dirichlet_l),                                &
     560                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                             &
     561                             MERGE( 2, 0, bc_dirichlet_l),                                         &
    536562                             .TRUE. )
    537        ENDIF
    538 
    539        IF ( humidity )  THEN
    540           CALL get_variable( pids_id, 'ls_forcing_left_qv',                    &
    541                              nest_offl%q_left,                                 &
    542                              MERGE( nys+1, 1, bc_dirichlet_l),                 &
    543                              MERGE( nzb+1, 1, bc_dirichlet_l),                 &
    544                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
    545                              MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
    546                              MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
    547                              MERGE( 2, 0, bc_dirichlet_l),                     &
     563
     564          CALL get_variable( pids_id, 'ls_forcing_left_w',                                         &
     565                             nest_offl%w_l,                                                        &
     566                             MERGE( nys+1, 1, bc_dirichlet_l),                                     &
     567                             MERGE( nzb+1, 1, bc_dirichlet_l),                                     &
     568                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                          &
     569                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),                                 &
     570                             MERGE( nest_offl%nzw, 0, bc_dirichlet_l),                             &
     571                             MERGE( 2, 0, bc_dirichlet_l),                                         &
     572                             .TRUE. )   
     573
     574          IF ( .NOT. neutral )  THEN
     575             CALL get_variable( pids_id, 'ls_forcing_left_pt',                                     &
     576                                nest_offl%pt_l,                                                    &
     577                                MERGE( nys+1, 1, bc_dirichlet_l),                                  &
     578                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
     579                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
     580                                MERGE( nyn-nys+1, 0, bc_dirichlet_l),                              &
     581                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          &
     582                                MERGE( 2, 0, bc_dirichlet_l),                                      &
     583                                .TRUE. )
     584          ENDIF
     585
     586          IF ( humidity )  THEN
     587             CALL get_variable( pids_id, 'ls_forcing_left_qv',                                     &
     588                                nest_offl%q_l,                                                     &
     589                                MERGE( nys+1, 1, bc_dirichlet_l),                                  &
     590                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
     591                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
     592                                MERGE( nyn-nys+1, 0, bc_dirichlet_l),                              &
     593                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          &
     594                                MERGE( 2, 0, bc_dirichlet_l),                                      &
     595                                .TRUE. )
     596          ENDIF
     597
     598          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     599             DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
     600                IF ( check_existence( nest_offl%var_names,                                         &
     601                                      nest_offl%var_names_chem_l(n) ) )  THEN
     602                   CALL get_variable( pids_id,                                                     &
     603                                      TRIM( nest_offl%var_names_chem_l(n) ),                       &
     604                                      nest_offl%chem_l(:,:,:,n),                                   &
     605                                      MERGE( nys+1, 1, bc_dirichlet_l),                            &
     606                                      MERGE( nzb+1, 1, bc_dirichlet_l),                            &
     607                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                 &
     608                                      MERGE( nyn-nys+1, 0, bc_dirichlet_l),                        &
     609                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                    &
     610                                      MERGE( 2, 0, bc_dirichlet_l),                                &
     611                                      .TRUE. )
     612                   nest_offl%chem_from_file_l(n) = .TRUE.
     613                ENDIF
     614             ENDDO
     615          ENDIF
     616!
     617!--       Read data for eastern boundary   
     618          CALL get_variable( pids_id, 'ls_forcing_right_u',                                        &
     619                             nest_offl%u_r,                                                        &
     620                             MERGE( nys+1, 1, bc_dirichlet_r),                                     &
     621                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
     622                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
     623                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                 &
     624                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
     625                             MERGE( 2, 0, bc_dirichlet_r),                                         &
    548626                             .TRUE. )
    549        ENDIF
    550 
    551        IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    552           DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
    553              IF ( check_existence( nest_offl%var_names,                        &
    554                                    nest_offl%var_names_chem_l(n) ) )  THEN
    555                 CALL get_variable( pids_id,                                    &
    556                            TRIM( nest_offl%var_names_chem_l(n) ),              &
    557                            nest_offl%chem_left(:,:,:,n),                       &
    558                            MERGE( nys+1, 1, bc_dirichlet_l),                   &
    559                            MERGE( nzb+1, 1, bc_dirichlet_l),                   &
    560                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),        &
    561                            MERGE( nyn-nys+1, 0, bc_dirichlet_l),               &
    562                            MERGE( nest_offl%nzu, 0, bc_dirichlet_l),           &
    563                            MERGE( 2, 0, bc_dirichlet_l),                       &
    564                            .TRUE. )
    565                 nest_offl%chem_from_file_l(n) = .TRUE.
    566              ENDIF
    567           ENDDO
    568        ENDIF
    569 !
    570 !--    Read data for eastern boundary   
    571        CALL get_variable( pids_id, 'ls_forcing_right_u',                       &
    572                           nest_offl%u_right,                                   &
    573                           MERGE( nys+1, 1, bc_dirichlet_r),                    &
    574                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    575                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    576                           MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
    577                           MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
    578                           MERGE( 2, 0, bc_dirichlet_r),                        &
    579                           .TRUE. )                                             
    580      
    581        CALL get_variable( pids_id, 'ls_forcing_right_v',                       &
    582                           nest_offl%v_right,                                   &
    583                           MERGE( nysv, 1, bc_dirichlet_r),                     &
    584                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    585                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    586                           MERGE( nyn-nysv+1, 0, bc_dirichlet_r),               &
    587                           MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
    588                           MERGE( 2, 0, bc_dirichlet_r),                        &
    589                           .TRUE. )                                             
    590 
    591        CALL get_variable( pids_id, 'ls_forcing_right_w',                       &
    592                           nest_offl%w_right,                                   &
    593                           MERGE( nys+1, 1, bc_dirichlet_r),                    &
    594                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    595                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    596                           MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
    597                           MERGE( nest_offl%nzw, 0, bc_dirichlet_r),            &
    598                           MERGE( 2, 0, bc_dirichlet_r),                        &
    599                           .TRUE. )   
    600 
    601        IF ( .NOT. neutral )  THEN
    602           CALL get_variable( pids_id, 'ls_forcing_right_pt',                   &
    603                              nest_offl%pt_right,                               &
    604                              MERGE( nys+1, 1, bc_dirichlet_r),                 &
    605                              MERGE( nzb+1, 1, bc_dirichlet_r),                 &
    606                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
    607                              MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
    608                              MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
    609                              MERGE( 2, 0, bc_dirichlet_r),                     &
     627
     628          CALL get_variable( pids_id, 'ls_forcing_right_v',                                        &
     629                             nest_offl%v_r,                                                        &
     630                             MERGE( nysv, 1, bc_dirichlet_r),                                      &
     631                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
     632                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
     633                             MERGE( nyn-nysv+1, 0, bc_dirichlet_r),                                &
     634                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                             &
     635                             MERGE( 2, 0, bc_dirichlet_r),                                         &
    610636                             .TRUE. )
    611        ENDIF
    612 
    613        IF ( humidity )  THEN
    614           CALL get_variable( pids_id, 'ls_forcing_right_qv',                   &
    615                              nest_offl%q_right,                                &
    616                              MERGE( nys+1, 1, bc_dirichlet_r),                 &
    617                              MERGE( nzb+1, 1, bc_dirichlet_r),                 &
    618                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
    619                              MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
    620                              MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
    621                              MERGE( 2, 0, bc_dirichlet_r),                     &
     637
     638          CALL get_variable( pids_id, 'ls_forcing_right_w',                                        &
     639                             nest_offl%w_r,                                                        &
     640                             MERGE( nys+1, 1, bc_dirichlet_r),                                     &
     641                             MERGE( nzb+1, 1, bc_dirichlet_r),                                     &
     642                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                          &
     643                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),                                 &
     644                             MERGE( nest_offl%nzw, 0, bc_dirichlet_r),                             &
     645                             MERGE( 2, 0, bc_dirichlet_r),                                         &
    622646                             .TRUE. )
    623        ENDIF
    624 
    625        IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    626           DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
    627              IF ( check_existence( nest_offl%var_names,                        &
    628                                    nest_offl%var_names_chem_r(n) ) )  THEN
    629                 CALL get_variable( pids_id,                                    &
    630                            TRIM( nest_offl%var_names_chem_r(n) ),              &
    631                            nest_offl%chem_right(:,:,:,n),                      &
    632                            MERGE( nys+1, 1, bc_dirichlet_r),                   &
    633                            MERGE( nzb+1, 1, bc_dirichlet_r),                   &
    634                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),        &
    635                            MERGE( nyn-nys+1, 0, bc_dirichlet_r),               &
    636                            MERGE( nest_offl%nzu, 0, bc_dirichlet_r),           &
    637                            MERGE( 2, 0, bc_dirichlet_r),                       &
    638                            .TRUE. )
    639                 nest_offl%chem_from_file_r(n) = .TRUE.
    640              ENDIF
    641           ENDDO
    642        ENDIF
    643 !
    644 !--    Read data for northern boundary
    645        CALL get_variable( pids_id, 'ls_forcing_north_u',                       & ! array to be read
    646                           nest_offl%u_north,                                   & ! start index x direction
    647                           MERGE( nxlu, 1, bc_dirichlet_n ),                    & ! start index z direction
    648                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    649                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    650                           MERGE( nxr-nxlu+1, 0, bc_dirichlet_n ),              & ! number of elements alogn z
    651                           MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    652                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    653                           .TRUE. )
    654 
    655        CALL get_variable( pids_id, 'ls_forcing_north_v',                       & ! array to be read
    656                           nest_offl%v_north,                                   & ! start index x direction
    657                           MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
    658                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    659                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    660                           MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
    661                           MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    662                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    663                           .TRUE. )
    664 
    665        CALL get_variable( pids_id, 'ls_forcing_north_w',                       & ! array to be read
    666                           nest_offl%w_north,                                   & ! start index x direction
    667                           MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
    668                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    669                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    670                           MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
    671                           MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    672                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    673                           .TRUE. )
    674 
    675        IF ( .NOT. neutral )  THEN
    676           CALL get_variable( pids_id, 'ls_forcing_north_pt',                   & ! array to be read
    677                              nest_offl%pt_north,                               & ! start index x direction
    678                              MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
    679                              MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
    680                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
    681                              MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
    682                              MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    683                              MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
     647
     648          IF ( .NOT. neutral )  THEN
     649             CALL get_variable( pids_id, 'ls_forcing_right_pt',                                    &
     650                                nest_offl%pt_r,                                                    &
     651                                MERGE( nys+1, 1, bc_dirichlet_r),                                  &
     652                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
     653                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
     654                                MERGE( nyn-nys+1, 0, bc_dirichlet_r),                              &
     655                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
     656                                MERGE( 2, 0, bc_dirichlet_r),                                      &
     657                                .TRUE. )
     658          ENDIF
     659
     660          IF ( humidity )  THEN
     661             CALL get_variable( pids_id, 'ls_forcing_right_qv',                                    &
     662                                nest_offl%q_r,                                                     &
     663                                MERGE( nys+1, 1, bc_dirichlet_r),                                  &
     664                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
     665                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
     666                                MERGE( nyn-nys+1, 0, bc_dirichlet_r),                              &
     667                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
     668                                MERGE( 2, 0, bc_dirichlet_r),                                      &
     669                                .TRUE. )
     670          ENDIF
     671
     672          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     673             DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
     674                IF ( check_existence( nest_offl%var_names,                                         &
     675                                      nest_offl%var_names_chem_r(n) ) )  THEN
     676                   CALL get_variable( pids_id,                                                     &
     677                                      TRIM( nest_offl%var_names_chem_r(n) ),                       &
     678                                      nest_offl%chem_r(:,:,:,n),                                   &
     679                                      MERGE( nys+1, 1, bc_dirichlet_r),                            &
     680                                      MERGE( nzb+1, 1, bc_dirichlet_r),                            &
     681                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                 &
     682                                      MERGE( nyn-nys+1, 0, bc_dirichlet_r),                        &
     683                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                    &
     684                                      MERGE( 2, 0, bc_dirichlet_r),                                &
     685                                      .TRUE. )
     686                   nest_offl%chem_from_file_r(n) = .TRUE.
     687                ENDIF
     688             ENDDO
     689          ENDIF
     690!
     691!--       Read data for northern boundary
     692          CALL get_variable( pids_id, 'ls_forcing_north_u',                                        &
     693                             nest_offl%u_n,                                                        &
     694                             MERGE( nxlu, 1, bc_dirichlet_n ),                                     &
     695                             MERGE( nzb+1, 1, bc_dirichlet_n ),                                    &
     696                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                         &
     697                             MERGE( nxr-nxlu+1, 0, bc_dirichlet_n ),                               &
     698                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                            &
     699                             MERGE( 2, 0, bc_dirichlet_n ),                                        &
    684700                             .TRUE. )
    685        ENDIF
    686        IF ( humidity )  THEN
    687           CALL get_variable( pids_id, 'ls_forcing_north_qv',                   & ! array to be read
    688                              nest_offl%q_north,                                & ! start index x direction
    689                              MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
    690                              MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
    691                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
    692                              MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
    693                              MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    694                              MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
     701
     702          CALL get_variable( pids_id, 'ls_forcing_north_v',                                        &
     703                             nest_offl%v_n,                                                        &
     704                             MERGE( nxl+1, 1, bc_dirichlet_n ),                                    &
     705                             MERGE( nzb+1, 1, bc_dirichlet_n ),                                    &
     706                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                         &
     707                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                &
     708                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                            &
     709                             MERGE( 2, 0, bc_dirichlet_n ),                                        &
    695710                             .TRUE. )
    696        ENDIF
    697 
    698        IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    699           DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)
    700              IF ( check_existence( nest_offl%var_names,                        &
    701                                    nest_offl%var_names_chem_n(n) ) )  THEN
    702                 CALL get_variable( pids_id,                                    &
    703                            TRIM( nest_offl%var_names_chem_n(n) ),              &
    704                            nest_offl%chem_north(:,:,:,n),                      &
    705                            MERGE( nxl+1, 1, bc_dirichlet_n ),                  &
    706                            MERGE( nzb+1, 1, bc_dirichlet_n ),                  &
    707                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),       &
    708                            MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),              &
    709                            MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),          &
    710                            MERGE( 2, 0, bc_dirichlet_n ),                      &
    711                            .TRUE. )
    712                 nest_offl%chem_from_file_n(n) = .TRUE.
    713              ENDIF
    714           ENDDO
    715        ENDIF
    716 !
    717 !--    Read data for southern boundary
    718        CALL get_variable( pids_id, 'ls_forcing_south_u',                       & ! array to be read
    719                           nest_offl%u_south,                                   & ! start index x direction
    720                           MERGE( nxlu, 1, bc_dirichlet_s ),                    & ! start index z direction
    721                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    722                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    723                           MERGE( nxr-nxlu+1, 0, bc_dirichlet_s ),              & ! number of elements alogn z
    724                           MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    725                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    726                           .TRUE. )
    727 
    728        CALL get_variable( pids_id, 'ls_forcing_south_v',                       & ! array to be read
    729                           nest_offl%v_south,                                   & ! start index x direction
    730                           MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
    731                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    732                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    733                           MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
    734                           MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    735                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    736                           .TRUE. )
    737 
    738        CALL get_variable( pids_id, 'ls_forcing_south_w',                       & ! array to be read
    739                           nest_offl%w_south,                                   & ! start index x direction
    740                           MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
    741                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    742                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    743                           MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
    744                           MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    745                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    746                           .TRUE. )
    747 
    748        IF ( .NOT. neutral )  THEN
    749           CALL get_variable( pids_id, 'ls_forcing_south_pt',                   & ! array to be read
    750                              nest_offl%pt_south,                               & ! start index x direction
    751                              MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
    752                              MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
    753                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
    754                              MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
    755                              MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    756                              MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
     711
     712          CALL get_variable( pids_id, 'ls_forcing_north_w',                                        &
     713                             nest_offl%w_n,                                                        &
     714                             MERGE( nxl+1, 1, bc_dirichlet_n ),                                    &
     715                             MERGE( nzb+1, 1, bc_dirichlet_n ),                                    &
     716                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                         &
     717                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                                &
     718                             MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),                            &
     719                             MERGE( 2, 0, bc_dirichlet_n ),                                        &
    757720                             .TRUE. )
    758        ENDIF
    759        IF ( humidity )  THEN
    760           CALL get_variable( pids_id, 'ls_forcing_south_qv',                   & ! array to be read
    761                              nest_offl%q_south,                                & ! start index x direction
    762                              MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
    763                              MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
    764                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
    765                              MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
    766                              MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    767                              MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
     721
     722          IF ( .NOT. neutral )  THEN
     723             CALL get_variable( pids_id, 'ls_forcing_north_pt',                                    &
     724                                nest_offl%pt_n,                                                    &
     725                                MERGE( nxl+1, 1, bc_dirichlet_n ),                                 &
     726                                MERGE( nzb+1, 1, bc_dirichlet_n ),                                 &
     727                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                      &
     728                                MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                             &
     729                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                         &
     730                                MERGE( 2, 0, bc_dirichlet_n ),                                     &
     731                                .TRUE. )
     732          ENDIF
     733          IF ( humidity )  THEN
     734             CALL get_variable( pids_id, 'ls_forcing_north_qv',                                    &
     735                                nest_offl%q_n,                                                     &
     736                                MERGE( nxl+1, 1, bc_dirichlet_n ),                                 &
     737                                MERGE( nzb+1, 1, bc_dirichlet_n ),                                 &
     738                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                      &
     739                                MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                             &
     740                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                         &
     741                                MERGE( 2, 0, bc_dirichlet_n ),                                     &
     742                                .TRUE. )
     743          ENDIF
     744
     745          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     746             DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)
     747                IF ( check_existence( nest_offl%var_names,                                         &
     748                                      nest_offl%var_names_chem_n(n) ) )  THEN
     749                   CALL get_variable( pids_id,                                                     &
     750                                      TRIM( nest_offl%var_names_chem_n(n) ),                       &
     751                                      nest_offl%chem_n(:,:,:,n),                                   &
     752                                      MERGE( nxl+1, 1, bc_dirichlet_n ),                           &
     753                                      MERGE( nzb+1, 1, bc_dirichlet_n ),                           &
     754                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),                &
     755                                      MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),                       &
     756                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),                   &
     757                                      MERGE( 2, 0, bc_dirichlet_n ),                               &
     758                                      .TRUE. )
     759                   nest_offl%chem_from_file_n(n) = .TRUE.
     760                ENDIF
     761             ENDDO
     762          ENDIF
     763!
     764!--       Read data for southern boundary
     765          CALL get_variable( pids_id, 'ls_forcing_south_u',                                        &
     766                             nest_offl%u_s,                                                        &
     767                             MERGE( nxlu, 1, bc_dirichlet_s ),                                     &
     768                             MERGE( nzb+1, 1, bc_dirichlet_s ),                                    &
     769                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                         &
     770                             MERGE( nxr-nxlu+1, 0, bc_dirichlet_s ),                               &
     771                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                            &
     772                             MERGE( 2, 0, bc_dirichlet_s ),                                        &
    768773                             .TRUE. )
    769        ENDIF
    770 
    771        IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    772           DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)
    773              IF ( check_existence( nest_offl%var_names,                        &
    774                                    nest_offl%var_names_chem_s(n) ) )  THEN
    775                 CALL get_variable( pids_id,                                    &
    776                            TRIM( nest_offl%var_names_chem_s(n) ),              &
    777                            nest_offl%chem_south(:,:,:,n),                      &
    778                            MERGE( nxl+1, 1, bc_dirichlet_s ),                  &
    779                            MERGE( nzb+1, 1, bc_dirichlet_s ),                  &
    780                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),       &
    781                            MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),              &
    782                            MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),          &
    783                            MERGE( 2, 0, bc_dirichlet_s ),                      &
    784                            .TRUE. )
    785                 nest_offl%chem_from_file_s(n) = .TRUE.
    786              ENDIF
    787           ENDDO
    788        ENDIF
    789 !
    790 !--    Top boundary
    791        CALL get_variable( pids_id, 'ls_forcing_top_u',                         &
    792                              nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),            &
    793                              nxlu, nys+1, nest_offl%tind+1,                    &
     774
     775          CALL get_variable( pids_id, 'ls_forcing_south_v',                                        &
     776                             nest_offl%v_s,                                                        &
     777                             MERGE( nxl+1, 1, bc_dirichlet_s ),                                    &
     778                             MERGE( nzb+1, 1, bc_dirichlet_s ),                                    &
     779                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                         &
     780                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                &
     781                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                            &
     782                             MERGE( 2, 0, bc_dirichlet_s ),                                        &
     783                             .TRUE. )
     784
     785          CALL get_variable( pids_id, 'ls_forcing_south_w',                                        &
     786                             nest_offl%w_s,                                                        &
     787                             MERGE( nxl+1, 1, bc_dirichlet_s ),                                    &
     788                             MERGE( nzb+1, 1, bc_dirichlet_s ),                                    &
     789                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                         &
     790                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                                &
     791                             MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),                            &
     792                             MERGE( 2, 0, bc_dirichlet_s ),                                        &
     793                             .TRUE. )
     794
     795          IF ( .NOT. neutral )  THEN
     796             CALL get_variable( pids_id, 'ls_forcing_south_pt',                                    &
     797                                nest_offl%pt_s,                                                    &
     798                                MERGE( nxl+1, 1, bc_dirichlet_s ),                                 &
     799                                MERGE( nzb+1, 1, bc_dirichlet_s ),                                 &
     800                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                      &
     801                                MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                             &
     802                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                         &
     803                                MERGE( 2, 0, bc_dirichlet_s ),                                     &
     804                                .TRUE. )
     805          ENDIF
     806          IF ( humidity )  THEN
     807             CALL get_variable( pids_id, 'ls_forcing_south_qv',                                    &
     808                                nest_offl%q_s,                                                     &
     809                                MERGE( nxl+1, 1, bc_dirichlet_s ),                                 &
     810                                MERGE( nzb+1, 1, bc_dirichlet_s ),                                 &
     811                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                      &
     812                                MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                             &
     813                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                         &
     814                                MERGE( 2, 0, bc_dirichlet_s ),                                     &
     815                                .TRUE. )
     816          ENDIF
     817
     818          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     819             DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)
     820                IF ( check_existence( nest_offl%var_names,                                         &
     821                                      nest_offl%var_names_chem_s(n) ) )  THEN
     822                   CALL get_variable( pids_id,                                                     &
     823                                      TRIM( nest_offl%var_names_chem_s(n) ),                       &
     824                                      nest_offl%chem_s(:,:,:,n),                                   &
     825                                      MERGE( nxl+1, 1, bc_dirichlet_s ),                           &
     826                                      MERGE( nzb+1, 1, bc_dirichlet_s ),                           &
     827                                      MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),                &
     828                                      MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),                       &
     829                                      MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),                   &
     830                                      MERGE( 2, 0, bc_dirichlet_s ),                               &
     831                                      .TRUE. )
     832                   nest_offl%chem_from_file_s(n) = .TRUE.
     833                ENDIF
     834             ENDDO
     835          ENDIF
     836!
     837!--       Top boundary
     838          CALL get_variable( pids_id, 'ls_forcing_top_u',                                          &
     839                             nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),                                &
     840                             nxlu, nys+1, nest_offl%tind+1,                                        &
    794841                             nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
    795842
    796        CALL get_variable( pids_id, 'ls_forcing_top_v',                         &
    797                              nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),            &
    798                              nxl+1, nysv, nest_offl%tind+1,                    &
     843          CALL get_variable( pids_id, 'ls_forcing_top_v',                                          &
     844                             nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),                                &
     845                             nxl+1, nysv, nest_offl%tind+1,                                        &
    799846                             nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
    800847
    801        CALL get_variable( pids_id, 'ls_forcing_top_w',                         &
    802                              nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
    803                              nxl+1, nys+1, nest_offl%tind+1,                   &
     848          CALL get_variable( pids_id, 'ls_forcing_top_w',                                          &
     849                             nest_offl%w_top(0:1,nys:nyn,nxl:nxr),                                 &
     850                             nxl+1, nys+1, nest_offl%tind+1,                                       &
    804851                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    805852
    806        IF ( .NOT. neutral )  THEN
    807           CALL get_variable( pids_id, 'ls_forcing_top_pt',                     &
    808                                 nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),         &
    809                                 nxl+1, nys+1, nest_offl%tind+1,                &
     853          IF ( .NOT. neutral )  THEN
     854             CALL get_variable( pids_id, 'ls_forcing_top_pt',                                      &
     855                                nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),                             &
     856                                nxl+1, nys+1, nest_offl%tind+1,                                    &
    810857                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    811        ENDIF
    812        IF ( humidity )  THEN
    813           CALL get_variable( pids_id, 'ls_forcing_top_qv',                     &
    814                                 nest_offl%q_top(0:1,nys:nyn,nxl:nxr),          &
    815                                 nxl+1, nys+1, nest_offl%tind+1,                &
     858          ENDIF
     859          IF ( humidity )  THEN
     860             CALL get_variable( pids_id, 'ls_forcing_top_qv',                                      &
     861                                nest_offl%q_top(0:1,nys:nyn,nxl:nxr),                              &
     862                                nxl+1, nys+1, nest_offl%tind+1,                                    &
    816863                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    817        ENDIF
    818 
    819        IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    820           DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
    821              IF ( check_existence( nest_offl%var_names,                        &
    822                                    nest_offl%var_names_chem_t(n) ) )  THEN
    823                 CALL get_variable( pids_id,                                    &
    824                               TRIM( nest_offl%var_names_chem_t(n) ),           &
    825                               nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),       &
    826                               nxl+1, nys+1, nest_offl%tind+1,                  &
    827                               nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    828                 nest_offl%chem_from_file_t(n) = .TRUE.
    829              ENDIF
    830           ENDDO
    831        ENDIF
     864          ENDIF
     865
     866          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     867             DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     868                IF ( check_existence( nest_offl%var_names,                                         &
     869                                      nest_offl%var_names_chem_t(n) ) )  THEN
     870                   CALL get_variable( pids_id,                                                     &
     871                                 TRIM( nest_offl%var_names_chem_t(n) ),                            &
     872                                 nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),                        &
     873                                 nxl+1, nys+1, nest_offl%tind+1,                                   &
     874                                 nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
     875                   nest_offl%chem_from_file_t(n) = .TRUE.
     876                ENDIF
     877             ENDDO
     878          ENDIF
     879!
     880!--    Read data for LOD 1, i.e. time-dependent profiles. In constrast to LOD 2 where the amount of
     881!--    IO is larger, only the respective boundary processes read the data.
     882       ELSE
     883          IF ( bc_dirichlet_l )  THEN
     884             CALL get_variable( pids_id, 'ls_forcing_left_u',                                      &
     885                                nest_offl%u_l(0:1,:,1:1),                                          & ! array to be read
     886                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  & ! start index z direction
     887                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       & ! start index time dimension
     888                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          & ! number of elements along z
     889                                MERGE( 2, 0, bc_dirichlet_l) )                                       ! number of time steps (2 or 0)
     890             CALL get_variable( pids_id, 'ls_forcing_left_v',                                      &
     891                                nest_offl%v_l(0:1,:,1:1),                                          &
     892                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
     893                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
     894                                MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                          &
     895                                MERGE( 2, 0, bc_dirichlet_l) )
     896             CALL get_variable( pids_id, 'ls_forcing_left_w',                                      &
     897                                nest_offl%w_l(0:1,:,1:1),                                          &
     898                                MERGE( nzb+1, 1, bc_dirichlet_l),                                  &
     899                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                       &
     900                                MERGE( nest_offl%nzw, 0, bc_dirichlet_l),                          &
     901                                MERGE( 2, 0, bc_dirichlet_l) )
     902             IF ( .NOT. neutral )  THEN
     903                CALL get_variable( pids_id, 'ls_forcing_left_pt',                                  &
     904                                   nest_offl%pt_l(0:1,:,1:1),                                      &
     905                                   MERGE( nzb+1, 1, bc_dirichlet_l),                               &
     906                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                    &
     907                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                       &
     908                                   MERGE( 2, 0, bc_dirichlet_l) )
     909             ENDIF
     910             IF ( humidity )  THEN
     911                CALL get_variable( pids_id, 'ls_forcing_left_qv',                                  &
     912                                   nest_offl%q_l(0:1,:,1:1),                                       &
     913                                   MERGE( nzb+1, 1, bc_dirichlet_l),                               &
     914                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),                    &
     915                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                       &
     916                                   MERGE( 2, 0, bc_dirichlet_l) )
     917             ENDIF
     918             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     919                DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     920                   IF ( check_existence( nest_offl%var_names,                                      &
     921                                         nest_offl%var_names_chem_t(n) ) )  THEN
     922                      CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),           &
     923                                         nest_offl%chem_l(0:1,:,1:1,n),                            &
     924                                         MERGE( nzb+1, 1, bc_dirichlet_l),                         &
     925                                         MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),              &
     926                                         MERGE( nest_offl%nzu, 0, bc_dirichlet_l),                 &
     927                                         MERGE( 2, 0, bc_dirichlet_l) )
     928                      nest_offl%chem_from_file_l(n) = .TRUE.
     929                   ENDIF
     930                ENDDO
     931             ENDIF
     932          ENDIF
     933          IF ( bc_dirichlet_r )  THEN
     934             CALL get_variable( pids_id, 'ls_forcing_right_u',                                     &
     935                                nest_offl%u_r(0:1,:,1:1),                                          &
     936                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
     937                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
     938                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
     939                                MERGE( 2, 0, bc_dirichlet_r) )
     940             CALL get_variable( pids_id, 'ls_forcing_right_v',                                     &
     941                                nest_offl%v_r(0:1,:,1:1),                                          &
     942                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
     943                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
     944                                MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                          &
     945                                MERGE( 2, 0, bc_dirichlet_r) )
     946             CALL get_variable( pids_id, 'ls_forcing_right_w',                                     &
     947                                nest_offl%w_r(0:1,:,1:1),                                          &
     948                                MERGE( nzb+1, 1, bc_dirichlet_r),                                  &
     949                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                       &
     950                                MERGE( nest_offl%nzw, 0, bc_dirichlet_r),                          &
     951                                MERGE( 2, 0, bc_dirichlet_r) )
     952             IF ( .NOT. neutral )  THEN
     953                CALL get_variable( pids_id, 'ls_forcing_right_pt',                                 &
     954                                   nest_offl%pt_r(0:1,:,1:1),                                      &
     955                                   MERGE( nzb+1, 1, bc_dirichlet_r),                               &
     956                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                    &
     957                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                       &
     958                                   MERGE( 2, 0, bc_dirichlet_r) )
     959             ENDIF
     960             IF ( humidity )  THEN
     961                CALL get_variable( pids_id, 'ls_forcing_right_qv',                                 &
     962                                   nest_offl%q_r(0:1,:,1:1),                                       &
     963                                   MERGE( nzb+1, 1, bc_dirichlet_r),                               &
     964                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),                    &
     965                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                       &
     966                                   MERGE( 2, 0, bc_dirichlet_r) )
     967             ENDIF
     968             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     969                DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     970                   IF ( check_existence( nest_offl%var_names,                                      &
     971                                         nest_offl%var_names_chem_t(n) ) )  THEN
     972                      CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),           &
     973                                         nest_offl%chem_r(0:1,:,1:1,n),                            &
     974                                         MERGE( nzb+1, 1, bc_dirichlet_r),                         &
     975                                         MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),              &
     976                                         MERGE( nest_offl%nzu, 0, bc_dirichlet_r),                 &
     977                                         MERGE( 2, 0, bc_dirichlet_r) )
     978                      nest_offl%chem_from_file_r(n) = .TRUE.
     979                   ENDIF
     980                ENDDO
     981             ENDIF
     982          ENDIF
     983          IF ( bc_dirichlet_n )  THEN
     984             CALL get_variable( pids_id, 'ls_forcing_north_u',                                     &
     985                                nest_offl%u_n(0:1,:,1:1),                                          &
     986                                MERGE( nzb+1, 1, bc_dirichlet_n),                                  &
     987                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                       &
     988                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                          &
     989                                MERGE( 2, 0, bc_dirichlet_n) )
     990             CALL get_variable( pids_id, 'ls_forcing_north_v',                                     &
     991                                nest_offl%v_n(0:1,:,1:1),                                          &
     992                                MERGE( nzb+1, 1, bc_dirichlet_n),                                  &
     993                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                       &
     994                                MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                          &
     995                                MERGE( 2, 0, bc_dirichlet_n) )
     996             CALL get_variable( pids_id, 'ls_forcing_north_w',                                     &
     997                                nest_offl%w_n(0:1,:,1:1),                                          &
     998                                MERGE( nzb+1, 1, bc_dirichlet_n),                                  &
     999                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                       &
     1000                                MERGE( nest_offl%nzw, 0, bc_dirichlet_n),                          &
     1001                                MERGE( 2, 0, bc_dirichlet_n) )
     1002             IF ( .NOT. neutral )  THEN
     1003                CALL get_variable( pids_id, 'ls_forcing_north_pt',                                 &
     1004                                   nest_offl%pt_n(0:1,:,1:1),                                      &
     1005                                   MERGE( nzb+1, 1, bc_dirichlet_n),                               &
     1006                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                    &
     1007                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                       &
     1008                                   MERGE( 2, 0, bc_dirichlet_n) )
     1009             ENDIF
     1010             IF ( humidity )  THEN
     1011                CALL get_variable( pids_id, 'ls_forcing_north_qv',                                 &
     1012                                   nest_offl%q_n(0:1,:,1:1),                                       &
     1013                                   MERGE( nzb+1, 1, bc_dirichlet_n),                               &
     1014                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),                    &
     1015                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                       &
     1016                                   MERGE( 2, 0, bc_dirichlet_n) )
     1017             ENDIF
     1018             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     1019                DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     1020                   IF ( check_existence( nest_offl%var_names,                                      &
     1021                                         nest_offl%var_names_chem_t(n) ) )  THEN
     1022                      CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),           &
     1023                                         nest_offl%chem_n(0:1,:,1:1,n),                            &
     1024                                         MERGE( nzb+1, 1, bc_dirichlet_n),                         &
     1025                                         MERGE( nest_offl%tind+1, 1, bc_dirichlet_n),              &
     1026                                         MERGE( nest_offl%nzu, 0, bc_dirichlet_n),                 &
     1027                                         MERGE( 2, 0, bc_dirichlet_n) )
     1028                      nest_offl%chem_from_file_n(n) = .TRUE.
     1029                   ENDIF
     1030                ENDDO
     1031             ENDIF
     1032          ENDIF
     1033          IF ( bc_dirichlet_s )  THEN
     1034             CALL get_variable( pids_id, 'ls_forcing_south_u',                                     &
     1035                                nest_offl%u_s(0:1,:,1:1),                                          &
     1036                                MERGE( nzb+1, 1, bc_dirichlet_s),                                  &
     1037                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                       &
     1038                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                          &
     1039                                MERGE( 2, 0, bc_dirichlet_s) )
     1040             CALL get_variable( pids_id, 'ls_forcing_south_v',                                     &
     1041                                nest_offl%v_s(0:1,:,1:1),                                          &
     1042                                MERGE( nzb+1, 1, bc_dirichlet_s),                                  &
     1043                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                       &
     1044                                MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                          &
     1045                                MERGE( 2, 0, bc_dirichlet_s) )
     1046             CALL get_variable( pids_id, 'ls_forcing_south_w',                                     &
     1047                                nest_offl%w_s(0:1,:,1:1),                                          &
     1048                                MERGE( nzb+1, 1, bc_dirichlet_s),                                  &
     1049                                MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                       &
     1050                                MERGE( nest_offl%nzw, 0, bc_dirichlet_s),                          &
     1051                                MERGE( 2, 0, bc_dirichlet_s) )
     1052             IF ( .NOT. neutral )  THEN
     1053                CALL get_variable( pids_id, 'ls_forcing_south_pt',                                 &
     1054                                   nest_offl%pt_s(0:1,:,1:1),                                      &
     1055                                   MERGE( nzb+1, 1, bc_dirichlet_s),                               &
     1056                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                    &
     1057                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                       &
     1058                                   MERGE( 2, 0, bc_dirichlet_s) )
     1059             ENDIF
     1060             IF ( humidity )  THEN
     1061                CALL get_variable( pids_id, 'ls_forcing_south_qv',                                 &
     1062                                   nest_offl%q_s(0:1,:,1:1),                                       &
     1063                                   MERGE( nzb+1, 1, bc_dirichlet_s),                               &
     1064                                   MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),                    &
     1065                                   MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                       &
     1066                                   MERGE( 2, 0, bc_dirichlet_s) )
     1067             ENDIF
     1068             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     1069                DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     1070                   IF ( check_existence( nest_offl%var_names,                                      &
     1071                                         nest_offl%var_names_chem_t(n) ) )  THEN
     1072                      CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),           &
     1073                                         nest_offl%chem_s(0:1,:,1:1,n),                            &
     1074                                         MERGE( nzb+1, 1, bc_dirichlet_s),                         &
     1075                                         MERGE( nest_offl%tind+1, 1, bc_dirichlet_s),              &
     1076                                         MERGE( nest_offl%nzu, 0, bc_dirichlet_s),                 &
     1077                                         MERGE( 2, 0, bc_dirichlet_s) )
     1078                      nest_offl%chem_from_file_s(n) = .TRUE.
     1079                   ENDIF
     1080                ENDDO
     1081             ENDIF
     1082          ENDIF
     1083!
     1084!--       Read top boundary data, which is actually only a scalar value in the LOD 1 case.
     1085          CALL get_variable( pids_id, 'ls_forcing_top_u',                                          &
     1086                             nest_offl%u_top(0:1,1,1),                                             & ! array to be read
     1087                             nest_offl%tind+1,                                                     & ! start index in time
     1088                             2 )                                                                     ! number of elements to be read
     1089          CALL get_variable( pids_id, 'ls_forcing_top_v',                                          &
     1090                             nest_offl%v_top(0:1,1,1),                                             &
     1091                             nest_offl%tind+1,                                                     &
     1092                             2 )
     1093          CALL get_variable( pids_id, 'ls_forcing_top_w',                                          &
     1094                             nest_offl%w_top(0:1,1,1),                                             &
     1095                             nest_offl%tind+1,                                                     &
     1096                             2 )
     1097          IF ( .NOT. neutral )  THEN
     1098             CALL get_variable( pids_id, 'ls_forcing_top_pt',                                      &
     1099                                nest_offl%pt_top(0:1,1,1),                                         &
     1100                                nest_offl%tind+1,                                                  &
     1101                                2 )
     1102          ENDIF
     1103          IF ( humidity )  THEN
     1104             CALL get_variable( pids_id, 'ls_forcing_top_qv',                                      &
     1105                                nest_offl%q_top(0:1,1,1),                                          &
     1106                                nest_offl%tind+1,                                                  &
     1107                                2 )
     1108          ENDIF
     1109          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     1110             DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     1111                IF ( check_existence( nest_offl%var_names,                                         &
     1112                                      nest_offl%var_names_chem_t(n) ) )  THEN
     1113                   CALL get_variable( pids_id, TRIM( nest_offl%var_names_chem_t(n) ),              &
     1114                                      nest_offl%chem_top(0:1,1,1,n),                               &
     1115                                      nest_offl%tind+1,                                            &
     1116                                      2 )
     1117                   nest_offl%chem_from_file_t(n) = .TRUE.
     1118                ENDIF
     1119             ENDDO
     1120          ENDIF
     1121       ENDIF
     1122
    8321123
    8331124!
     
    9671258!> layer.
    9681259!------------------------------------------------------------------------------!
    969     SUBROUTINE nesting_offl_bc                     
     1260    SUBROUTINE nesting_offl_bc
    9701261
    9711262       USE exchange_horiz_mod,                                                    &
     
    9761267       INTEGER(iwp) ::  k !< running index z-direction
    9771268       INTEGER(iwp) ::  n !< running index for chemical species
    978        
     1269
    9791270       REAL(wp), DIMENSION(nzb:nzt+1) ::  pt_ref   !< reference profile for potential temperature
    9801271       REAL(wp), DIMENSION(nzb:nzt+1) ::  pt_ref_l !< reference profile for potential temperature on subdomain
     
    9851276       REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref    !< reference profile for v-component
    9861277       REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref_l  !< reference profile for v-component on subdomain
     1278       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_1d   !< pre-interpolated profile for LOD1 mode
    9871279
    9881280       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ref_chem   !< reference profile for chemical species
     
    9911283       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'start' )
    9921284
    993        CALL  cpu_log( log_point(58), 'offline nesting', 'start' )     
    994 !
    995 !--    Initialize mean profiles, derived from boundary data, to zero
     1285       CALL  cpu_log( log_point(58), 'offline nesting', 'start' )
     1286!
     1287!--    Initialize mean profiles, derived from boundary data, to zero.
    9961288       pt_ref   = 0.0_wp
    9971289       q_ref    = 0.0_wp
     
    10201312!--    boundary_conditions() to restore prognostic values.
    10211313!--    Further, sum up data to calculate mean profiles from boundary data,
    1022 !--    used for Rayleigh damping.
    1023        IF ( bc_dirichlet_l )  THEN
    1024 
    1025           DO  j = nys, nyn
    1026              DO  k = nzb+1, nzt
    1027                 u(k,j,0) = interpolate_in_time( nest_offl%u_left(0,k,j),       &
    1028                                                 nest_offl%u_left(1,k,j),       &
    1029                                                 fac_dt ) *                     &
    1030                              MERGE( 1.0_wp, 0.0_wp,                            &
    1031                                     BTEST( wall_flags_total_0(k,j,0), 1 ) )
    1032                 u(k,j,-1) = u(k,j,0)
    1033              ENDDO
    1034              u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,0)
    1035           ENDDO
    1036 
    1037           DO  j = nys, nyn
    1038              DO  k = nzb+1, nzt-1
    1039                 w(k,j,-1) = interpolate_in_time( nest_offl%w_left(0,k,j),      &
    1040                                                  nest_offl%w_left(1,k,j),      &
    1041                                                  fac_dt ) *                    &
    1042                             MERGE( 1.0_wp, 0.0_wp,                             &
    1043                                    BTEST( wall_flags_total_0(k,j,-1), 3 ) )
    1044              ENDDO
    1045              w(nzt,j,-1) = w(nzt-1,j,-1)
    1046           ENDDO
    1047 
    1048           DO  j = nysv, nyn
    1049              DO  k = nzb+1, nzt
    1050                 v(k,j,-1) = interpolate_in_time( nest_offl%v_left(0,k,j),      &
    1051                                                  nest_offl%v_left(1,k,j),      &
    1052                                                  fac_dt ) *                    &
    1053                                MERGE( 1.0_wp, 0.0_wp,                          &
    1054                                       BTEST( wall_flags_total_0(k,j,-1), 2 ) )
    1055              ENDDO
    1056              v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,-1)
    1057           ENDDO
    1058 
    1059           IF ( .NOT. neutral )  THEN
     1314!--    used for Rayleigh damping.
     1315       IF ( bc_dirichlet_l  )  THEN
     1316!
     1317!--       u-component
     1318          IF ( lod == 2 )  THEN
    10601319             DO  j = nys, nyn
    10611320                DO  k = nzb+1, nzt
    1062                    pt(k,j,-1) = interpolate_in_time( nest_offl%pt_left(0,k,j), &
    1063                                                      nest_offl%pt_left(1,k,j), &
    1064                                                      fac_dt )
    1065  
    1066                 ENDDO
    1067                 pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,-1)
    1068              ENDDO
    1069           ENDIF
    1070 
     1321                   u(k,j,i_bound_u) = interpolate_in_time( nest_offl%u_l(0,k,j),                   &
     1322                                                           nest_offl%u_l(1,k,j),                   &
     1323                                                           fac_dt ) *                              &
     1324                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1325                                             BTEST( wall_flags_total_0(k,j,i_bound_u), 1 ) )
     1326                ENDDO
     1327                u(:,j,i_bound_u-1) = u(:,j,i_bound_u)
     1328                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
     1329             ENDDO
     1330          ELSE
     1331!
     1332!--          Pre-interpolate profile before mapping onto the boundaries.
     1333             DO  k = nzb+1, nzt
     1334                var_1d(k) = interpolate_in_time( nest_offl%u_l(0,k,1),                             &
     1335                                                 nest_offl%u_l(1,k,1),                             &
     1336                                                 fac_dt )
     1337             ENDDO
     1338             DO  j = nys, nyn
     1339                u(nzb+1:nzt,j,i_bound_u) = var_1d(nzb+1:nzt) *                                     &
     1340                                     MERGE( 1.0_wp, 0.0_wp,                                        &
     1341                                            BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound_u), 1 ) )
     1342                u(:,j,i_bound_u-1) = u(:,j,i_bound_u)
     1343                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
     1344             ENDDO
     1345          ENDIF
     1346!
     1347!--       w-component
     1348          IF ( lod == 2 )  THEN
     1349             DO  j = nys, nyn
     1350                DO  k = nzb+1, nzt-1
     1351                   w(k,j,i_bound) = interpolate_in_time( nest_offl%w_l(0,k,j),                     &
     1352                                                         nest_offl%w_l(1,k,j),                     &
     1353                                                         fac_dt ) *                                &
     1354                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1355                                           BTEST( wall_flags_total_0(k,j,i_bound), 3 ) )
     1356                ENDDO
     1357                w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
     1358             ENDDO
     1359          ELSE
     1360             DO  k = nzb+1, nzt-1
     1361                var_1d(k) = interpolate_in_time( nest_offl%w_l(0,k,1),                             &
     1362                                                 nest_offl%w_l(1,k,1),                             &
     1363                                                 fac_dt )
     1364             ENDDO
     1365             DO  j = nys, nyn
     1366                w(nzb+1:nzt-1,j,i_bound) = var_1d(nzb+1:nzt-1) *                                   &
     1367                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1368                                             BTEST( wall_flags_total_0(nzb+1:nzt-1,j,i_bound), 3 ) )
     1369                w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
     1370             ENDDO
     1371          ENDIF
     1372!
     1373!--       v-component
     1374          IF ( lod == 2 )  THEN
     1375             DO  j = nysv, nyn
     1376                DO  k = nzb+1, nzt
     1377                   v(k,j,i_bound) = interpolate_in_time( nest_offl%v_l(0,k,j),                     &
     1378                                                         nest_offl%v_l(1,k,j),                     &
     1379                                                         fac_dt ) *                                &
     1380                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1381                                           BTEST( wall_flags_total_0(k,j,i_bound), 2 ) )
     1382                ENDDO
     1383                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
     1384             ENDDO
     1385          ELSE
     1386             DO  k = nzb+1, nzt
     1387                var_1d(k) = interpolate_in_time( nest_offl%v_l(0,k,1),                             &
     1388                                                 nest_offl%v_l(1,k,1),                             &
     1389                                                 fac_dt )
     1390             ENDDO
     1391             DO  j = nysv, nyn
     1392                v(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt) *                                       &
     1393                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1394                                             BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound), 2 ) )
     1395                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
     1396             ENDDO
     1397          ENDIF
     1398!
     1399!--       potential temperature
     1400          IF ( .NOT. neutral )  THEN
     1401             IF ( lod == 2 )  THEN
     1402                DO  j = nys, nyn
     1403                   DO  k = nzb+1, nzt
     1404                      pt(k,j,i_bound) = interpolate_in_time( nest_offl%pt_l(0,k,j),                &
     1405                                                             nest_offl%pt_l(1,k,j),                &
     1406                                                             fac_dt )
     1407                   ENDDO
     1408                   pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
     1409                ENDDO
     1410             ELSE
     1411                DO  k = nzb+1, nzt
     1412                   var_1d(k) = interpolate_in_time( nest_offl%pt_l(0,k,1),                         &
     1413                                                    nest_offl%pt_l(1,k,1),                         &
     1414                                                    fac_dt )
     1415                ENDDO
     1416                DO  j = nys, nyn
     1417                   pt(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1418                   pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
     1419                ENDDO
     1420             ENDIF
     1421          ENDIF
     1422!
     1423!--       humidity
    10711424          IF ( humidity )  THEN
    1072              DO  j = nys, nyn
     1425             IF ( lod == 2 )  THEN
     1426                DO  j = nys, nyn
     1427                   DO  k = nzb+1, nzt
     1428                      q(k,j,i_bound) = interpolate_in_time( nest_offl%q_l(0,k,j),                  &
     1429                                                            nest_offl%q_l(1,k,j),                  &
     1430                                                            fac_dt )
     1431                   ENDDO
     1432                   q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
     1433                ENDDO
     1434             ELSE
    10731435                DO  k = nzb+1, nzt
    1074                    q(k,j,-1) = interpolate_in_time( nest_offl%q_left(0,k,j),   &
    1075                                                     nest_offl%q_left(1,k,j),   &
     1436                   var_1d(k) = interpolate_in_time( nest_offl%q_l(0,k,1),                          &
     1437                                                    nest_offl%q_l(1,k,1),                          &
    10761438                                                    fac_dt )
    1077  
    1078                 ENDDO
    1079                 q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,-1)
    1080              ENDDO
    1081           ENDIF
    1082 
     1439                ENDDO
     1440                DO  j = nys, nyn
     1441                   q(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1442                   q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
     1443                ENDDO
     1444             ENDIF
     1445          ENDIF
     1446!
     1447!--       chemistry
    10831448          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    10841449             DO  n = 1, UBOUND( chem_species, 1 )
    10851450                IF ( nest_offl%chem_from_file_l(n) )  THEN
    1086                    DO  j = nys, nyn
     1451                   IF ( lod == 2 )  THEN
     1452                      DO  j = nys, nyn
     1453                         DO  k = nzb+1, nzt
     1454                            chem_species(n)%conc(k,j,i_bound) = interpolate_in_time(               &
     1455                                                                        nest_offl%chem_l(0,k,j,n), &
     1456                                                                        nest_offl%chem_l(1,k,j,n), &
     1457                                                                        fac_dt                   )
     1458                         ENDDO
     1459                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1460                                            + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
     1461                      ENDDO
     1462                   ELSE
    10871463                      DO  k = nzb+1, nzt
    1088                          chem_species(n)%conc(k,j,-1) = interpolate_in_time(   &
    1089                                                   nest_offl%chem_left(0,k,j,n),&
    1090                                                   nest_offl%chem_left(1,k,j,n),&
    1091                                                   fac_dt                   )
     1464                         var_1d(k) = interpolate_in_time( nest_offl%chem_l(0,k,1,n),               &
     1465                                                          nest_offl%chem_l(1,k,1,n),               &
     1466                                                          fac_dt )
    10921467                      ENDDO
    1093                       ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)        &
    1094                                          + chem_species(n)%conc(nzb+1:nzt,j,-1)
    1095                    ENDDO
     1468                      DO  j = nys, nyn
     1469                         chem_species(n)%conc(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1470                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1471                                                 + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
     1472                      ENDDO
     1473                   ENDIF
    10961474                ENDIF
    10971475             ENDDO
     
    11001478       ENDIF
    11011479
    1102        IF ( bc_dirichlet_r )  THEN
    1103 
    1104           DO  j = nys, nyn
    1105              DO  k = nzb+1, nzt
    1106                 u(k,j,nxr+1) = interpolate_in_time( nest_offl%u_right(0,k,j),  &
    1107                                                     nest_offl%u_right(1,k,j),  &
    1108                                                     fac_dt ) *                 &
    1109                              MERGE( 1.0_wp, 0.0_wp,                            &
    1110                                     BTEST( wall_flags_total_0(k,j,nxr+1), 1 ) )
    1111              ENDDO
    1112              u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,nxr+1)
    1113           ENDDO
    1114           DO  j = nys, nyn
    1115              DO  k = nzb+1, nzt-1
    1116                 w(k,j,nxr+1) = interpolate_in_time( nest_offl%w_right(0,k,j),  &
    1117                                                     nest_offl%w_right(1,k,j),  &
    1118                                                     fac_dt ) *                 &
    1119                              MERGE( 1.0_wp, 0.0_wp,                            &
    1120                                     BTEST( wall_flags_total_0(k,j,nxr+1), 3 ) )
    1121              ENDDO
    1122              w(nzt,j,nxr+1) = w(nzt-1,j,nxr+1)
    1123           ENDDO
    1124 
    1125           DO  j = nysv, nyn
    1126              DO  k = nzb+1, nzt
    1127                 v(k,j,nxr+1) = interpolate_in_time( nest_offl%v_right(0,k,j),  &
    1128                                                     nest_offl%v_right(1,k,j),  &
    1129                                                     fac_dt ) *                 &
    1130                              MERGE( 1.0_wp, 0.0_wp,                            &
    1131                                     BTEST( wall_flags_total_0(k,j,nxr+1), 2 ) )
    1132              ENDDO
    1133              v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,nxr+1)
    1134           ENDDO
    1135 
    1136           IF ( .NOT. neutral )  THEN
     1480       IF ( bc_dirichlet_r  )  THEN
     1481!
     1482!--       u-component
     1483          IF ( lod == 2 )  THEN
    11371484             DO  j = nys, nyn
    11381485                DO  k = nzb+1, nzt
    1139                    pt(k,j,nxr+1) = interpolate_in_time(                        &
    1140                                                   nest_offl%pt_right(0,k,j),   &
    1141                                                   nest_offl%pt_right(1,k,j),   &
    1142                                                   fac_dt )
    1143                 ENDDO
    1144                 pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,nxr+1)
    1145              ENDDO
    1146           ENDIF
    1147 
     1486                   u(k,j,i_bound_u) = interpolate_in_time( nest_offl%u_r(0,k,j),                   &
     1487                                                           nest_offl%u_r(1,k,j),                   &
     1488                                                           fac_dt ) *                              &
     1489                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1490                                             BTEST( wall_flags_total_0(k,j,i_bound_u), 1 ) )
     1491                ENDDO
     1492                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
     1493             ENDDO
     1494          ELSE
     1495             DO  k = nzb+1, nzt
     1496                var_1d(k) = interpolate_in_time( nest_offl%u_r(0,k,1),                             &
     1497                                                 nest_offl%u_r(1,k,1),                             &
     1498                                                 fac_dt )
     1499             ENDDO
     1500             DO  j = nys, nyn
     1501                u(nzb+1:nzt,j,i_bound_u) = var_1d(nzb+1:nzt) *                                     &
     1502                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1503                                             BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound_u), 1 ) )
     1504                u_ref_l(nzb+1:nzt)       = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j,i_bound_u)
     1505             ENDDO
     1506          ENDIF
     1507!
     1508!--       w-component
     1509          IF ( lod == 2 )  THEN
     1510             DO  j = nys, nyn
     1511                DO  k = nzb+1, nzt-1
     1512                   w(k,j,i_bound) = interpolate_in_time( nest_offl%w_r(0,k,j),                     &
     1513                                                         nest_offl%w_r(1,k,j),                     &
     1514                                                         fac_dt ) *                                &
     1515                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1516                                           BTEST( wall_flags_total_0(k,j,i_bound), 3 ) )
     1517                ENDDO
     1518                w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
     1519             ENDDO
     1520          ELSE
     1521             DO  k = nzb+1, nzt-1
     1522                var_1d(k) = interpolate_in_time( nest_offl%w_r(0,k,1),                             &
     1523                                                 nest_offl%w_r(1,k,1),                             &
     1524                                                 fac_dt )
     1525             ENDDO
     1526             DO  j = nys, nyn
     1527                w(nzb+1:nzt-1,j,i_bound) = var_1d(nzb+1:nzt-1) *                                   &
     1528                                     MERGE( 1.0_wp, 0.0_wp,                                        &
     1529                                            BTEST( wall_flags_total_0(nzb+1:nzt-1,j,i_bound), 3 ) )
     1530                w(nzt,j,i_bound) = w(nzt-1,j,i_bound)
     1531             ENDDO
     1532          ENDIF
     1533!
     1534!--       v-component
     1535          IF ( lod == 2 )  THEN
     1536             DO  j = nysv, nyn
     1537                DO  k = nzb+1, nzt
     1538                   v(k,j,i_bound) = interpolate_in_time( nest_offl%v_r(0,k,j),                     &
     1539                                                         nest_offl%v_r(1,k,j),                     &
     1540                                                         fac_dt ) *                                &
     1541                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1542                                           BTEST( wall_flags_total_0(k,j,i_bound), 2 ) )
     1543                ENDDO
     1544                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
     1545             ENDDO
     1546          ELSE
     1547             DO  k = nzb+1, nzt
     1548                var_1d(k) = interpolate_in_time( nest_offl%v_r(0,k,1),                             &
     1549                                                 nest_offl%v_r(1,k,1),                             &
     1550                                                 fac_dt )
     1551             ENDDO
     1552             DO  j = nysv, nyn
     1553                v(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt) *                                       &
     1554                                       MERGE( 1.0_wp, 0.0_wp,                                      &
     1555                                              BTEST( wall_flags_total_0(nzb+1:nzt,j,i_bound), 2 ) )
     1556                v_ref_l(nzb+1:nzt)     = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j,i_bound)
     1557             ENDDO
     1558          ENDIF
     1559!
     1560!--       potential temperature
     1561          IF ( .NOT. neutral )  THEN
     1562             IF ( lod == 2 )  THEN
     1563                DO  j = nys, nyn
     1564                   DO  k = nzb+1, nzt
     1565                      pt(k,j,i_bound) = interpolate_in_time( nest_offl%pt_r(0,k,j),                &
     1566                                                             nest_offl%pt_r(1,k,j),                &
     1567                                                             fac_dt )
     1568                   ENDDO
     1569                   pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
     1570                ENDDO
     1571             ELSE
     1572                DO  k = nzb+1, nzt
     1573                   var_1d(k) = interpolate_in_time( nest_offl%pt_r(0,k,1),                         &
     1574                                                    nest_offl%pt_r(1,k,1),                         &
     1575                                                    fac_dt )
     1576                ENDDO
     1577                DO  j = nys, nyn
     1578                   pt(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1579                   pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j,i_bound)
     1580                ENDDO
     1581             ENDIF
     1582          ENDIF
     1583!
     1584!--       humidity
    11481585          IF ( humidity )  THEN
    1149              DO  j = nys, nyn
     1586             IF ( lod == 2 )  THEN
     1587                DO  j = nys, nyn
     1588                   DO  k = nzb+1, nzt
     1589                      q(k,j,i_bound) = interpolate_in_time( nest_offl%q_r(0,k,j),                  &
     1590                                                            nest_offl%q_r(1,k,j),                  &
     1591                                                            fac_dt )
     1592                   ENDDO
     1593                   q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
     1594                ENDDO
     1595             ELSE
    11501596                DO  k = nzb+1, nzt
    1151                    q(k,j,nxr+1) = interpolate_in_time(                         &
    1152                                                   nest_offl%q_right(0,k,j),    &
    1153                                                   nest_offl%q_right(1,k,j),    &
    1154                                                   fac_dt )
    1155  
    1156                 ENDDO
    1157                 q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,nxr+1)
    1158              ENDDO
    1159           ENDIF
    1160 
     1597                   var_1d(k) = interpolate_in_time( nest_offl%q_r(0,k,1),                          &
     1598                                                    nest_offl%q_r(1,k,1),                          &
     1599                                                    fac_dt )
     1600                ENDDO
     1601                DO  j = nys, nyn
     1602                   q(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1603                   q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j,i_bound)
     1604                ENDDO
     1605             ENDIF
     1606          ENDIF
     1607!
     1608!--       chemistry
    11611609          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    11621610             DO  n = 1, UBOUND( chem_species, 1 )
    11631611                IF ( nest_offl%chem_from_file_r(n) )  THEN
    1164                    DO  j = nys, nyn
     1612                   IF ( lod == 2 )  THEN
     1613                      DO  j = nys, nyn
     1614                         DO  k = nzb+1, nzt
     1615                            chem_species(n)%conc(k,j,i_bound) = interpolate_in_time(               &
     1616                                                                        nest_offl%chem_r(0,k,j,n), &
     1617                                                                        nest_offl%chem_r(1,k,j,n), &
     1618                                                                        fac_dt                   )
     1619                         ENDDO
     1620                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1621                                            + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
     1622                      ENDDO
     1623                   ELSE
    11651624                      DO  k = nzb+1, nzt
    1166                          chem_species(n)%conc(k,j,nxr+1) = interpolate_in_time(&
    1167                                                  nest_offl%chem_right(0,k,j,n),&
    1168                                                  nest_offl%chem_right(1,k,j,n),&
    1169                                                  fac_dt                       )
     1625                         var_1d(k) = interpolate_in_time( nest_offl%chem_r(0,k,1,n),               &
     1626                                                          nest_offl%chem_r(1,k,1,n),               &
     1627                                                          fac_dt )
    11701628                      ENDDO
    1171                       ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)        &
    1172                                        + chem_species(n)%conc(nzb+1:nzt,j,nxr+1)
    1173                    ENDDO
     1629                      DO  j = nys, nyn
     1630                         chem_species(n)%conc(nzb+1:nzt,j,i_bound) = var_1d(nzb+1:nzt)
     1631                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1632                                                 + chem_species(n)%conc(nzb+1:nzt,j,i_bound)
     1633                      ENDDO
     1634                   ENDIF
    11741635                ENDIF
    11751636             ENDDO
     
    11781639       ENDIF
    11791640
    1180        IF ( bc_dirichlet_s )  THEN
    1181 
    1182           DO  i = nxl, nxr
    1183              DO  k = nzb+1, nzt
    1184                 v(k,0,i) = interpolate_in_time( nest_offl%v_south(0,k,i),      &
    1185                                                 nest_offl%v_south(1,k,i),      &
    1186                                                 fac_dt ) *                     &
    1187                            MERGE( 1.0_wp, 0.0_wp,                              &
    1188                                   BTEST( wall_flags_total_0(k,0,i), 2 ) )
    1189                 v(k,-1,i) = v(k,0,i)
    1190              ENDDO
    1191              v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,0,i)
    1192           ENDDO
    1193 
    1194           DO  i = nxl, nxr
    1195              DO  k = nzb+1, nzt-1
    1196                 w(k,-1,i) = interpolate_in_time( nest_offl%w_south(0,k,i),     &
    1197                                                  nest_offl%w_south(1,k,i),     &
    1198                                                  fac_dt ) *                    &
    1199                            MERGE( 1.0_wp, 0.0_wp,                              &
    1200                                   BTEST( wall_flags_total_0(k,-1,i), 3 ) )
    1201              ENDDO
    1202              w(nzt,-1,i) = w(nzt-1,-1,i)
    1203           ENDDO
    1204 
    1205           DO  i = nxlu, nxr
    1206              DO  k = nzb+1, nzt
    1207                 u(k,-1,i) = interpolate_in_time( nest_offl%u_south(0,k,i),     &
    1208                                                  nest_offl%u_south(1,k,i),     &
    1209                                                  fac_dt ) *                    &
    1210                            MERGE( 1.0_wp, 0.0_wp,                              &
    1211                                   BTEST( wall_flags_total_0(k,-1,i), 1 ) )
    1212              ENDDO
    1213              u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,-1,i)
    1214           ENDDO
    1215 
    1216           IF ( .NOT. neutral )  THEN
     1641       IF ( bc_dirichlet_n )  THEN
     1642!
     1643!--       v-component
     1644          IF ( lod == 2 )  THEN
    12171645             DO  i = nxl, nxr
    12181646                DO  k = nzb+1, nzt
    1219                    pt(k,-1,i) = interpolate_in_time(                           &
    1220                                                  nest_offl%pt_south(0,k,i),    &
    1221                                                  nest_offl%pt_south(1,k,i),    &
     1647                   v(k,j_bound_v,i) = interpolate_in_time( nest_offl%v_n(0,k,i),                   &
     1648                                                           nest_offl%v_n(1,k,i),                   &
     1649                                                           fac_dt ) *                              &
     1650                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1651                                             BTEST( wall_flags_total_0(k,j_bound_v,i), 2 ) )
     1652                ENDDO
     1653                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
     1654             ENDDO
     1655          ELSE
     1656             DO  k = nzb+1, nzt
     1657                var_1d(k) = interpolate_in_time( nest_offl%v_n(0,k,1),                             &
     1658                                                 nest_offl%v_n(1,k,1),                             &
    12221659                                                 fac_dt )
    1223  
    1224                 ENDDO
    1225                 pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,-1,i)
    1226              ENDDO
    1227           ENDIF
    1228 
     1660             ENDDO
     1661             DO  i = nxl, nxr
     1662                v(nzb+1:nzt,j_bound_v,i) = var_1d(nzb+1:nzt) *                                     &
     1663                                     MERGE( 1.0_wp, 0.0_wp,                                        &
     1664                                            BTEST( wall_flags_total_0(nzb+1:nzt,j_bound_v,i), 2 ) )
     1665                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
     1666             ENDDO
     1667          ENDIF
     1668!
     1669!--       w-component
     1670          IF ( lod == 2 )  THEN
     1671             DO  i = nxl, nxr
     1672                DO  k = nzb+1, nzt-1
     1673                   w(k,j_bound,i) = interpolate_in_time( nest_offl%w_n(0,k,i),                     &
     1674                                                         nest_offl%w_n(1,k,i),                     &
     1675                                                         fac_dt ) *                                &
     1676                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1677                                           BTEST( wall_flags_total_0(k,j_bound,i), 3 ) )
     1678                ENDDO
     1679                w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
     1680             ENDDO
     1681          ELSE
     1682             DO  k = nzb+1, nzt-1
     1683                var_1d(k) = interpolate_in_time( nest_offl%w_n(0,k,1),                             &
     1684                                                 nest_offl%w_n(1,k,1),                             &
     1685                                                 fac_dt )
     1686             ENDDO
     1687             DO  i = nxl, nxr
     1688                w(nzb+1:nzt-1,j_bound,i) = var_1d(nzb+1:nzt-1) *                                   &
     1689                                     MERGE( 1.0_wp, 0.0_wp,                                        &
     1690                                            BTEST( wall_flags_total_0(nzb+1:nzt-1,j_bound,i), 3 ) )
     1691                w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
     1692             ENDDO
     1693          ENDIF
     1694!
     1695!--       u-component
     1696          IF ( lod == 2 )  THEN
     1697             DO  i = nxlu, nxr
     1698                DO  k = nzb+1, nzt
     1699                   u(k,j_bound,i) = interpolate_in_time( nest_offl%u_n(0,k,i),                     &
     1700                                                         nest_offl%u_n(1,k,i),                     &
     1701                                                         fac_dt ) *                                &
     1702                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1703                                           BTEST( wall_flags_total_0(k,j_bound,i), 1 ) )
     1704                ENDDO
     1705                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
     1706             ENDDO
     1707          ELSE
     1708             DO  k = nzb+1, nzt
     1709                var_1d(k) = interpolate_in_time( nest_offl%u_n(0,k,1),                             &
     1710                                                 nest_offl%u_n(1,k,1),                             &
     1711                                                 fac_dt )
     1712             ENDDO
     1713             DO  i = nxlu, nxr
     1714                u(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt) *                                       &
     1715                                       MERGE( 1.0_wp, 0.0_wp,                                      &
     1716                                              BTEST( wall_flags_total_0(nzb+1:nzt,j_bound,i), 1 ) )
     1717                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
     1718             ENDDO
     1719          ENDIF
     1720!
     1721!--       potential temperature
     1722          IF ( .NOT. neutral )  THEN
     1723             IF ( lod == 2 )  THEN
     1724                DO  i = nxl, nxr
     1725                   DO  k = nzb+1, nzt
     1726                      pt(k,j_bound,i) = interpolate_in_time( nest_offl%pt_n(0,k,i),                &
     1727                                                             nest_offl%pt_n(1,k,i),                &
     1728                                                             fac_dt )
     1729                   ENDDO
     1730                   pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
     1731                ENDDO
     1732             ELSE
     1733                DO  k = nzb+1, nzt
     1734                   var_1d(k) = interpolate_in_time( nest_offl%pt_n(0,k,1),                         &
     1735                                                    nest_offl%pt_n(1,k,1),                         &
     1736                                                    fac_dt )
     1737                ENDDO
     1738                DO  i = nxl, nxr
     1739                   pt(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1740                   pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
     1741                ENDDO
     1742             ENDIF
     1743          ENDIF
     1744!
     1745!--       humidity
    12291746          IF ( humidity )  THEN
     1747             IF ( lod == 2 )  THEN
     1748                DO  i = nxl, nxr
     1749                   DO  k = nzb+1, nzt
     1750                      q(k,j_bound,i) = interpolate_in_time( nest_offl%q_n(0,k,i),                  &
     1751                                                            nest_offl%q_n(1,k,i),                  &
     1752                                                            fac_dt )
     1753                   ENDDO
     1754                   q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
     1755                ENDDO
     1756             ELSE
     1757                DO  k = nzb+1, nzt
     1758                   var_1d(k) = interpolate_in_time( nest_offl%q_n(0,k,1),                          &
     1759                                                    nest_offl%q_n(1,k,1),                          &
     1760                                                    fac_dt )
     1761                ENDDO
     1762                DO  i = nxl, nxr
     1763                   q(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1764                   q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
     1765                ENDDO
     1766             ENDIF
     1767          ENDIF
     1768!
     1769!--       chemistry
     1770          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     1771             DO  n = 1, UBOUND( chem_species, 1 )
     1772                IF ( nest_offl%chem_from_file_n(n) )  THEN
     1773                   IF ( lod == 2 )  THEN
     1774                      DO  i = nxl, nxr
     1775                         DO  k = nzb+1, nzt
     1776                            chem_species(n)%conc(k,j_bound,i) = interpolate_in_time(               &
     1777                                                                        nest_offl%chem_n(0,k,i,n), &
     1778                                                                        nest_offl%chem_n(1,k,i,n), &
     1779                                                                        fac_dt                    )
     1780                         ENDDO
     1781                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1782                                          + chem_species(n)%conc(nzb+1:nzt,j_bound,i)
     1783                      ENDDO
     1784                   ELSE
     1785                      DO  k = nzb+1, nzt
     1786                         var_1d(k) = interpolate_in_time( nest_offl%chem_n(0,k,1,n),               &
     1787                                                          nest_offl%chem_n(1,k,1,n),               &
     1788                                                          fac_dt )
     1789                      ENDDO
     1790                      DO  i = nxl, nxr
     1791                         chem_species(n)%conc(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1792                         ref_chem_l(nzb+1:nzt,n)                   = ref_chem_l(nzb+1:nzt,n) +     &
     1793                                                                     chem_species(n)%conc(nzb+1:nzt,j_bound,i)
     1794                      ENDDO
     1795                   ENDIF
     1796                ENDIF
     1797             ENDDO
     1798          ENDIF
     1799       ENDIF
     1800
     1801       IF ( bc_dirichlet_s )  THEN
     1802!
     1803!--       v-component
     1804          IF ( lod == 2 )  THEN
    12301805             DO  i = nxl, nxr
    12311806                DO  k = nzb+1, nzt
    1232                    q(k,-1,i) = interpolate_in_time(                            &
    1233                                                  nest_offl%q_south(0,k,i),     &
    1234                                                  nest_offl%q_south(1,k,i),     &
     1807                   v(k,j_bound_v,i) = interpolate_in_time( nest_offl%v_s(0,k,i),                   &
     1808                                                           nest_offl%v_s(1,k,i),                   &
     1809                                                           fac_dt ) *                              &
     1810                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1811                                             BTEST( wall_flags_total_0(k,j_bound_v,i), 2 ) )
     1812                ENDDO
     1813                v(:,j_bound_v-1,i) = v(:,j_bound_v,i)
     1814                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
     1815             ENDDO
     1816          ELSE
     1817             DO  k = nzb+1, nzt
     1818                var_1d(k) = interpolate_in_time( nest_offl%v_s(0,k,1),                             &
     1819                                                 nest_offl%v_s(1,k,1),                             &
    12351820                                                 fac_dt )
    1236  
    1237                 ENDDO
    1238                 q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,-1,i)
    1239              ENDDO
    1240           ENDIF
    1241 
     1821             ENDDO
     1822             DO  i = nxl, nxr
     1823                v(nzb+1:nzt,j_bound_v,i) = var_1d(nzb+1:nzt) *                                     &
     1824                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1825                                             BTEST( wall_flags_total_0(nzb+1:nzt,j_bound_v,i), 2 ) )
     1826                v(:,j_bound_v-1,i) = v(:,j_bound_v,i)
     1827                v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,j_bound_v,i)
     1828             ENDDO
     1829          ENDIF
     1830!
     1831!--       w-component
     1832          IF ( lod == 2 )  THEN
     1833             DO  i = nxl, nxr
     1834                DO  k = nzb+1, nzt-1
     1835                   w(k,j_bound,i) = interpolate_in_time( nest_offl%w_s(0,k,i),                     &
     1836                                                         nest_offl%w_s(1,k,i),                     &
     1837                                                         fac_dt ) *                                &
     1838                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1839                                           BTEST( wall_flags_total_0(k,j_bound,i), 3 ) )
     1840                ENDDO
     1841                w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
     1842             ENDDO
     1843          ELSE
     1844             DO  k = nzb+1, nzt-1
     1845                var_1d(k) = interpolate_in_time( nest_offl%w_s(0,k,1),                             &
     1846                                                 nest_offl%w_s(1,k,1),                             &
     1847                                                 fac_dt )
     1848             ENDDO
     1849             DO  i = nxl, nxr
     1850                w(nzb+1:nzt-1,j_bound,i) = var_1d(nzb+1:nzt-1) *                                   &
     1851                                     MERGE( 1.0_wp, 0.0_wp,                                        &
     1852                                            BTEST( wall_flags_total_0(nzb+1:nzt-1,j_bound,i), 3 ) )
     1853                w(nzt,j_bound,i) = w(nzt-1,j_bound,i)
     1854             ENDDO
     1855          ENDIF
     1856!
     1857!--       u-component
     1858          IF ( lod == 2 )  THEN
     1859             DO  i = nxlu, nxr
     1860                DO  k = nzb+1, nzt
     1861                   u(k,j_bound,i) = interpolate_in_time( nest_offl%u_s(0,k,i),                     &
     1862                                                         nest_offl%u_s(1,k,i),                     &
     1863                                                         fac_dt ) *                                &
     1864                                    MERGE( 1.0_wp, 0.0_wp,                                         &
     1865                                           BTEST( wall_flags_total_0(k,j_bound,i), 1 ) )
     1866                ENDDO
     1867                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
     1868             ENDDO
     1869          ELSE
     1870             DO  k = nzb+1, nzt
     1871                var_1d(k) = interpolate_in_time( nest_offl%u_s(0,k,1),                             &
     1872                                                 nest_offl%u_s(1,k,1),                             &
     1873                                                 fac_dt )
     1874             ENDDO
     1875             DO  i = nxlu, nxr
     1876                u(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt) *                                       &
     1877                                       MERGE( 1.0_wp, 0.0_wp,                                      &
     1878                                              BTEST( wall_flags_total_0(nzb+1:nzt,j_bound,i), 1 ) )
     1879                u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,j_bound,i)
     1880             ENDDO
     1881          ENDIF
     1882!
     1883!--       potential temperature
     1884          IF ( .NOT. neutral )  THEN
     1885             IF ( lod == 2 )  THEN
     1886                DO  i = nxl, nxr
     1887                   DO  k = nzb+1, nzt
     1888                      pt(k,j_bound,i) = interpolate_in_time( nest_offl%pt_s(0,k,i),                &
     1889                                                             nest_offl%pt_s(1,k,i),                &
     1890                                                             fac_dt )
     1891                   ENDDO
     1892                   pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
     1893                ENDDO
     1894             ELSE
     1895                DO  k = nzb+1, nzt
     1896                   var_1d(k) = interpolate_in_time( nest_offl%pt_s(0,k,1),                         &
     1897                                                    nest_offl%pt_s(1,k,1),                         &
     1898                                                    fac_dt )
     1899                ENDDO
     1900                DO  i = nxl, nxr
     1901                   pt(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1902                   pt_ref_l(nzb+1:nzt)     = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,j_bound,i)
     1903                ENDDO
     1904             ENDIF
     1905          ENDIF
     1906!
     1907!--       humidity
     1908          IF ( humidity )  THEN
     1909             IF ( lod == 2 )  THEN
     1910                DO  i = nxl, nxr
     1911                   DO  k = nzb+1, nzt
     1912                      q(k,j_bound,i) = interpolate_in_time( nest_offl%q_s(0,k,i),                  &
     1913                                                            nest_offl%q_s(1,k,i),                  &
     1914                                                            fac_dt )
     1915                   ENDDO
     1916                   q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
     1917                ENDDO
     1918             ELSE
     1919                DO  k = nzb+1, nzt
     1920                   var_1d(k) = interpolate_in_time( nest_offl%q_s(0,k,1),                          &
     1921                                                    nest_offl%q_s(1,k,1),                          &
     1922                                                    fac_dt )
     1923                ENDDO
     1924                DO  i = nxl, nxr
     1925                   q(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1926                   q_ref_l(nzb+1:nzt)     = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,j_bound,i)
     1927                ENDDO
     1928             ENDIF
     1929          ENDIF
     1930!
     1931!--       chemistry
    12421932          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    12431933             DO  n = 1, UBOUND( chem_species, 1 )
    12441934                IF ( nest_offl%chem_from_file_s(n) )  THEN
    1245                    DO  i = nxl, nxr
     1935                   IF ( lod == 2 )  THEN
     1936                      DO  i = nxl, nxr
     1937                         DO  k = nzb+1, nzt
     1938                            chem_species(n)%conc(k,j_bound,i) = interpolate_in_time(               &
     1939                                                                        nest_offl%chem_s(0,k,i,n), &
     1940                                                                        nest_offl%chem_s(1,k,i,n), &
     1941                                                                        fac_dt                    )
     1942                         ENDDO
     1943                         ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)                         &
     1944                                          + chem_species(n)%conc(nzb+1:nzt,j_bound,i)
     1945                      ENDDO
     1946                   ELSE
    12461947                      DO  k = nzb+1, nzt
    1247                          chem_species(n)%conc(k,-1,i) = interpolate_in_time(   &
    1248                                                  nest_offl%chem_south(0,k,i,n),&
    1249                                                  nest_offl%chem_south(1,k,i,n),&
    1250                                                  fac_dt                    )
     1948                         var_1d(k) = interpolate_in_time( nest_offl%chem_s(0,k,1,n),               &
     1949                                                          nest_offl%chem_s(1,k,1,n),               &
     1950                                                          fac_dt )
    12511951                      ENDDO
    1252                       ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)        &
    1253                                        + chem_species(n)%conc(nzb+1:nzt,-1,i)
    1254                    ENDDO
     1952                      DO  i = nxl, nxr
     1953                         chem_species(n)%conc(nzb+1:nzt,j_bound,i) = var_1d(nzb+1:nzt)
     1954                         ref_chem_l(nzb+1:nzt,n)                   = ref_chem_l(nzb+1:nzt,n) +     &
     1955                                                                     chem_species(n)%conc(nzb+1:nzt,j_bound,i)
     1956                      ENDDO
     1957                   ENDIF
    12551958                ENDIF
    12561959             ENDDO
    12571960          ENDIF
    1258 
    1259        ENDIF
    1260 
    1261        IF ( bc_dirichlet_n )  THEN
    1262 
    1263           DO  i = nxl, nxr
    1264              DO  k = nzb+1, nzt
    1265                 v(k,nyn+1,i) = interpolate_in_time( nest_offl%v_north(0,k,i),  &
    1266                                                     nest_offl%v_north(1,k,i),  &
    1267                                                     fac_dt ) *                 &
    1268                                MERGE( 1.0_wp, 0.0_wp,                          &
    1269                                     BTEST( wall_flags_total_0(k,nyn+1,i), 2 ) )
    1270              ENDDO
    1271              v_ref_l(nzb+1:nzt) = v_ref_l(nzb+1:nzt) + v(nzb+1:nzt,nyn+1,i)
     1961       ENDIF
     1962!
     1963!--    Top boundary
     1964!--    u-component
     1965       IF ( lod == 2 )  THEN
     1966          DO  i = nxlu, nxr
     1967             DO  j = nys, nyn
     1968                u(nzt+1,j,i) = interpolate_in_time( nest_offl%u_top(0,j,i),                        &
     1969                                                    nest_offl%u_top(1,j,i),                        &
     1970                                                    fac_dt ) *                                     &
     1971                              MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt+1,j,i), 1 ) )
     1972                u_ref_l(nzt+1) = u_ref_l(nzt+1) + u(nzt+1,j,i)
     1973             ENDDO
    12721974          ENDDO
    1273           DO  i = nxl, nxr
    1274              DO  k = nzb+1, nzt-1
    1275                 w(k,nyn+1,i) = interpolate_in_time( nest_offl%w_north(0,k,i),  &
    1276                                                     nest_offl%w_north(1,k,i),  &
    1277                                                     fac_dt ) *                 &
    1278                                MERGE( 1.0_wp, 0.0_wp,                          &
    1279                                     BTEST( wall_flags_total_0(k,nyn+1,i), 3 ) )
    1280              ENDDO
    1281              w(nzt,nyn+1,i) = w(nzt-1,nyn+1,i)
    1282           ENDDO
    1283 
    1284           DO  i = nxlu, nxr
    1285              DO  k = nzb+1, nzt
    1286                 u(k,nyn+1,i) = interpolate_in_time( nest_offl%u_north(0,k,i),  &
    1287                                                     nest_offl%u_north(1,k,i),  &
    1288                                                     fac_dt ) *                 &
    1289                                MERGE( 1.0_wp, 0.0_wp,                          &
    1290                                     BTEST( wall_flags_total_0(k,nyn+1,i), 1 ) )
    1291 
    1292              ENDDO
    1293              u_ref_l(nzb+1:nzt) = u_ref_l(nzb+1:nzt) + u(nzb+1:nzt,nyn+1,i)
    1294           ENDDO
    1295 
    1296           IF ( .NOT. neutral )  THEN
    1297              DO  i = nxl, nxr
    1298                 DO  k = nzb+1, nzt
    1299                    pt(k,nyn+1,i) = interpolate_in_time(                        &
    1300                                                     nest_offl%pt_north(0,k,i), &
    1301                                                     nest_offl%pt_north(1,k,i), &
    1302                                                     fac_dt )
    1303  
    1304                 ENDDO
    1305                 pt_ref_l(nzb+1:nzt) = pt_ref_l(nzb+1:nzt) + pt(nzb+1:nzt,nyn+1,i)
    1306              ENDDO
    1307           ENDIF
    1308 
    1309           IF ( humidity )  THEN
    1310              DO  i = nxl, nxr
    1311                 DO  k = nzb+1, nzt
    1312                    q(k,nyn+1,i) = interpolate_in_time(                         &
    1313                                                     nest_offl%q_north(0,k,i),  &
    1314                                                     nest_offl%q_north(1,k,i),  &
    1315                                                     fac_dt )
    1316  
    1317                 ENDDO
    1318                 q_ref_l(nzb+1:nzt) = q_ref_l(nzb+1:nzt) + q(nzb+1:nzt,nyn+1,i)
    1319              ENDDO
    1320           ENDIF
    1321 
    1322           IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    1323              DO  n = 1, UBOUND( chem_species, 1 )
    1324                 IF ( nest_offl%chem_from_file_n(n) )  THEN
    1325                    DO  i = nxl, nxr
    1326                       DO  k = nzb+1, nzt
    1327                          chem_species(n)%conc(k,nyn+1,i) = interpolate_in_time(&
    1328                                                  nest_offl%chem_north(0,k,i,n),&
    1329                                                  nest_offl%chem_north(1,k,i,n),&
    1330                                                  fac_dt                       )
    1331                       ENDDO
    1332                       ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n)        &
    1333                                        + chem_species(n)%conc(nzb+1:nzt,nyn+1,i)
    1334                    ENDDO
    1335                 ENDIF
    1336              ENDDO
    1337           ENDIF
    1338 
    1339        ENDIF
    1340 !
    1341 !--    Top boundary
    1342        DO  i = nxlu, nxr
    1343           DO  j = nys, nyn
    1344              u(nzt+1,j,i) = interpolate_in_time( nest_offl%u_top(0,j,i),       &
    1345                                                  nest_offl%u_top(1,j,i),       &
    1346                                                  fac_dt ) *                    &
    1347                            MERGE( 1.0_wp, 0.0_wp,                              &
    1348                                   BTEST( wall_flags_total_0(nzt+1,j,i), 1 ) )
    1349              u_ref_l(nzt+1) = u_ref_l(nzt+1) + u(nzt+1,j,i)
    1350           ENDDO
    1351        ENDDO
     1975       ELSE
     1976          var_1d(nzt+1) = interpolate_in_time( nest_offl%u_top(0,1,1),                             &
     1977                                               nest_offl%u_top(1,1,1),                             &
     1978                                               fac_dt )
     1979          u(nzt+1,nys:nyn,nxlu:nxr) = var_1d(nzt+1) *                                              &
     1980                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     1981                                             BTEST( wall_flags_total_0(nzt+1,nys:nyn,nxlu:nxr), 1 ) )
     1982          u_ref_l(nzt+1) = u_ref_l(nzt+1) + SUM( u(nzt+1,nys:nyn,nxlu:nxr) )
     1983       ENDIF
    13521984!
    13531985!--    For left boundary set boundary condition for u-component also at top
     
    13551987!--    Note, this has no effect on the numeric solution, only for data output.
    13561988       IF ( bc_dirichlet_l )  u(nzt+1,:,nxl) = u(nzt+1,:,nxlu)
    1357 
    1358        DO  i = nxl, nxr
    1359           DO  j = nysv, nyn
    1360              v(nzt+1,j,i) = interpolate_in_time( nest_offl%v_top(0,j,i),       &
    1361                                                  nest_offl%v_top(1,j,i),       &
    1362                                                  fac_dt ) *                    &
    1363                            MERGE( 1.0_wp, 0.0_wp,                              &
    1364                                   BTEST( wall_flags_total_0(nzt+1,j,i), 2 ) )
    1365              v_ref_l(nzt+1) = v_ref_l(nzt+1) + v(nzt+1,j,i)
     1989!
     1990!--    v-component
     1991       IF ( lod == 2 )  THEN
     1992          DO  i = nxl, nxr
     1993             DO  j = nysv, nyn
     1994                v(nzt+1,j,i) = interpolate_in_time( nest_offl%v_top(0,j,i),                        &
     1995                                                    nest_offl%v_top(1,j,i),                        &
     1996                                                    fac_dt ) *                                     &
     1997                              MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt+1,j,i), 2 ) )
     1998                v_ref_l(nzt+1) = v_ref_l(nzt+1) + v(nzt+1,j,i)
     1999             ENDDO
    13662000          ENDDO
    1367        ENDDO
     2001       ELSE
     2002          var_1d(nzt+1) = interpolate_in_time( nest_offl%v_top(0,1,1),                             &
     2003                                               nest_offl%v_top(1,1,1),                             &
     2004                                               fac_dt )
     2005          v(nzt+1,nysv:nyn,nxl:nxr) = var_1d(nzt+1) *                                              &
     2006                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     2007                                             BTEST( wall_flags_total_0(nzt+1,nysv:nyn,nxl:nxr), 2 ) )
     2008          v_ref_l(nzt+1) = v_ref_l(nzt+1) + SUM( v(nzt+1,nysv:nyn,nxl:nxr) )
     2009       ENDIF
    13682010!
    13692011!--    For south boundary set boundary condition for v-component also at top
     
    13712013!--    Note, this has no effect on the numeric solution, only for data output.
    13722014       IF ( bc_dirichlet_s )  v(nzt+1,nys,:) = v(nzt+1,nysv,:)
    1373 
    1374        DO  i = nxl, nxr
    1375           DO  j = nys, nyn
    1376              w(nzt,j,i) = interpolate_in_time( nest_offl%w_top(0,j,i),         &
    1377                                                nest_offl%w_top(1,j,i),         &
    1378                                                fac_dt ) *                      &
    1379                            MERGE( 1.0_wp, 0.0_wp,                              &
    1380                                   BTEST( wall_flags_total_0(nzt,j,i), 3 ) )
    1381              w(nzt+1,j,i) = w(nzt,j,i)
    1382           ENDDO
    1383        ENDDO
    1384 
    1385 
    1386        IF ( .NOT. neutral )  THEN
     2015!
     2016!--    w-component
     2017       IF ( lod == 2 )  THEN
    13872018          DO  i = nxl, nxr
    13882019             DO  j = nys, nyn
    1389                 pt(nzt+1,j,i) = interpolate_in_time( nest_offl%pt_top(0,j,i),  &
    1390                                                      nest_offl%pt_top(1,j,i),  &
    1391                                                      fac_dt )
    1392                 pt_ref_l(nzt+1) = pt_ref_l(nzt+1) + pt(nzt+1,j,i)
     2020                w(nzt,j,i) = interpolate_in_time( nest_offl%w_top(0,j,i),                          &
     2021                                                  nest_offl%w_top(1,j,i),                          &
     2022                                                  fac_dt ) *                                       &
     2023                              MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(nzt,j,i), 3 ) )
     2024                w(nzt+1,j,i) = w(nzt,j,i)
    13932025             ENDDO
    13942026          ENDDO
    1395        ENDIF
    1396 
     2027       ELSE
     2028          var_1d(nzt) = interpolate_in_time( nest_offl%w_top(0,1,1),                               &
     2029                                             nest_offl%w_top(1,1,1),                               &
     2030                                             fac_dt )
     2031          w(nzt,nys:nyn,nxl:nxr) = var_1d(nzt) *                                                   &
     2032                                      MERGE( 1.0_wp, 0.0_wp,                                       &
     2033                                             BTEST( wall_flags_total_0(nzt,nys:nyn,nxl:nxr), 3 ) )
     2034          w(nzt+1,nys:nyn,nxl:nxr) = w(nzt,nys:nyn,nxl:nxr)
     2035       ENDIF
     2036!
     2037!--    potential temperture
     2038       IF ( .NOT. neutral )  THEN
     2039          IF ( lod == 2 )  THEN
     2040             DO  i = nxl, nxr
     2041                DO  j = nys, nyn
     2042                   pt(nzt+1,j,i) = interpolate_in_time( nest_offl%pt_top(0,j,i),                   &
     2043                                                        nest_offl%pt_top(1,j,i),                   &
     2044                                                        fac_dt )
     2045                   pt_ref_l(nzt+1) = pt_ref_l(nzt+1) + pt(nzt+1,j,i)
     2046                ENDDO
     2047             ENDDO
     2048          ELSE
     2049             var_1d(nzt+1) = interpolate_in_time( nest_offl%pt_top(0,1,1),                         &
     2050                                                  nest_offl%pt_top(1,1,1),                         &
     2051                                                  fac_dt )
     2052             pt(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
     2053             pt_ref_l(nzt+1) = pt_ref_l(nzt+1) + SUM( pt(nzt+1,nys:nyn,nxl:nxr) )
     2054          ENDIF
     2055       ENDIF
     2056!
     2057!--    humidity
    13972058       IF ( humidity )  THEN
    1398           DO  i = nxl, nxr
    1399              DO  j = nys, nyn
    1400                 q(nzt+1,j,i) = interpolate_in_time( nest_offl%q_top(0,j,i),    &
    1401                                                     nest_offl%q_top(1,j,i),    &
    1402                                                     fac_dt )
    1403                 q_ref_l(nzt+1) = q_ref_l(nzt+1) + q(nzt+1,j,i)
    1404              ENDDO
    1405           ENDDO
     2059          IF ( lod == 2 )  THEN
     2060             DO  i = nxl, nxr
     2061                DO  j = nys, nyn
     2062                   q(nzt+1,j,i) = interpolate_in_time( nest_offl%q_top(0,j,i),                     &
     2063                                                       nest_offl%q_top(1,j,i),                     &
     2064                                                       fac_dt )
     2065                   q_ref_l(nzt+1) = q_ref_l(nzt+1) + q(nzt+1,j,i)
     2066                ENDDO
     2067             ENDDO
     2068          ELSE
     2069             var_1d(nzt+1) = interpolate_in_time( nest_offl%q_top(0,1,1),                          &
     2070                                                  nest_offl%q_top(1,1,1),                          &
     2071                                                  fac_dt )
     2072             q(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
     2073             q_ref_l(nzt+1) = q_ref_l(nzt+1) + SUM( q(nzt+1,nys:nyn,nxl:nxr) )
     2074          ENDIF
    14062075       ENDIF
    14072076
     
    14092078          DO  n = 1, UBOUND( chem_species, 1 )
    14102079             IF ( nest_offl%chem_from_file_t(n) )  THEN
    1411                 DO  i = nxl, nxr
    1412                    DO  j = nys, nyn
    1413                       chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time(   &
    1414                                               nest_offl%chem_top(0,j,i,n),     &
    1415                                               nest_offl%chem_top(1,j,i,n),     &
    1416                                               fac_dt                       )
    1417                       ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) +              &
    1418                                             chem_species(n)%conc(nzt+1,j,i)
     2080                IF ( lod == 2 )  THEN
     2081                   DO  i = nxl, nxr
     2082                      DO  j = nys, nyn
     2083                         chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time(                    &
     2084                                                 nest_offl%chem_top(0,j,i,n),                      &
     2085                                                 nest_offl%chem_top(1,j,i,n),                      &
     2086                                                 fac_dt                       )
     2087                         ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) +                               &
     2088                                               chem_species(n)%conc(nzt+1,j,i)
     2089                      ENDDO
    14192090                   ENDDO
    1420                 ENDDO
     2091                ELSE
     2092                   var_1d(nzt+1) = interpolate_in_time( nest_offl%chem_top(0,1,1,n),               &
     2093                                                        nest_offl%chem_top(1,1,1,n),               &
     2094                                                        fac_dt )
     2095                   chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) = var_1d(nzt+1)
     2096                   ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) +                                     &
     2097                                         SUM( chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) )
     2098                ENDIF
    14212099             ENDIF
    14222100          ENDDO
     
    14552133!--          Do local exchange only when necessary, i.e. when data is coming
    14562134!--          from dynamic file.
    1457              IF ( nest_offl%chem_from_file_t(n) )                              &
    1458                 CALL exchange_horiz( chem_species(n)%conc, nbgp )
     2135             IF ( nest_offl%chem_from_file_t(n) )  CALL exchange_horiz( chem_species(n)%conc, nbgp )
    14592136          ENDDO
    14602137       ENDIF
     
    14672144       IF ( salsa )  CALL salsa_nesting_offl_bc
    14682145!
    1469 !--    In case of Rayleigh damping, where the profiles u_init, v_init
    1470 !--    q_init and pt_init are still used, update these profiles from the
    1471 !--    averaged boundary data.
    1472 !--    But first, average these data.
     2146!--    Calculate the mean profiles. These are later stored on u_init, v_init,
     2147!--    etc., in order to adjust the Rayleigh damping under time-evolving atmospheric conditions
     2148!--    accordingly - damping against the representative mean profiles, not against the initial
     2149!--    profiles. Note, in LOD = 1 case no averaging is required.
    14732150#if defined( __parallel )
    1474        CALL MPI_ALLREDUCE( u_ref_l, u_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM,     &
    1475                            comm2d, ierr )
    1476        CALL MPI_ALLREDUCE( v_ref_l, v_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM,     &
    1477                            comm2d, ierr )
     2151       CALL MPI_ALLREDUCE( u_ref_l, u_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
     2152       CALL MPI_ALLREDUCE( v_ref_l, v_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
    14782153       IF ( humidity )  THEN
    1479           CALL MPI_ALLREDUCE( q_ref_l, q_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM,  &
    1480                               comm2d, ierr )
     2154          CALL MPI_ALLREDUCE( q_ref_l, q_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
    14812155       ENDIF
    14822156       IF ( .NOT. neutral )  THEN
    1483           CALL MPI_ALLREDUCE( pt_ref_l, pt_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM,&
    1484                               comm2d, ierr )
     2157          CALL MPI_ALLREDUCE( pt_ref_l, pt_ref, nzt+1-nzb+1, MPI_REAL, MPI_SUM, comm2d, ierr )
    14852158       ENDIF
    14862159       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    1487           CALL MPI_ALLREDUCE( ref_chem_l, ref_chem,                            &
    1488                               ( nzt+1-nzb+1 ) * SIZE( ref_chem(nzb,:) ),       &
     2160          CALL MPI_ALLREDUCE( ref_chem_l, ref_chem, ( nzt+1-nzb+1 ) * SIZE( ref_chem(nzb,:) ),  &
    14892161                              MPI_REAL, MPI_SUM, comm2d, ierr )
    14902162       ENDIF
     
    15012173!--    number of input data is different from nzb:nzt compared to nzt+1.
    15022174!--    Derived from lateral boundaries.
    1503        u_ref(nzb:nzt) = u_ref(nzb:nzt) / REAL( 2.0_wp * ( ny + 1 + nx     ),   &
    1504                                                KIND = wp ) 
    1505        v_ref(nzb:nzt) = v_ref(nzb:nzt) / REAL( 2.0_wp * ( ny   + nx + 1   ),   &
    1506                                                KIND = wp )
    1507        IF ( humidity )                                                         &
    1508           q_ref(nzb:nzt) = q_ref(nzb:nzt)   / REAL( 2.0_wp *                   &
    1509                                                           ( ny + 1 + nx + 1 ), &
    1510                                                     KIND = wp )
    1511        IF ( .NOT. neutral )                                                    &
    1512           pt_ref(nzb:nzt) = pt_ref(nzb:nzt) / REAL( 2.0_wp *                   &
    1513                                                           ( ny + 1 + nx + 1 ), &
    1514                                               KIND = wp )
    1515        IF ( air_chemistry  .AND.  nesting_offline_chem )                       &
    1516           ref_chem(nzb:nzt,:) = ref_chem(nzb:nzt,:) / REAL( 2.0_wp *           &
    1517                                                           ( ny + 1 + nx + 1 ), &
    1518                                                             KIND = wp )
    1519 !
    1520 !--    Derived from top boundary.   
     2175       u_ref(nzb:nzt) = u_ref(nzb:nzt) / REAL( 2.0_wp * ( ny + 1 + nx     ), KIND = wp ) 
     2176       v_ref(nzb:nzt) = v_ref(nzb:nzt) / REAL( 2.0_wp * ( ny   + nx + 1   ), KIND = wp )
     2177       IF ( humidity )                                                                          &
     2178          q_ref(nzb:nzt) = q_ref(nzb:nzt)   / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
     2179       IF ( .NOT. neutral )                                                                     &
     2180          pt_ref(nzb:nzt) = pt_ref(nzb:nzt) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
     2181       IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     2182          ref_chem(nzb:nzt,:) = ref_chem(nzb:nzt,:) / REAL( 2.0_wp * ( ny + 1 + nx + 1 ), KIND = wp )
     2183!
     2184!--    Derived from top boundary.
    15212185       u_ref(nzt+1) = u_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx     ), KIND = wp )
    15222186       v_ref(nzt+1) = v_ref(nzt+1) / REAL( ( ny     ) * ( nx + 1 ), KIND = wp )
    1523        IF ( humidity )                                                         &
    1524           q_ref(nzt+1) = q_ref(nzt+1)   / REAL( ( ny + 1 ) * ( nx + 1 ),       &
    1525                                                 KIND = wp )
    1526        IF ( .NOT. neutral )                                                    &
    1527           pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ),       &
    1528                                                 KIND = wp )
    1529        IF ( air_chemistry  .AND.  nesting_offline_chem )                       &
    1530           ref_chem(nzt+1,:) = ref_chem(nzt+1,:) /                              &
    1531                               REAL( ( ny + 1 ) * ( nx + 1 ),KIND = wp )
     2187       IF ( humidity )                                                                          &
     2188          q_ref(nzt+1) = q_ref(nzt+1)   / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
     2189       IF ( .NOT. neutral )                                                                     &
     2190          pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ), KIND = wp )
     2191       IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     2192          ref_chem(nzt+1,:) = ref_chem(nzt+1,:) / REAL( ( ny + 1 ) * ( nx + 1 ),KIND = wp )
    15322193!
    15332194!--    Write onto init profiles, which are used for damping. Also set lower
     
    15482209          DO  n = 1, UBOUND( chem_species, 1 )
    15492210             IF ( nest_offl%chem_from_file_t(n) )  THEN
    1550                 chem_species(n)%conc_pr_init(:) = ref_chem(:,n)
    1551                 chem_species(n)%conc_pr_init(nzb) =                            &
    1552                                             chem_species(n)%conc_pr_init(nzb+1)
     2211                chem_species(n)%conc_pr_init(:)   = ref_chem(:,n)
     2212                chem_species(n)%conc_pr_init(nzb) = chem_species(n)%conc_pr_init(nzb+1)
    15532213             ENDIF
    15542214          ENDDO
    15552215       ENDIF
    1556 
    15572216       IF ( ALLOCATED( ref_chem   ) )  DEALLOCATE( ref_chem   )
    15582217       IF ( ALLOCATED( ref_chem_l ) )  DEALLOCATE( ref_chem_l )
     
    15612220!--    Therefore, calculate boundary-layer depth first.
    15622221       CALL nesting_offl_calc_zi
    1563        CALL adjust_sponge_layer 
     2222       CALL adjust_sponge_layer
    15642223
    15652224       CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
     
    19072566!------------------------------------------------------------------------------!
    19082567    SUBROUTINE nesting_offl_init
    1909            
    1910        INTEGER(iwp) ::  n !< running index for chemical species
    1911 
     2568
     2569       INTEGER(iwp) ::  i   !< loop index for x-direction
     2570       INTEGER(iwp) ::  j   !< loop index for y-direction
     2571       INTEGER(iwp) ::  n   !< running index for chemical species
     2572
     2573!
     2574!--    Before arrays for the boundary data are allocated, the LOD of the dynamic input data
     2575!--    at the boundaries is read.
     2576#if defined ( __netcdf )
     2577!
     2578!--    Open file in read-only mode
     2579       CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), pids_id )
     2580!
     2581!--    Read attributes for LOD. In order to gurantee that also older drivers, where attribute is not given,
     2582!--    are working, do not abort the run but assume LOD2 forcing.
     2583       CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_pt,  .FALSE., 'ls_forcing_left_pt', .FALSE. )
     2584       CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_qv,  .FALSE., 'ls_forcing_left_qv', .FALSE. )
     2585       CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_u,   .FALSE., 'ls_forcing_left_u',  .FALSE. )
     2586       CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_v,   .FALSE., 'ls_forcing_left_v',  .FALSE. )
     2587       CALL get_attribute( pids_id, char_lod, nest_offl%lod_east_w,   .FALSE., 'ls_forcing_left_w',  .FALSE. )
     2588
     2589       CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_pt, .FALSE., 'ls_forcing_north_pt', .FALSE. )
     2590       CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_qv, .FALSE., 'ls_forcing_north_qv', .FALSE. )
     2591       CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_u,  .FALSE., 'ls_forcing_north_u',  .FALSE. )
     2592       CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_v,  .FALSE., 'ls_forcing_north_v',  .FALSE. )
     2593       CALL get_attribute( pids_id, char_lod, nest_offl%lod_north_w,  .FALSE., 'ls_forcing_north_w',  .FALSE. )
     2594
     2595       CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_pt, .FALSE., 'ls_forcing_south_pt', .FALSE. )
     2596       CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_qv, .FALSE., 'ls_forcing_south_qv', .FALSE. )
     2597       CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_u,  .FALSE., 'ls_forcing_south_u',  .FALSE. )
     2598       CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_v,  .FALSE., 'ls_forcing_south_v',  .FALSE. )
     2599       CALL get_attribute( pids_id, char_lod, nest_offl%lod_south_w,  .FALSE., 'ls_forcing_south_w',  .FALSE. )
     2600
     2601       CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_pt,  .FALSE., 'ls_forcing_right_pt', .FALSE. )
     2602       CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_qv,  .FALSE., 'ls_forcing_right_qv', .FALSE. )
     2603       CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_u,   .FALSE., 'ls_forcing_right_u',  .FALSE. )
     2604       CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_v,   .FALSE., 'ls_forcing_right_v',  .FALSE. )
     2605       CALL get_attribute( pids_id, char_lod, nest_offl%lod_west_w,   .FALSE., 'ls_forcing_right_w',  .FALSE. )
     2606
     2607       CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_pt,   .FALSE., 'ls_forcing_top_pt', .FALSE. )
     2608       CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_qv,   .FALSE., 'ls_forcing_top_qv', .FALSE. )
     2609       CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_u,    .FALSE., 'ls_forcing_top_u',  .FALSE. )
     2610       CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_v,    .FALSE., 'ls_forcing_top_v',  .FALSE. )
     2611       CALL get_attribute( pids_id, char_lod, nest_offl%lod_top_w,    .FALSE., 'ls_forcing_top_w',  .FALSE. )
     2612
     2613       CALL close_input_file( pids_id )
     2614#endif
     2615!
     2616!--    Temporary workaround until most of the dynamic drivers contain a LOD attribute. So far INIFOR
     2617!--    did not provide the LOD attribute. In order to still use these older dynamic drivers, provide
     2618!--    a temporary workaround. If the LOD is not given, a NetCDF interal error will occur but the simulation
     2619!--    will not be aborted since the no_abort flag is passed. However, the respective attribute value
     2620!--    might be given an arbitrary number. Hence, check for valid LOD's and manually set them to LOD 2
     2621!--    (as assumed so far). Note, this workaround should be removed later (date of reference: 6. Oct. 2020).
     2622       IF ( nest_offl%lod_east_pt /= 1  .AND.  nest_offl%lod_east_pt /= 2 )  nest_offl%lod_east_pt = 2
     2623       IF ( nest_offl%lod_east_qv /= 1  .AND.  nest_offl%lod_east_qv /= 2 )  nest_offl%lod_east_qv = 2
     2624       IF ( nest_offl%lod_east_u  /= 1  .AND.  nest_offl%lod_east_u  /= 2 )  nest_offl%lod_east_u  = 2
     2625       IF ( nest_offl%lod_east_v  /= 1  .AND.  nest_offl%lod_east_v  /= 2 )  nest_offl%lod_east_v  = 2
     2626       IF ( nest_offl%lod_east_w  /= 1  .AND.  nest_offl%lod_east_w  /= 2 )  nest_offl%lod_east_w  = 2
     2627
     2628       IF ( nest_offl%lod_north_pt /= 1  .AND.  nest_offl%lod_north_pt /= 2 )  nest_offl%lod_north_pt = 2
     2629       IF ( nest_offl%lod_north_qv /= 1  .AND.  nest_offl%lod_north_qv /= 2 )  nest_offl%lod_north_qv = 2
     2630       IF ( nest_offl%lod_north_u  /= 1  .AND.  nest_offl%lod_north_u  /= 2 )  nest_offl%lod_north_u  = 2
     2631       IF ( nest_offl%lod_north_v  /= 1  .AND.  nest_offl%lod_north_v  /= 2 )  nest_offl%lod_north_v  = 2
     2632       IF ( nest_offl%lod_north_w  /= 1  .AND.  nest_offl%lod_north_w  /= 2 )  nest_offl%lod_north_w  = 2
     2633
     2634       IF ( nest_offl%lod_south_pt /= 1  .AND.  nest_offl%lod_south_pt /= 2 )  nest_offl%lod_south_pt = 2
     2635       IF ( nest_offl%lod_south_qv /= 1  .AND.  nest_offl%lod_south_qv /= 2 )  nest_offl%lod_south_qv = 2
     2636       IF ( nest_offl%lod_south_u  /= 1  .AND.  nest_offl%lod_south_u  /= 2 )  nest_offl%lod_south_u  = 2
     2637       IF ( nest_offl%lod_south_v  /= 1  .AND.  nest_offl%lod_south_v  /= 2 )  nest_offl%lod_south_v  = 2
     2638       IF ( nest_offl%lod_south_w  /= 1  .AND.  nest_offl%lod_south_w  /= 2 )  nest_offl%lod_south_w  = 2
     2639
     2640       IF ( nest_offl%lod_west_pt /= 1  .AND.  nest_offl%lod_west_pt /= 2 )  nest_offl%lod_west_pt = 2
     2641       IF ( nest_offl%lod_west_qv /= 1  .AND.  nest_offl%lod_west_qv /= 2 )  nest_offl%lod_west_qv = 2
     2642       IF ( nest_offl%lod_west_u  /= 1  .AND.  nest_offl%lod_west_u  /= 2 )  nest_offl%lod_west_u  = 2
     2643       IF ( nest_offl%lod_west_v  /= 1  .AND.  nest_offl%lod_west_v  /= 2 )  nest_offl%lod_west_v  = 2
     2644       IF ( nest_offl%lod_west_w  /= 1  .AND.  nest_offl%lod_west_w  /= 2 )  nest_offl%lod_west_w  = 2
     2645
     2646       IF ( nest_offl%lod_top_pt /= 1  .AND.  nest_offl%lod_top_pt /= 2 )  nest_offl%lod_top_pt = 2
     2647       IF ( nest_offl%lod_top_qv /= 1  .AND.  nest_offl%lod_top_qv /= 2 )  nest_offl%lod_top_qv = 2
     2648       IF ( nest_offl%lod_top_u  /= 1  .AND.  nest_offl%lod_top_u  /= 2 )  nest_offl%lod_top_u  = 2
     2649       IF ( nest_offl%lod_top_v  /= 1  .AND.  nest_offl%lod_top_v  /= 2 )  nest_offl%lod_top_v  = 2
     2650       IF ( nest_offl%lod_top_w  /= 1  .AND.  nest_offl%lod_top_w  /= 2 )  nest_offl%lod_top_w  = 2
     2651!
     2652!--    For consistency, check if all boundary input variables have the same LOD.
     2653       IF ( MAX( nest_offl%lod_east_pt,  nest_offl%lod_east_qv,  nest_offl%lod_east_u,             &
     2654                 nest_offl%lod_east_v,   nest_offl%lod_east_w,                                     &
     2655                 nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,            &
     2656                 nest_offl%lod_north_v,  nest_offl%lod_north_w,                                    &
     2657                 nest_offl%lod_south_pt, nest_offl%lod_south_qv, nest_offl%lod_south_u,            &
     2658                 nest_offl%lod_south_v,  nest_offl%lod_south_w,                                    &
     2659                 nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,            &
     2660                 nest_offl%lod_north_v,  nest_offl%lod_north_w,                                    &
     2661                 nest_offl%lod_top_pt,   nest_offl%lod_top_qv,   nest_offl%lod_top_u,              &
     2662                 nest_offl%lod_top_v,    nest_offl%lod_top_w )                                     &
     2663               /=                                                                                  &
     2664            MIN( nest_offl%lod_east_pt,  nest_offl%lod_east_qv,  nest_offl%lod_east_u,             &
     2665                 nest_offl%lod_east_v,   nest_offl%lod_east_w,                                     &
     2666                 nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,            &
     2667                 nest_offl%lod_north_v,  nest_offl%lod_north_w,                                    &
     2668                 nest_offl%lod_south_pt, nest_offl%lod_south_qv, nest_offl%lod_south_u,            &
     2669                 nest_offl%lod_south_v,  nest_offl%lod_south_w,                                    &
     2670                 nest_offl%lod_north_pt, nest_offl%lod_north_qv, nest_offl%lod_north_u,            &
     2671                 nest_offl%lod_north_v,  nest_offl%lod_north_w,                                    &
     2672                 nest_offl%lod_top_pt,   nest_offl%lod_top_qv,   nest_offl%lod_top_u,              &
     2673                 nest_offl%lod_top_v,    nest_offl%lod_top_w ) )  THEN
     2674          message_string = 'A mixture of different LOD for the provided boundary data is not ' //  &
     2675                           'possible.'
     2676          CALL message( 'nesting_offl_init', 'PA0504', 1, 2, 0, 6, 0 )
     2677       ENDIF
     2678!
     2679!--    As all LODs are the same, store it.
     2680       lod = nest_offl%lod_east_u
     2681!
    19122682!--    Allocate arrays for geostrophic wind components. Arrays will
    19132683!--    incorporate 2 time levels in order to interpolate in between.
     
    19152685       ALLOCATE( nest_offl%vg(0:1,1:nzt) )
    19162686!
    1917 !--    Allocate arrays for reading left/right boundary values. Arrays will
    1918 !--    incorporate 2  time levels in order to interpolate in between. If the core has
    1919 !--    no boundary, allocate a dummy array, in order to enable netcdf parallel
    1920 !--    access. Dummy arrays will be allocated with dimension length zero.
     2687!--    Set index range according to the given LOD in order to allocate the input arrays
     2688       IF ( bc_dirichlet_l  .OR.  bc_dirichlet_r  )  THEN
     2689          IF ( lod == 2 )  THEN
     2690             j_start   = nys
     2691             j_start_v = nysv
     2692             j_end     = nyn
     2693          ELSE
     2694             j_start   = 1
     2695             j_start_v = 1
     2696             j_end     = 1
     2697          ENDIF
     2698       ENDIF
     2699
     2700       IF ( bc_dirichlet_n  .OR.  bc_dirichlet_s )  THEN
     2701          IF( lod == 2 )  THEN
     2702             i_start   = nxl
     2703             i_start_u = nxlu
     2704             i_end     = nxr
     2705          ELSE
     2706             i_start   = 1
     2707             i_start_u = 1
     2708             i_end     = 1
     2709          ENDIF
     2710       ENDIF
     2711!
     2712!--    Allocate arrays for reading left/right boundary values. Arrays will
     2713!--    incorporate 2 time levels in order to interpolate in between. Depending on the given LOD,
     2714!--    the x-, or y-dimension will be either nxl:nxr, or nys:nyn (for LOD=2), or it reduces to
     2715!--    one element for LOD=1. If the core has no lateral boundary, allocate a dummy array as well,
     2716!--    in order to enable netcdf parallel access. Dummy arrays will be allocated with dimension
     2717!--    length zero.
    19212718       IF ( bc_dirichlet_l )  THEN
    1922           ALLOCATE( nest_offl%u_left(0:1,nzb+1:nzt,nys:nyn)  )
    1923           ALLOCATE( nest_offl%v_left(0:1,nzb+1:nzt,nysv:nyn) )
    1924           ALLOCATE( nest_offl%w_left(0:1,nzb+1:nzt-1,nys:nyn) )
    1925           IF ( humidity )       ALLOCATE( nest_offl%q_left(0:1,nzb+1:nzt,nys:nyn)  )
    1926           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_left(0:1,nzb+1:nzt,nys:nyn) )
     2719          ALLOCATE( nest_offl%u_l(0:1,nzb+1:nzt,j_start:j_end)  )
     2720          ALLOCATE( nest_offl%v_l(0:1,nzb+1:nzt,j_start_v:j_end) )
     2721          ALLOCATE( nest_offl%w_l(0:1,nzb+1:nzt-1,j_start:j_end) )
     2722          IF ( humidity )       ALLOCATE( nest_offl%q_l(0:1,nzb+1:nzt,j_start:j_end)  )
     2723          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_l(0:1,nzb+1:nzt,j_start:j_end) )
    19272724          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1928              ALLOCATE( nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,1:UBOUND( chem_species, 1 )) )
     2725             ALLOCATE( nest_offl%chem_l(0:1,nzb+1:nzt,j_start:j_end,1:UBOUND( chem_species, 1 )) )
    19292726       ELSE
    1930           ALLOCATE( nest_offl%u_left(1:1,1:1,1:1)  )
    1931           ALLOCATE( nest_offl%v_left(1:1,1:1,1:1)  )
    1932           ALLOCATE( nest_offl%w_left(1:1,1:1,1:1)  )
    1933           IF ( humidity )       ALLOCATE( nest_offl%q_left(1:1,1:1,1:1)  )
    1934           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_left(1:1,1:1,1:1)  )
     2727          ALLOCATE( nest_offl%u_l(1:1,1:1,1:1)  )
     2728          ALLOCATE( nest_offl%v_l(1:1,1:1,1:1)  )
     2729          ALLOCATE( nest_offl%w_l(1:1,1:1,1:1)  )
     2730          IF ( humidity )       ALLOCATE( nest_offl%q_l(1:1,1:1,1:1)  )
     2731          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_l(1:1,1:1,1:1)  )
    19352732          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1936              ALLOCATE( nest_offl%chem_left(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
     2733             ALLOCATE( nest_offl%chem_l(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19372734       ENDIF
    19382735       IF ( bc_dirichlet_r )  THEN
    1939           ALLOCATE( nest_offl%u_right(0:1,nzb+1:nzt,nys:nyn)  )
    1940           ALLOCATE( nest_offl%v_right(0:1,nzb+1:nzt,nysv:nyn) )
    1941           ALLOCATE( nest_offl%w_right(0:1,nzb+1:nzt-1,nys:nyn) )
    1942           IF ( humidity )       ALLOCATE( nest_offl%q_right(0:1,nzb+1:nzt,nys:nyn)  )
    1943           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_right(0:1,nzb+1:nzt,nys:nyn) )
     2736          ALLOCATE( nest_offl%u_r(0:1,nzb+1:nzt,j_start:j_end)  )
     2737          ALLOCATE( nest_offl%v_r(0:1,nzb+1:nzt,j_start_v:j_end) )
     2738          ALLOCATE( nest_offl%w_r(0:1,nzb+1:nzt-1,j_start:j_end) )
     2739          IF ( humidity )       ALLOCATE( nest_offl%q_r(0:1,nzb+1:nzt,j_start:j_end)  )
     2740          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_r(0:1,nzb+1:nzt,j_start:j_end) )
    19442741          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1945              ALLOCATE( nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,1:UBOUND( chem_species, 1 )) )
     2742             ALLOCATE( nest_offl%chem_r(0:1,nzb+1:nzt,j_start:j_end,1:UBOUND( chem_species, 1 )) )
    19462743       ELSE
    1947           ALLOCATE( nest_offl%u_right(1:1,1:1,1:1)  )
    1948           ALLOCATE( nest_offl%v_right(1:1,1:1,1:1)  )
    1949           ALLOCATE( nest_offl%w_right(1:1,1:1,1:1)  )
    1950           IF ( humidity )       ALLOCATE( nest_offl%q_right(1:1,1:1,1:1)  )
    1951           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_right(1:1,1:1,1:1)  )
     2744          ALLOCATE( nest_offl%u_r(1:1,1:1,1:1)  )
     2745          ALLOCATE( nest_offl%v_r(1:1,1:1,1:1)  )
     2746          ALLOCATE( nest_offl%w_r(1:1,1:1,1:1)  )
     2747          IF ( humidity )       ALLOCATE( nest_offl%q_r(1:1,1:1,1:1)  )
     2748          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_r(1:1,1:1,1:1)  )
    19522749          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1953              ALLOCATE( nest_offl%chem_right(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
     2750             ALLOCATE( nest_offl%chem_r(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19542751       ENDIF
    19552752!
     
    19592756!--    access. Dummy arrays will be allocated with dimension length zero.
    19602757       IF ( bc_dirichlet_n )  THEN
    1961           ALLOCATE( nest_offl%u_north(0:1,nzb+1:nzt,nxlu:nxr) )
    1962           ALLOCATE( nest_offl%v_north(0:1,nzb+1:nzt,nxl:nxr)  )
    1963           ALLOCATE( nest_offl%w_north(0:1,nzb+1:nzt-1,nxl:nxr) )
    1964           IF ( humidity )       ALLOCATE( nest_offl%q_north(0:1,nzb+1:nzt,nxl:nxr)  )
    1965           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_north(0:1,nzb+1:nzt,nxl:nxr) )
     2758          ALLOCATE( nest_offl%u_n(0:1,nzb+1:nzt,i_start_u:i_end) )
     2759          ALLOCATE( nest_offl%v_n(0:1,nzb+1:nzt,i_start:i_end)  )
     2760          ALLOCATE( nest_offl%w_n(0:1,nzb+1:nzt-1,i_start:i_end) )
     2761          IF ( humidity )       ALLOCATE( nest_offl%q_n(0:1,nzb+1:nzt,i_start:i_end)  )
     2762          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_n(0:1,nzb+1:nzt,i_start:i_end) )
    19662763          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1967              ALLOCATE( nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,1:UBOUND( chem_species, 1 )) )
     2764             ALLOCATE( nest_offl%chem_n(0:1,nzb+1:nzt,i_start:i_end,1:UBOUND( chem_species, 1 )) )
    19682765       ELSE
    1969           ALLOCATE( nest_offl%u_north(1:1,1:1,1:1)  )
    1970           ALLOCATE( nest_offl%v_north(1:1,1:1,1:1)  )
    1971           ALLOCATE( nest_offl%w_north(1:1,1:1,1:1)  )
    1972           IF ( humidity )       ALLOCATE( nest_offl%q_north(1:1,1:1,1:1)  )
    1973           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_north(1:1,1:1,1:1)  )
     2766          ALLOCATE( nest_offl%u_n(1:1,1:1,1:1)  )
     2767          ALLOCATE( nest_offl%v_n(1:1,1:1,1:1)  )
     2768          ALLOCATE( nest_offl%w_n(1:1,1:1,1:1)  )
     2769          IF ( humidity )       ALLOCATE( nest_offl%q_n(1:1,1:1,1:1)  )
     2770          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_n(1:1,1:1,1:1)  )
    19742771          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1975              ALLOCATE( nest_offl%chem_north(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
     2772             ALLOCATE( nest_offl%chem_n(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19762773       ENDIF
    19772774       IF ( bc_dirichlet_s )  THEN
    1978           ALLOCATE( nest_offl%u_south(0:1,nzb+1:nzt,nxlu:nxr) )
    1979           ALLOCATE( nest_offl%v_south(0:1,nzb+1:nzt,nxl:nxr)  )
    1980           ALLOCATE( nest_offl%w_south(0:1,nzb+1:nzt-1,nxl:nxr)    )
    1981           IF ( humidity )       ALLOCATE( nest_offl%q_south(0:1,nzb+1:nzt,nxl:nxr)  )
    1982           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_south(0:1,nzb+1:nzt,nxl:nxr) )
     2775          ALLOCATE( nest_offl%u_s(0:1,nzb+1:nzt,i_start_u:i_end) )
     2776          ALLOCATE( nest_offl%v_s(0:1,nzb+1:nzt,i_start:i_end)  )
     2777          ALLOCATE( nest_offl%w_s(0:1,nzb+1:nzt-1,i_start:i_end) )
     2778          IF ( humidity )       ALLOCATE( nest_offl%q_s(0:1,nzb+1:nzt,i_start:i_end)  )
     2779          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_s(0:1,nzb+1:nzt,i_start:i_end) )
    19832780          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1984              ALLOCATE( nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,1:UBOUND( chem_species, 1 )) )
     2781             ALLOCATE( nest_offl%chem_s(0:1,nzb+1:nzt,i_start:i_end,1:UBOUND( chem_species, 1 )) )
    19852782       ELSE
    1986           ALLOCATE( nest_offl%u_south(1:1,1:1,1:1)  )
    1987           ALLOCATE( nest_offl%v_south(1:1,1:1,1:1)  )
    1988           ALLOCATE( nest_offl%w_south(1:1,1:1,1:1)  )
    1989           IF ( humidity )       ALLOCATE( nest_offl%q_south(1:1,1:1,1:1)  )
    1990           IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_south(1:1,1:1,1:1)  )
     2783          ALLOCATE( nest_offl%u_s(1:1,1:1,1:1)  )
     2784          ALLOCATE( nest_offl%v_s(1:1,1:1,1:1)  )
     2785          ALLOCATE( nest_offl%w_s(1:1,1:1,1:1)  )
     2786          IF ( humidity )       ALLOCATE( nest_offl%q_s(1:1,1:1,1:1)  )
     2787          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_s(1:1,1:1,1:1)  )
    19912788          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
    1992              ALLOCATE( nest_offl%chem_south(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
     2789             ALLOCATE( nest_offl%chem_s(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19932790       ENDIF
    19942791!
     
    19962793!--    lateral boundaries, every core reads these data so that no dummy
    19972794!--    arrays need to be allocated.
    1998        ALLOCATE( nest_offl%u_top(0:1,nys:nyn,nxlu:nxr) )
    1999        ALLOCATE( nest_offl%v_top(0:1,nysv:nyn,nxl:nxr) )
    2000        ALLOCATE( nest_offl%w_top(0:1,nys:nyn,nxl:nxr)  )
    2001        IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,nys:nyn,nxl:nxr)  )
    2002        IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,nys:nyn,nxl:nxr) )
    2003        IF ( air_chemistry  .AND.  nesting_offline_chem )                                           &
    2004           ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,1:UBOUND( chem_species, 1 )) )
     2795       IF ( lod == 2 )  THEN
     2796          ALLOCATE( nest_offl%u_top(0:1,nys:nyn,nxlu:nxr) )
     2797          ALLOCATE( nest_offl%v_top(0:1,nysv:nyn,nxl:nxr) )
     2798          ALLOCATE( nest_offl%w_top(0:1,nys:nyn,nxl:nxr)  )
     2799          IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,nys:nyn,nxl:nxr)  )
     2800          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,nys:nyn,nxl:nxr) )
     2801          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     2802             ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,1:UBOUND( chem_species, 1 )) )
     2803       ELSE
     2804          ALLOCATE( nest_offl%u_top(0:1,1:1,1:1) )
     2805          ALLOCATE( nest_offl%v_top(0:1,1:1,1:1) )
     2806          ALLOCATE( nest_offl%w_top(0:1,1:1,1:1)  )
     2807          IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,1:1,1:1)  )
     2808          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,1:1,1:1) )
     2809          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     2810             ALLOCATE( nest_offl%chem_top(0:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
     2811       ENDIF
    20052812!
    20062813!--    For chemical species, create the names of the variables. This is necessary
     
    20672874       ENDIF
    20682875!
     2876!--    Set indicies for boundary grid points
     2877       IF ( bc_dirichlet_l  .OR.  bc_dirichlet_r )  THEN
     2878          i_bound   = MERGE( nxl  - 1, nxr + 1, bc_dirichlet_l )
     2879          i_bound_u = MERGE( nxlu - 1, nxr + 1, bc_dirichlet_l )
     2880       ENDIF
     2881       IF ( bc_dirichlet_n  .OR.  bc_dirichlet_s )  THEN
     2882          j_bound   = MERGE( nys  - 1, nyn + 1, bc_dirichlet_s )
     2883          j_bound_v = MERGE( nysv - 1, nyn + 1, bc_dirichlet_s )
     2884       ENDIF
     2885!
    20692886!--    Initialize boundary data. Please note, do not initialize boundaries in
    20702887!--    case of restart runs. This case the boundaries are already initialized
    2071 !--    and the boundary data from file would be on the wrong time level. 
     2888!--    and the boundary data from file would be on the wrong time level.
    20722889       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    2073           IF ( bc_dirichlet_l )  THEN
    2074              u(nzb+1:nzt,nys:nyn,0)    = nest_offl%u_left(0,nzb+1:nzt,nys:nyn)
    2075              v(nzb+1:nzt,nysv:nyn,-1)  = nest_offl%v_left(0,nzb+1:nzt,nysv:nyn)
    2076              w(nzb+1:nzt-1,nys:nyn,-1) = nest_offl%w_left(0,nzb+1:nzt-1,nys:nyn)
    2077              IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,-1) =                  &
    2078                                       nest_offl%pt_left(0,nzb+1:nzt,nys:nyn)
    2079              IF ( humidity      )  q(nzb+1:nzt,nys:nyn,-1)  =                  &
    2080                                       nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
     2890!
     2891!--       Distinguish between LOD = 1 and LOD = 2 inititialization
     2892          IF ( lod == 2 )  THEN
     2893             IF ( bc_dirichlet_l )  THEN
     2894                u(nzb+1:nzt,nys:nyn,i_bound_u) = nest_offl%u_l(0,nzb+1:nzt,nys:nyn)
     2895                v(nzb+1:nzt,nysv:nyn,i_bound)  = nest_offl%v_l(0,nzb+1:nzt,nysv:nyn)
     2896                w(nzb+1:nzt-1,nys:nyn,i_bound) = nest_offl%w_l(0,nzb+1:nzt-1,nys:nyn)
     2897                IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%pt_l(0,nzb+1:nzt,nys:nyn)
     2898                IF ( humidity      )  q(nzb+1:nzt,nys:nyn,i_bound)  = nest_offl%q_l(0,nzb+1:nzt,nys:nyn)
     2899                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     2900                   DO  n = 1, UBOUND( chem_species, 1 )
     2901                      IF( nest_offl%chem_from_file_l(n) )  THEN
     2902                         chem_species(n)%conc(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%chem_l(0,nzb+1:nzt,nys:nyn,n)
     2903                      ENDIF
     2904                   ENDDO
     2905                ENDIF
     2906             ENDIF
     2907             IF ( bc_dirichlet_r )  THEN
     2908                u(nzb+1:nzt,nys:nyn,i_bound_u) = nest_offl%u_r(0,nzb+1:nzt,nys:nyn)
     2909                v(nzb+1:nzt,nysv:nyn,i_bound)  = nest_offl%v_r(0,nzb+1:nzt,nysv:nyn)
     2910                w(nzb+1:nzt-1,nys:nyn,i_bound) = nest_offl%w_r(0,nzb+1:nzt-1,nys:nyn)
     2911                IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%pt_r(0,nzb+1:nzt,nys:nyn)
     2912                IF ( humidity      )  q(nzb+1:nzt,nys:nyn,i_bound)  = nest_offl%q_r(0,nzb+1:nzt,nys:nyn)
     2913                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     2914                   DO  n = 1, UBOUND( chem_species, 1 )
     2915                      IF( nest_offl%chem_from_file_r(n) )  THEN
     2916                         chem_species(n)%conc(nzb+1:nzt,nys:nyn,i_bound) = nest_offl%chem_r(0,nzb+1:nzt,nys:nyn,n)
     2917                      ENDIF
     2918                   ENDDO
     2919                ENDIF
     2920             ENDIF
     2921
     2922             IF ( bc_dirichlet_n)  THEN
     2923                u(nzb+1:nzt,j_bound,nxlu:nxr)  = nest_offl%u_n(0,nzb+1:nzt,nxlu:nxr)
     2924                v(nzb+1:nzt,j_bound_v,nxl:nxr) = nest_offl%v_n(0,nzb+1:nzt,nxl:nxr)
     2925                w(nzb+1:nzt-1,j_bound,nxl:nxr) = nest_offl%w_n(0,nzb+1:nzt-1,nxl:nxr)
     2926                IF ( .NOT. neutral )  pt(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%pt_n(0,nzb+1:nzt,nxl:nxr)
     2927                IF ( humidity      )  q(nzb+1:nzt,j_bound,nxl:nxr)  = nest_offl%q_n(0,nzb+1:nzt,nxl:nxr)
     2928                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     2929                   DO  n = 1, UBOUND( chem_species, 1 )
     2930                      IF( nest_offl%chem_from_file_n(n) )  THEN
     2931                         chem_species(n)%conc(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%chem_n(0,nzb+1:nzt,nxl:nxr,n)
     2932                      ENDIF
     2933                   ENDDO
     2934                ENDIF
     2935             ENDIF
     2936             IF ( bc_dirichlet_s)  THEN
     2937                u(nzb+1:nzt,j_bound,nxlu:nxr)  = nest_offl%u_s(0,nzb+1:nzt,nxlu:nxr)
     2938                v(nzb+1:nzt,j_bound_v,nxl:nxr) = nest_offl%v_s(0,nzb+1:nzt,nxl:nxr)
     2939                w(nzb+1:nzt-1,j_bound,nxl:nxr) = nest_offl%w_s(0,nzb+1:nzt-1,nxl:nxr)
     2940                IF ( .NOT. neutral )  pt(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%pt_s(0,nzb+1:nzt,nxl:nxr)
     2941                IF ( humidity      )  q(nzb+1:nzt,j_bound,nxl:nxr)  = nest_offl%q_s(0,nzb+1:nzt,nxl:nxr)
     2942                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     2943                   DO  n = 1, UBOUND( chem_species, 1 )
     2944                      IF( nest_offl%chem_from_file_s(n) )  THEN
     2945                         chem_species(n)%conc(nzb+1:nzt,j_bound,nxl:nxr) = nest_offl%chem_s(0,nzb+1:nzt,nxl:nxr,n)
     2946                      ENDIF
     2947                   ENDDO
     2948                ENDIF
     2949             ENDIF
     2950
     2951             u(nzt+1,nys:nyn,nxlu:nxr) = nest_offl%u_top(0,nys:nyn,nxlu:nxr)
     2952             v(nzt+1,nysv:nyn,nxl:nxr) = nest_offl%v_top(0,nysv:nyn,nxl:nxr)
     2953             w(nzt,nys:nyn,nxl:nxr)    = nest_offl%w_top(0,nys:nyn,nxl:nxr)
     2954             w(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%w_top(0,nys:nyn,nxl:nxr)
     2955             IF ( .NOT. neutral )  pt(nzt+1,nys:nyn,nxl:nxr) = nest_offl%pt_top(0,nys:nyn,nxl:nxr)
     2956             IF ( humidity )       q(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%q_top(0,nys:nyn,nxl:nxr)
    20812957             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    20822958                DO  n = 1, UBOUND( chem_species, 1 )
    2083                    IF( nest_offl%chem_from_file_l(n) )  THEN
    2084                       chem_species(n)%conc(nzb+1:nzt,nys:nyn,-1) =             &
    2085                                       nest_offl%chem_left(0,nzb+1:nzt,nys:nyn,n)
     2959                   IF( nest_offl%chem_from_file_t(n) )  THEN
     2960                      chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) = nest_offl%chem_top(0,nys:nyn,nxl:nxr,n)
    20862961                   ENDIF
    20872962                ENDDO
    20882963             ENDIF
    2089           ENDIF
    2090           IF ( bc_dirichlet_r )  THEN
    2091              u(nzb+1:nzt,nys:nyn,nxr+1)   = nest_offl%u_right(0,nzb+1:nzt,nys:nyn)
    2092              v(nzb+1:nzt,nysv:nyn,nxr+1)  = nest_offl%v_right(0,nzb+1:nzt,nysv:nyn)
    2093              w(nzb+1:nzt-1,nys:nyn,nxr+1) = nest_offl%w_right(0,nzb+1:nzt-1,nys:nyn)
    2094              IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,nxr+1) =               &
    2095                                       nest_offl%pt_right(0,nzb+1:nzt,nys:nyn)
    2096              IF ( humidity      )  q(nzb+1:nzt,nys:nyn,nxr+1)  =               &
    2097                                       nest_offl%q_right(0,nzb+1:nzt,nys:nyn)
     2964!
     2965!--       LOD 1
     2966          ELSE
     2967             IF ( bc_dirichlet_l )  THEN
     2968                DO  j = nys, nyn
     2969                   u(nzb+1:nzt,j,i_bound_u) = nest_offl%u_l(0,nzb+1:nzt,1)
     2970                   w(nzb+1:nzt-1,j,i_bound) = nest_offl%w_l(0,nzb+1:nzt-1,1)
     2971                ENDDO
     2972                DO  j = nysv, nyn
     2973                   v(nzb+1:nzt,j,i_bound)  = nest_offl%v_l(0,nzb+1:nzt,1)
     2974                ENDDO
     2975                IF ( .NOT. neutral )  THEN
     2976                   DO  j = nys, nyn
     2977                      pt(nzb+1:nzt,j,i_bound) = nest_offl%pt_l(0,nzb+1:nzt,1)
     2978                   ENDDO
     2979                ENDIF
     2980                IF ( humidity      )  THEN
     2981                   DO  j = nys, nyn
     2982                      q(nzb+1:nzt,j,i_bound)  = nest_offl%q_l(0,nzb+1:nzt,1)
     2983                   ENDDO
     2984                ENDIF
     2985                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     2986                   DO  n = 1, UBOUND( chem_species, 1 )
     2987                      IF( nest_offl%chem_from_file_l(n) )  THEN
     2988                         DO  j = nys, nyn
     2989                            chem_species(n)%conc(nzb+1:nzt,j,i_bound) = nest_offl%chem_l(0,nzb+1:nzt,1,n)
     2990                         ENDDO
     2991                      ENDIF
     2992                   ENDDO
     2993                ENDIF
     2994             ENDIF
     2995             IF ( bc_dirichlet_r )  THEN
     2996                DO  j = nys, nyn
     2997                   u(nzb+1:nzt,j,i_bound_u) = nest_offl%u_r(0,nzb+1:nzt,1)
     2998                   w(nzb+1:nzt-1,j,i_bound) = nest_offl%w_r(0,nzb+1:nzt-1,1)
     2999                ENDDO
     3000                DO  j = nysv, nyn
     3001                   v(nzb+1:nzt,j,i_bound)  = nest_offl%v_r(0,nzb+1:nzt,1)
     3002                ENDDO
     3003                IF ( .NOT. neutral )  THEN
     3004                   DO  j = nys, nyn
     3005                      pt(nzb+1:nzt,j,i_bound) = nest_offl%pt_r(0,nzb+1:nzt,1)
     3006                   ENDDO
     3007                ENDIF
     3008                IF ( humidity      )  THEN
     3009                   DO  j = nys, nyn
     3010                      q(nzb+1:nzt,j,i_bound)  = nest_offl%q_r(0,nzb+1:nzt,1)
     3011                   ENDDO
     3012                ENDIF
     3013                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     3014                   DO  n = 1, UBOUND( chem_species, 1 )
     3015                      IF( nest_offl%chem_from_file_r(n) )  THEN
     3016                         DO  j = nys, nyn
     3017                            chem_species(n)%conc(nzb+1:nzt,j,i_bound) = nest_offl%chem_r(0,nzb+1:nzt,1,n)
     3018                         ENDDO
     3019                      ENDIF
     3020                   ENDDO
     3021                ENDIF
     3022             ENDIF
     3023             IF ( bc_dirichlet_n )  THEN
     3024                DO  i = nxlu, nxr
     3025                   u(nzb+1:nzt,j_bound,i)  = nest_offl%u_n(0,nzb+1:nzt,1)
     3026                ENDDO
     3027                DO  i = nxl, nxr
     3028                   v(nzb+1:nzt,j_bound_v,i) = nest_offl%v_n(0,nzb+1:nzt,1)
     3029                   w(nzb+1:nzt-1,j_bound,i) = nest_offl%w_n(0,nzb+1:nzt-1,1)
     3030                ENDDO
     3031                IF ( .NOT. neutral )  THEN
     3032                   DO  i = nxl, nxr
     3033                      pt(nzb+1:nzt,j_bound,i) = nest_offl%pt_n(0,nzb+1:nzt,1)
     3034                   ENDDO
     3035                ENDIF
     3036                IF ( humidity      )  THEN
     3037                   DO  i = nxl, nxr
     3038                      q(nzb+1:nzt,j_bound,i)  = nest_offl%q_n(0,nzb+1:nzt,1)
     3039                   ENDDO
     3040                ENDIF
     3041                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     3042                   DO  n = 1, UBOUND( chem_species, 1 )
     3043                      IF( nest_offl%chem_from_file_n(n) )  THEN
     3044                         DO  i = nxl, nxr
     3045                            chem_species(n)%conc(nzb+1:nzt,j_bound,i) = nest_offl%chem_n(0,nzb+1:nzt,1,n)
     3046                         ENDDO
     3047                      ENDIF
     3048                   ENDDO
     3049                ENDIF
     3050             ENDIF
     3051             IF ( bc_dirichlet_s )  THEN
     3052                DO  i = nxlu, nxr
     3053                   u(nzb+1:nzt,j_bound,i)  = nest_offl%u_s(0,nzb+1:nzt,1)
     3054                ENDDO
     3055                DO  i = nxl, nxr
     3056                   v(nzb+1:nzt,j_bound_v,i) = nest_offl%v_s(0,nzb+1:nzt,1)
     3057                   w(nzb+1:nzt-1,j_bound,i) = nest_offl%w_s(0,nzb+1:nzt-1,1)
     3058                ENDDO
     3059                IF ( .NOT. neutral )  THEN
     3060                   DO  i = nxl, nxr
     3061                      pt(nzb+1:nzt,j_bound,i) = nest_offl%pt_s(0,nzb+1:nzt,1)
     3062                   ENDDO
     3063                ENDIF
     3064                IF ( humidity      )  THEN
     3065                   DO  i = nxl, nxr
     3066                      q(nzb+1:nzt,j_bound,i)  = nest_offl%q_s(0,nzb+1:nzt,1)
     3067                   ENDDO
     3068                ENDIF
     3069                IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     3070                   DO  n = 1, UBOUND( chem_species, 1 )
     3071                      IF( nest_offl%chem_from_file_s(n) )  THEN
     3072                         DO  i = nxl, nxr
     3073                            chem_species(n)%conc(nzb+1:nzt,j_bound,i) = nest_offl%chem_s(0,nzb+1:nzt,1,n)
     3074                         ENDDO
     3075                      ENDIF
     3076                   ENDDO
     3077                ENDIF
     3078             ENDIF
     3079
     3080             u(nzt+1,nys:nyn,nxlu:nxr) = nest_offl%u_top(0,1,1)
     3081             v(nzt+1,nysv:nyn,nxl:nxr) = nest_offl%v_top(0,1,1)
     3082             w(nzt,nys:nyn,nxl:nxr)    = nest_offl%w_top(0,1,1)
     3083             w(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%w_top(0,1,1)
     3084             IF ( .NOT. neutral )  pt(nzt+1,nys:nyn,nxl:nxr) = nest_offl%pt_top(0,1,1)
     3085             IF ( humidity )       q(nzt+1,nys:nyn,nxl:nxr)  = nest_offl%q_top(0,1,1)
    20983086             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    20993087                DO  n = 1, UBOUND( chem_species, 1 )
    2100                    IF( nest_offl%chem_from_file_r(n) )  THEN
    2101                       chem_species(n)%conc(nzb+1:nzt,nys:nyn,nxr+1) =          &
    2102                                       nest_offl%chem_right(0,nzb+1:nzt,nys:nyn,n)
    2103                    ENDIF
    2104                 ENDDO
    2105              ENDIF
    2106           ENDIF
    2107           IF ( bc_dirichlet_s )  THEN
    2108              u(nzb+1:nzt,-1,nxlu:nxr)  = nest_offl%u_south(0,nzb+1:nzt,nxlu:nxr)
    2109              v(nzb+1:nzt,0,nxl:nxr)    = nest_offl%v_south(0,nzb+1:nzt,nxl:nxr)
    2110              w(nzb+1:nzt-1,-1,nxl:nxr) = nest_offl%w_south(0,nzb+1:nzt-1,nxl:nxr)
    2111              IF ( .NOT. neutral )  pt(nzb+1:nzt,-1,nxl:nxr) =                  &
    2112                                       nest_offl%pt_south(0,nzb+1:nzt,nxl:nxr)
    2113              IF ( humidity      )  q(nzb+1:nzt,-1,nxl:nxr)  =                  &
    2114                                       nest_offl%q_south(0,nzb+1:nzt,nxl:nxr)
    2115              IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    2116                 DO  n = 1, UBOUND( chem_species, 1 )
    2117                    IF( nest_offl%chem_from_file_s(n) )  THEN
    2118                       chem_species(n)%conc(nzb+1:nzt,-1,nxl:nxr) =             &
    2119                                       nest_offl%chem_south(0,nzb+1:nzt,nxl:nxr,n)
    2120                    ENDIF
    2121                 ENDDO
    2122              ENDIF
    2123           ENDIF
    2124           IF ( bc_dirichlet_n )  THEN
    2125              u(nzb+1:nzt,nyn+1,nxlu:nxr)  = nest_offl%u_north(0,nzb+1:nzt,nxlu:nxr)
    2126              v(nzb+1:nzt,nyn+1,nxl:nxr)   = nest_offl%v_north(0,nzb+1:nzt,nxl:nxr)
    2127              w(nzb+1:nzt-1,nyn+1,nxl:nxr) = nest_offl%w_north(0,nzb+1:nzt-1,nxl:nxr)
    2128              IF ( .NOT. neutral )  pt(nzb+1:nzt,nyn+1,nxl:nxr) =               &
    2129                                       nest_offl%pt_north(0,nzb+1:nzt,nxl:nxr)
    2130              IF ( humidity      )  q(nzb+1:nzt,nyn+1,nxl:nxr)  =               &
    2131                                       nest_offl%q_north(0,nzb+1:nzt,nxl:nxr)
    2132              IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    2133                 DO  n = 1, UBOUND( chem_species, 1 )
    2134                    IF( nest_offl%chem_from_file_n(n) )  THEN
    2135                       chem_species(n)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =          &
    2136                                       nest_offl%chem_north(0,nzb+1:nzt,nxl:nxr,n)
     3088                   IF( nest_offl%chem_from_file_t(n) )  THEN
     3089                      chem_species(n)%conc(nzt+1,nys:nyn,nxl:nxr) = nest_offl%chem_top(0,1,1,n)
    21373090                   ENDIF
    21383091                ENDDO
     
    21593112!--    generator correctly.
    21603113       CALL nesting_offl_calc_zi
    2161        
    21623114!
    21633115!--    After boundary data is initialized, ensure mass conservation. Not
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r4641 r4724  
    2525! -----------------
    2626! $Id$
     27! - New routines to read LOD=1 variables from dynamic input file
     28! - add no_abort option to all get_attribute routines
     29!
     30! 4641 2020-08-13 09:57:07Z suehring
    2731! To follow (UC)2 standard, change default of attribute data_content
    2832!
     
    741745       MODULE PROCEDURE get_variable_2d_int32
    742746       MODULE PROCEDURE get_variable_2d_real
     747       MODULE PROCEDURE get_variable_2d_real_dynamic
    743748       MODULE PROCEDURE get_variable_3d_int8
    744749       MODULE PROCEDURE get_variable_3d_real
     
    39964001!------------------------------------------------------------------------------!
    39974002     SUBROUTINE get_attribute_int32( id, attribute_name, value, global,        &
    3998                                      variable_name )
     4003                                     variable_name, no_abort )
    39994004
    40004005       USE pegrid
     
    40094014       INTEGER(iwp), INTENT(INOUT) ::  value            !< read value
    40104015
    4011        LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     4016       LOGICAL                       ::  check_error    !< flag indicating if handle_error shall be checked
     4017       LOGICAL, INTENT(IN)           ::  global         !< flag indicating global attribute
     4018       LOGICAL, INTENT(IN), OPTIONAL ::  no_abort       !< flag indicating if errors should be checked
    40124019#if defined( __netcdf )
    40134020
     4021       IF ( PRESENT( no_abort ) )  THEN
     4022          check_error = no_abort
     4023       ELSE
     4024          check_error = .TRUE.
     4025       ENDIF
    40144026!
    40154027!--    Read global attribute
    40164028       IF ( global )  THEN
    40174029          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
    4018           CALL handle_error( 'get_attribute_int32 global', 522, attribute_name )
     4030          IF ( check_error)  CALL handle_error( 'get_attribute_int32 global', 522, attribute_name )
    40194031!
    40204032!--    Read attributes referring to a single variable. Therefore, first inquire
     
    40224034       ELSE
    40234035          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    4024           CALL handle_error( 'get_attribute_int32', 522, attribute_name )
     4036          IF ( check_error)  CALL handle_error( 'get_attribute_int32', 522, attribute_name )
    40254037          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    4026           CALL handle_error( 'get_attribute_int32', 522, attribute_name )
     4038          IF ( check_error)  CALL handle_error( 'get_attribute_int32', 522, attribute_name )
    40274039       ENDIF
    40284040#endif
     
    40354047!------------------------------------------------------------------------------!
    40364048     SUBROUTINE get_attribute_int8( id, attribute_name, value, global,         &
    4037                                     variable_name )
     4049                                    variable_name, no_abort )
    40384050
    40394051       USE pegrid
     
    40484060       INTEGER(KIND=1), INTENT(INOUT) ::  value         !< read value
    40494061
    4050        LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     4062       LOGICAL                       ::  check_error    !< flag indicating if handle_error shall be checked
     4063       LOGICAL, INTENT(IN), OPTIONAL ::  no_abort       !< flag indicating if errors should be checked
     4064       LOGICAL, INTENT(IN)           ::  global         !< flag indicating global attribute
    40514065#if defined( __netcdf )
    40524066
     4067       IF ( PRESENT( no_abort ) )  THEN
     4068          check_error = no_abort
     4069       ELSE
     4070          check_error = .TRUE.
     4071       ENDIF
    40534072!
    40544073!--    Read global attribute
    40554074       IF ( global )  THEN
    40564075          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
    4057           CALL handle_error( 'get_attribute_int8 global', 523, attribute_name )
     4076          IF ( check_error)  CALL handle_error( 'get_attribute_int8 global', 523, attribute_name )
    40584077!
    40594078!--    Read attributes referring to a single variable. Therefore, first inquire
     
    40614080       ELSE
    40624081          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    4063           CALL handle_error( 'get_attribute_int8', 523, attribute_name )
     4082          IF ( check_error)  CALL handle_error( 'get_attribute_int8', 523, attribute_name )
    40644083          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    4065           CALL handle_error( 'get_attribute_int8', 523, attribute_name )
     4084          IF ( check_error)  CALL handle_error( 'get_attribute_int8', 523, attribute_name )
    40664085       ENDIF
    40674086#endif
     
    40744093!------------------------------------------------------------------------------!
    40754094     SUBROUTINE get_attribute_real( id, attribute_name, value, global,         &
    4076                                     variable_name )
     4095                                    variable_name, no_abort )
    40774096
    40784097       USE pegrid
     
    40864105       INTEGER(iwp)                ::  id_var           !< variable id
    40874106
    4088        LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     4107       LOGICAL                       ::  check_error    !< flag indicating if handle_error shall be checked
     4108       LOGICAL, INTENT(IN)           ::  global         !< flag indicating global attribute
     4109       LOGICAL, INTENT(IN), OPTIONAL ::  no_abort       !< flag indicating if errors should be checked
    40894110
    40904111       REAL(wp), INTENT(INOUT)     ::  value            !< read value
    40914112#if defined( __netcdf )
    40924113
    4093 
    4094 !
    4095 !-- Read global attribute
     4114       IF ( PRESENT( no_abort ) )  THEN
     4115          check_error = no_abort
     4116       ELSE
     4117          check_error = .TRUE.
     4118       ENDIF
     4119!
     4120!--    Read global attribute
    40964121       IF ( global )  THEN
    40974122          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
    4098           CALL handle_error( 'get_attribute_real global', 524, attribute_name )
    4099 !
    4100 !-- Read attributes referring to a single variable. Therefore, first inquire
    4101 !-- variable id
     4123          IF ( check_error)  CALL handle_error( 'get_attribute_real global', 524, attribute_name )
     4124!
     4125!--    Read attributes referring to a single variable. Therefore, first inquire
     4126!--    variable id
    41024127       ELSE
    41034128          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    4104           CALL handle_error( 'get_attribute_real', 524, attribute_name )
     4129          IF ( check_error)  CALL handle_error( 'get_attribute_real', 524, attribute_name )
    41054130          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    4106           CALL handle_error( 'get_attribute_real', 524, attribute_name )
     4131          IF ( check_error)  CALL handle_error( 'get_attribute_real', 524, attribute_name )
    41074132       ENDIF
    41084133#endif
     
    43324357
    43334358!------------------------------------------------------------------------------!
    4334 ! Description:
    4335 ! ------------
    4336 !> Reads a character variable in a 1D array
     4359!    Description:
     4360!    ------------
     4361!>   Reads a character variable in a 1D array
    43374362!------------------------------------------------------------------------------!
    43384363     SUBROUTINE get_variable_1d_char( id, variable_name, var )
     
    44054430       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
    44064431!
    4407 !--    Inquire dimension length
     4432!--    Read variable
    44084433       nc_stat = NF90_GET_VAR( id, id_var, var )
    44094434       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
     
    44174442!> Reads a 1D float variable from file.
    44184443!------------------------------------------------------------------------------!
    4419      SUBROUTINE get_variable_1d_real( id, variable_name, var )
     4444     SUBROUTINE get_variable_1d_real( id, variable_name, var, is, count_elements )
    44204445
    44214446       USE pegrid
     
    44284453       INTEGER(iwp)                ::  id_var           !< dimension id
    44294454
     4455       INTEGER(iwp), INTENT(IN), OPTIONAL ::  count_elements !< number of elements to be read
     4456       INTEGER(iwp), INTENT(IN), OPTIONAL ::  is             !< start index
     4457
    44304458       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var    !< variable to be read
    44314459#if defined( __netcdf )
    4432 
    44334460!
    44344461!--    First, inquire variable ID
     
    44364463       CALL handle_error( 'get_variable_1d_real', 528, variable_name )
    44374464!
    4438 !--    Inquire dimension length
    4439        nc_stat = NF90_GET_VAR( id, id_var, var )
    4440        CALL handle_error( 'get_variable_1d_real', 528, variable_name )
     4465!--    Read variable
     4466       IF ( PRESENT( is ) )  THEN
     4467          nc_stat = NF90_GET_VAR( id, id_var, var, start = (/ is /), count = (/ count_elements /) )
     4468          CALL handle_error( 'get_variable_1d_real', 528, variable_name )
     4469       ELSE
     4470          nc_stat = NF90_GET_VAR( id, id_var, var )
     4471          CALL handle_error( 'get_variable_1d_real', 528, variable_name )
     4472       ENDIF
    44414473
    44424474#endif
     
    44634495       INTEGER(iwp), INTENT(IN)              ::  t                !< timestep number
    44644496
    4465        REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
     4497       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var              !< variable to be read
    44664498
    44674499#if defined( __netcdf )
     
    47434775
    47444776!
    4745 !-- Allocate temporary variable according to memory access on file.
     4777!--    Allocate temporary variable according to memory access on file.
    47464778       ALLOCATE( tmp(is:ie,js:je) )
    47474779!
    4748 !-- Get variable
     4780!--    Get variable
    47494781       nc_stat = NF90_GET_VAR( id, id_var, tmp,            &
    47504782                      start = (/ is+1,      js+1 /),       &
    47514783                      count = (/ ie-is + 1, je-js+1 /) )   
    4752           CALL handle_error( 'get_variable_2d_real', 530, variable_name )
    4753 !
    4754 !-- Resort data. Please note, dimension subscripts of var all start at 1.
    4755           DO  i = is, ie
    4756              DO  j = js, je
    4757                 var(j-js+1,i-is+1) = tmp(i,j)
    4758              ENDDO
     4784       CALL handle_error( 'get_variable_2d_real', 530, variable_name )
     4785!
     4786!--    Resort data. Please note, dimension subscripts of var all start at 1.
     4787       DO  i = is, ie
     4788          DO  j = js, je
     4789             var(j-js+1,i-is+1) = tmp(i,j)
    47594790          ENDDO
     4791       ENDDO
    47604792       
    4761           DEALLOCATE( tmp )
     4793       DEALLOCATE( tmp )
    47624794
    47634795#endif
     
    51715203#endif
    51725204    END SUBROUTINE get_variable_4d_to_3d_real
     5205
     5206!------------------------------------------------------------------------------!
     5207! Description:
     5208! ------------
     5209!> Reads a 3D float variables from dynamic driver with the last dimension only
     5210!> having 1 entry (time,z). Please note,
     5211!> the passed arguments are start indices and number of elements in each
     5212!> dimension, which is in contrast to the other 3d versions where start- and
     5213!> end indices are passed. The different handling compared to get_variable_2d_real
     5214!> is due to its different start-index treatment.
     5215!------------------------------------------------------------------------------!
     5216    SUBROUTINE get_variable_2d_real_dynamic( id, variable_name, var,           &
     5217                                             i1s, i2s,                         &
     5218                                             count_1, count_2 )
     5219                               
     5220       USE indices
     5221       USE pegrid
     5222
     5223       IMPLICIT NONE
     5224
     5225       CHARACTER(LEN=*)              ::  variable_name   !< variable name
     5226
     5227       INTEGER(iwp)                  ::  count_1         !< number of elements to be read along 1st dimension (with respect to file)
     5228       INTEGER(iwp)                  ::  count_2         !< number of elements to be read along 2nd dimension (with respect to file)
     5229       INTEGER(iwp)                  ::  i1              !< running index along 1st dimension on file
     5230       INTEGER(iwp)                  ::  i1s             !< start index for subdomain input along 1st dimension (with respect to file)
     5231       INTEGER(iwp)                  ::  i2              !< running index along 2nd dimension on file       
     5232       INTEGER(iwp)                  ::  i2s             !< start index for subdomain input along 2nd dimension (with respect to file)
     5233       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
     5234       INTEGER(iwp)                  ::  id_var          !< variable id
     5235       INTEGER(iwp)                  ::  lb1             !< lower bound of 1st dimension (with respect to file)
     5236       INTEGER(iwp)                  ::  lb2             !< lower bound of 2nd dimension (with respect to file)
     5237       INTEGER(iwp)                  ::  ub1             !< upper bound of 1st dimension (with respect to file)
     5238       INTEGER(iwp)                  ::  ub2             !< upper bound of 2nd dimension (with respect to file)
     5239
     5240       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  tmp   !< temporary variable to read data from file according to its reverse memory access
     5241
     5242       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var !< input variable
     5243
     5244#if defined( __netcdf )
     5245!
     5246!--    Inquire variable id.
     5247       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     5248!
     5249!--    Allocate temporary variable according to memory access on file.
     5250!--    Therefore, determine dimension bounds of input array.
     5251       lb1 = LBOUND(var,2)
     5252       ub1 = UBOUND(var,2)
     5253       lb2 = LBOUND(var,1)
     5254       ub2 = UBOUND(var,1)
     5255
     5256       ALLOCATE( tmp(lb1:ub1,lb2:ub2) )
     5257!
     5258!--    Get variable
     5259       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
     5260                               start = (/ i1s,     i2s /),                     &
     5261                               count = (/ count_1, count_2 /) )
     5262
     5263       CALL handle_error( 'get_variable_2d_real_dynamic', 537, variable_name )
     5264!
     5265!--    Resort data. Please note, dimension subscripts of var all start at 1.
     5266       DO i2 = lb2, ub2
     5267          DO  i1 = lb1, ub1
     5268             var(i2,i1,1) = tmp(i1,i2)
     5269          ENDDO
     5270       ENDDO
     5271
     5272       DEALLOCATE( tmp )       
     5273#endif
     5274    END SUBROUTINE get_variable_2d_real_dynamic
    51735275
    51745276!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.