Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

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

    r3106 r3182  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Adjust input of dynamic driver according to revised Inifor version.
     23! Replace simulated_time by time_since_reference_point.
     24! Rename variables in mesoscale-offline nesting mode.
    2325!
    2426! Former revisions:
     
    199201!-- Define data type for nesting in larger-scale models like COSMO.
    200202!-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
    201     TYPE force_type
     203    TYPE nest_offl_type
    202204
    203205       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
     
    206208       INTEGER(iwp) ::  nzu    !< number of vertical levels on scalar grid in dynamic input file
    207209       INTEGER(iwp) ::  nzw    !< number of vertical levels on w grid in dynamic input file
    208        INTEGER(iwp) ::  tind   !< time index for reference time in large-scale forcing data
    209        INTEGER(iwp) ::  tind_p !< time index for following time in large-scale forcing data
     210       INTEGER(iwp) ::  tind   !< time index for reference time in mesoscale-offline nesting
     211       INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
    210212
    211213       LOGICAL      ::  init         = .FALSE.
    212        LOGICAL      ::  interpolated = .FALSE.
    213214       LOGICAL      ::  from_file    = .FALSE.
    214215
     
    251252       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
    252253
    253     END TYPE force_type
     254    END TYPE nest_offl_type
    254255
    255256    TYPE init_type
     
    474475    TYPE(dims_xy)    ::  dim_static  !< data structure for x, y-dimension in static input file
    475476
    476     TYPE(force_type) ::  force     !< data structure for data input at lateral and top boundaries (provided by Inifor)
     477    TYPE(nest_offl_type) ::  nest_offl  !< data structure for data input at lateral and top boundaries (provided by Inifor) 
    477478
    478479    TYPE(init_type) ::  init_3d    !< data structure for the initialization of the 3D flow and soil fields
     
    606607!-- Public variables
    607608    PUBLIC albedo_pars_f, albedo_type_f, basal_area_density_f, buildings_f,    &
    608            building_id_f, building_pars_f, building_type_f, force, init_3d,    &
     609           building_id_f, building_pars_f, building_type_f, init_3d,           &
    609610           init_model, input_file_static, input_pids_static,                   &
    610            input_pids_dynamic, leaf_area_density_f,                            &
     611           input_pids_dynamic, leaf_area_density_f, nest_offl,                 &
    611612           pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,       &
    612613           root_area_density_lad_f, root_area_density_lsm_f, soil_pars_f,      &
     
    719720!--    sun-zenith angles. To avoid this, longitude and latitude in each model
    720721!--    domain will be set to the values of the root model. Please note, this
    721 !--    synchronization is required already here.
     722!--    synchronization is required already here. 
    722723#if defined( __parallel )
    723724       CALL MPI_BCAST( init_model%latitude,  1, MPI_REAL, 0,                   &
     
    726727                       MPI_COMM_WORLD, ierr )
    727728#endif
    728 
    729729
    730730    END SUBROUTINE netcdf_data_input_init
     
    20572057
    20582058       USE arrays_3d,                                                          &
    2059            ONLY:  q, pt, u, v, w
     2059           ONLY:  q, pt, u, v, w, zu, zw
    20602060
    20612061       USE control_parameters,                                                 &
    2062            ONLY:  bc_lr_cyc, bc_ns_cyc, forcing, humidity, land_surface,       &
    2063                   message_string, neutral, surface_pressure
     2062           ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, land_surface, message_string,&
     2063                  nesting_offline, neutral, surface_pressure
    20642064
    20652065       USE indices,                                                            &
     
    21192119       CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
    21202120       CALL get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
    2121        CALL get_dimension_length( id_dynamic, init_3d%nzs, 'depth' )
     2121       CALL get_dimension_length( id_dynamic, init_3d%nzs, 'zsoil' )
    21222122!
    21232123!--    Read also the horizontal dimensions. These are used just used fo
     
    21422142       ENDIF
    21432143
    2144        IF ( init_3d%nzu-1 /= nz )  THEN
     2144       IF ( init_3d%nzu /= nz )  THEN
    21452145          message_string = 'Number of inifor vertical grid points ' //         &
    21462146                           'does not match the number of numeric grid '//      &
     
    21592159          CALL get_variable( id_dynamic, 'zw', init_3d%zw_atmos )
    21602160       ENDIF
    2161        IF ( check_existence( var_names, 'depth' ) )  THEN
     2161       IF ( check_existence( var_names, 'zsoil' ) )  THEN
    21622162          ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
    2163           CALL get_variable( id_dynamic, 'depth', init_3d%z_soil )
    2164        ENDIF
    2165 !
    2166 !--    Read initial geostrophic wind components at t = 0 (index 1 in file).
    2167 !        IF ( check_existence( var_names, 'tend_ug' ) )  THEN
     2163          CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )
     2164       ENDIF
     2165!
     2166!--    Check for consistency between vertical coordinates in dynamic
     2167!--    driver and numeric grid.
     2168!--    Please note, depending on compiler options both may be
     2169!--    equal up to a certain threshold, and differences between
     2170!--    the numeric grid and vertical coordinate in the driver can built-
     2171!--    up to 10E-1-10E-0 m. For this reason, the check is performed not
     2172!--    for exactly matching values.
     2173       IF ( ANY( ABS( zu(1:nzt)   - init_3d%zu_atmos(1:init_3d%nzu) )    &
     2174                      > 10E-1 )  .OR.                                    &
     2175            ANY( ABS( zw(1:nzt-1) - init_3d%zw_atmos(1:init_3d%nzw) )    &
     2176                      > 10E-1 ) )  THEN
     2177          message_string = 'Vertical grid in dynamic driver does not '// &
     2178                           'match the numeric grid.'
     2179          CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
     2180       ENDIF
     2181!
     2182!--    Read initial geostrophic wind components at
     2183!--    t = 0 (index 1 in file).
    21682184       IF ( check_existence( var_names, 'ls_forcing_ug' ) )  THEN
    21692185          ALLOCATE( init_3d%ug_init(nzb:nzt+1) )
    2170 !           CALL get_variable_pr( id_dynamic, 'tend_ug', 1,                      &
    2171 !                                 init_3d%ug_init )
    2172           CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1,                &
    2173                                 init_3d%ug_init )
     2186          init_3d%ug_init = 0.0_wp
     2187
     2188          CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1,          &
     2189                                init_3d%ug_init(1:nzt) )
     2190!
     2191!--       Set top-boundary condition (Neumann)
     2192          init_3d%ug_init(nzt+1) = init_3d%ug_init(nzt)
     2193
    21742194          init_3d%from_file_ug = .TRUE.
    21752195       ELSE
    21762196          init_3d%from_file_ug = .FALSE.
    21772197       ENDIF
    2178 !        IF ( check_existence( var_names, 'tend_vg' ) )  THEN
    21792198       IF ( check_existence( var_names, 'ls_forcing_vg' ) )  THEN
    21802199          ALLOCATE( init_3d%vg_init(nzb:nzt+1) )
    2181 !           CALL get_variable_pr( id_dynamic, 'tend_vg', 1,                      &
    2182 !                                 init_3d%vg_init )
    2183           CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1,                &
    2184                                 init_3d%vg_init )
     2200          init_3d%vg_init = 0.0_wp
     2201
     2202          CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1,          &
     2203                                init_3d%vg_init(1:nzt) )
     2204!
     2205!--       Set top-boundary condition (Neumann)
     2206          init_3d%vg_init(nzt+1) = init_3d%vg_init(nzt)
     2207
    21852208          init_3d%from_file_vg = .TRUE.
    21862209       ELSE
     
    21952218!--    into separate loops. 
    21962219!--    Read u-component
    2197        IF ( check_existence( var_names, 'init_u' ) )  THEN
     2220       IF ( check_existence( var_names, 'init_atmosphere_u' ) )  THEN
    21982221!
    21992222!--       Read attributes for the fill value and level-of-detail
    22002223          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_u,           &
    2201                               .FALSE., 'init_u' )
     2224                              .FALSE., 'init_atmosphere_u' )
    22022225          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_u,             &
    2203                               .FALSE., 'init_u' )
     2226                              .FALSE., 'init_atmosphere_u' )
    22042227!
    22052228!--       level-of-detail 1 - read initialization profile
     
    22082231             init_3d%u_init = 0.0_wp
    22092232
    2210              CALL get_variable( id_dynamic, 'init_u',                          &
    2211                                 init_3d%u_init(nzb+1:nzt+1) )
     2233             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
     2234                                init_3d%u_init(nzb+1:nzt) )
     2235!
     2236!--          Set top-boundary condition (Neumann)
     2237             init_3d%u_init(nzt+1) = init_3d%u_init(nzt)
    22122238!
    22132239!--       level-of-detail 2 - read 3D initialization data
    22142240          ELSEIF ( init_3d%lod_u == 2 )  THEN
    2215 
    2216              CALL get_variable( id_dynamic, 'init_u',                          &
    2217                                 u(nzb+1:nzt+1,nys:nyn,nxlu:nxr),               &
     2241             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
     2242                                u(nzb+1:nzt,nys:nyn,nxlu:nxr),                 &
    22182243                                nxlu, nys+1, nzb+1,                            &
    22192244                                nxr-nxlu+1, nyn-nys+1, init_3d%nzu,            &
    22202245                                dynamic_3d )
     2246!
     2247!--          Set value at leftmost model grid point nxl = 0. This is because
     2248!--          Inifor provides data only from 1:nx-1 since it assumes non-cyclic
     2249!--          conditions.
     2250             IF ( nxl == 0 )                                                   &
     2251                u(nzb+1:nzt,nys:nyn,nxl) = u(nzb+1:nzt,nys:nyn,nxlu)
     2252!
     2253!--          Set bottom and top-boundary
     2254             u(nzb,:,:)   = u(nzb+1,:,:)
     2255             u(nzt+1,:,:) = u(nzt,:,:)
     2256             
    22212257          ENDIF
    22222258          init_3d%from_file_u = .TRUE.
     
    22242260!
    22252261!--    Read v-component
    2226        IF ( check_existence( var_names, 'init_v' ) )  THEN
     2262       IF ( check_existence( var_names, 'init_atmosphere_v' ) )  THEN
    22272263!
    22282264!--       Read attributes for the fill value and level-of-detail
    22292265          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_v,           &
    2230                               .FALSE., 'init_v' )
     2266                              .FALSE., 'init_atmosphere_v' )
    22312267          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_v,             &
    2232                               .FALSE., 'init_v' )
     2268                              .FALSE., 'init_atmosphere_v' )
    22332269!
    22342270!--       level-of-detail 1 - read initialization profile
     
    22372273             init_3d%v_init = 0.0_wp
    22382274
    2239              CALL get_variable( id_dynamic, 'init_v',                          &
    2240                                 init_3d%v_init(nzb+1:nzt+1) )
    2241 
     2275             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
     2276                                init_3d%v_init(nzb+1:nzt) )
     2277!
     2278!--          Set top-boundary condition (Neumann)
     2279             init_3d%v_init(nzt+1) = init_3d%v_init(nzt)
    22422280!
    22432281!--       level-of-detail 2 - read 3D initialization data
    22442282          ELSEIF ( init_3d%lod_v == 2 )  THEN
    2245 
    2246              CALL get_variable( id_dynamic, 'init_v',                          &
    2247                                 v(nzb+1:nzt+1,nysv:nyn,nxl:nxr),               &
     2283         
     2284             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
     2285                                v(nzb+1:nzt,nysv:nyn,nxl:nxr),                 &
    22482286                                nxl+1, nysv, nzb+1,                            &
    22492287                                nxr-nxl+1, nyn-nysv+1, init_3d%nzu,            &
    22502288                                dynamic_3d )
     2289!
     2290!--          Set value at southmost model grid point nys = 0. This is because
     2291!--          Inifor provides data only from 1:ny-1 since it assumes non-cyclic
     2292!--          conditions.
     2293             IF ( nys == 0 )                                                   &
     2294                v(nzb+1:nzt,nys,nxl:nxr) = v(nzb+1:nzt,nysv,nxl:nxr)                               
     2295!
     2296!--          Set bottom and top-boundary
     2297             v(nzb,:,:)   = v(nzb+1,:,:)
     2298             v(nzt+1,:,:) = v(nzt,:,:)
    22512299             
    22522300          ENDIF
     
    22552303!
    22562304!--    Read w-component
    2257        IF ( check_existence( var_names, 'init_w' ) )  THEN
     2305       IF ( check_existence( var_names, 'init_atmosphere_w' ) )  THEN
    22582306!
    22592307!--       Read attributes for the fill value and level-of-detail
    22602308          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_w,           &
    2261                               .FALSE., 'init_w' )
     2309                              .FALSE., 'init_atmosphere_w' )
    22622310          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_w,             &
    2263                               .FALSE., 'init_w' )
     2311                              .FALSE., 'init_atmosphere_w' )
    22642312!
    22652313!--       level-of-detail 1 - read initialization profile
     
    22682316             init_3d%w_init = 0.0_wp
    22692317
    2270              CALL get_variable( id_dynamic, 'init_w',                          &
    2271                                 init_3d%w_init(nzb+1:nzt) )
    2272 
     2318             CALL get_variable( id_dynamic, 'init_atmosphere_w',               &
     2319                                init_3d%w_init(nzb+1:nzt-1) )
     2320!
     2321!--          Set top-boundary condition (Neumann)
     2322             init_3d%w_init(nzt:nzt+1) = init_3d%w_init(nzt-1)
    22732323!
    22742324!--       level-of-detail 2 - read 3D initialization data
    22752325          ELSEIF ( init_3d%lod_w == 2 )  THEN
    22762326
    2277              CALL get_variable( id_dynamic, 'init_w',                           &
    2278                                 w(nzb+1:nzt,nys:nyn,nxl:nxr),                   &
     2327             CALL get_variable( id_dynamic, 'init_atmosphere_w',                &
     2328                                w(nzb+1:nzt-1,nys:nyn,nxl:nxr),                 &
    22792329                                nxl+1, nys+1, nzb+1,                            &
    22802330                                nxr-nxl+1, nyn-nys+1, init_3d%nzw,              &
    22812331                                dynamic_3d )
     2332!
     2333!--          Set bottom and top-boundary                               
     2334             w(nzb,:,:)   = 0.0_wp 
     2335             w(nzt,:,:)   = w(nzt-1,:,:)
     2336             w(nzt+1,:,:) = w(nzt-1,:,:)
    22822337
    22832338          ENDIF
     
    22872342!--    Read potential temperature
    22882343       IF ( .NOT. neutral )  THEN
    2289           IF ( check_existence( var_names, 'init_pt' ) )  THEN
     2344          IF ( check_existence( var_names, 'init_atmosphere_pt' ) )  THEN
    22902345!
    22912346!--          Read attributes for the fill value and level-of-detail
    22922347             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_pt,       &
    2293                                  .FALSE., 'init_pt' )
     2348                                 .FALSE., 'init_atmosphere_pt' )
    22942349             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_pt,         &
    2295                                  .FALSE., 'init_pt' )
     2350                                 .FALSE., 'init_atmosphere_pt' )
    22962351!
    22972352!--          level-of-detail 1 - read initialization profile
     
    22992354                ALLOCATE( init_3d%pt_init(nzb:nzt+1) )
    23002355
    2301                 CALL get_variable( id_dynamic, 'init_pt',                      &
    2302                                    init_3d%pt_init(nzb+1:nzt+1) )
    2303 !
    2304 !--             Set Neumann surface boundary condition for initial profil
    2305                 init_3d%pt_init(nzb) = init_3d%pt_init(nzb+1)
     2356                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
     2357                                   init_3d%pt_init(nzb+1:nzt) )
     2358!
     2359!--             Set Neumann top and surface boundary condition for initial
     2360!--             profil
     2361                init_3d%pt_init(nzb)   = init_3d%pt_init(nzb+1)
     2362                init_3d%pt_init(nzt+1) = init_3d%pt_init(nzt)
    23062363!
    23072364!--          level-of-detail 2 - read 3D initialization data
    23082365             ELSEIF ( init_3d%lod_pt == 2 )  THEN
    23092366
    2310                 CALL get_variable( id_dynamic, 'init_pt',                      &
    2311                                    pt(nzb+1:nzt+1,nys:nyn,nxl:nxr),            &
     2367                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
     2368                                   pt(nzb+1:nzt,nys:nyn,nxl:nxr),              &
    23122369                                   nxl+1, nys+1, nzb+1,                        &
    23132370                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
    23142371                                   dynamic_3d )
    2315 
     2372                                   
     2373!
     2374!--             Set bottom and top-boundary
     2375                pt(nzb,:,:)   = pt(nzb+1,:,:)
     2376                pt(nzt+1,:,:) = pt(nzt,:,:)             
    23162377
    23172378             ENDIF
     
    23222383!--    Read mixing ratio
    23232384       IF ( humidity )  THEN
    2324           IF ( check_existence( var_names, 'init_qv' ) )  THEN
     2385          IF ( check_existence( var_names, 'init_atmosphere_qv' ) )  THEN
    23252386!
    23262387!--          Read attributes for the fill value and level-of-detail
    23272388             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_q,        &
    2328                                  .FALSE., 'init_qv' )
     2389                                 .FALSE., 'init_atmosphere_qv' )
    23292390             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_q,          &
    2330                                  .FALSE., 'init_qv' )
     2391                                 .FALSE., 'init_atmosphere_qv' )
    23312392!
    23322393!--          level-of-detail 1 - read initialization profile
     
    23342395                ALLOCATE( init_3d%q_init(nzb:nzt+1) )
    23352396
    2336                 CALL get_variable( id_dynamic, 'init_qv',                      &
    2337                                    init_3d%q_init(nzb+1:nzt+1) )
    2338 !
    2339 !--             Set Neumann surface boundary condition for initial profil
    2340                 init_3d%q_init(nzb) = init_3d%q_init(nzb+1)
    2341 
     2397                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
     2398                                    init_3d%q_init(nzb+1:nzt) )
     2399!
     2400!--             Set bottom and top boundary condition (Neumann)
     2401                init_3d%q_init(nzb)   = init_3d%q_init(nzb+1)
     2402                init_3d%q_init(nzt+1) = init_3d%q_init(nzt)
    23422403!
    23432404!--          level-of-detail 2 - read 3D initialization data
    23442405             ELSEIF ( init_3d%lod_q == 2 )  THEN
    23452406             
    2346                 CALL get_variable( id_dynamic, 'init_qv',                      &
    2347                                    q(nzb+1:nzt+1,nys:nyn,nxl:nxr),             &
     2407                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
     2408                                   q(nzb+1:nzt,nys:nyn,nxl:nxr),               &
    23482409                                   nxl+1, nys+1, nzb+1,                        &
    23492410                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
    23502411                                   dynamic_3d )
    2351 
    2352 
    2353 
     2412                                   
     2413!
     2414!--             Set bottom and top-boundary
     2415                q(nzb,:,:)   = q(nzb+1,:,:)
     2416                q(nzt+1,:,:) = q(nzt,:,:)
     2417               
    23542418             ENDIF
    23552419             init_3d%from_file_q = .TRUE.
     
    23822446
    23832447               CALL get_variable( id_dynamic, 'init_soil_m',                   &   
    2384                                   init_3d%msoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
    2385                                   nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
     2448                                init_3d%msoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
     2449                                nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
    23862450
    23872451             ENDIF
     
    24132477               
    24142478                CALL get_variable( id_dynamic, 'init_soil_t',                  &   
    2415                                   init_3d%tsoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
    2416                                   nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
     2479                                init_3d%tsoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
     2480                                nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
    24172481             ENDIF
    24182482             init_3d%from_file_tsoil = .TRUE.
     
    24392503          ENDIF
    24402504          IF ( .NOT. check_passed )  THEN
    2441              message_string = 'NetCDF input for u_init must not contain ' //   &
    2442                               'any _FillValues'
     2505             message_string = 'NetCDF input for init_atmosphere_u must ' //    &
     2506                              'not contain any _FillValues'
    24432507             CALL message( 'netcdf_data_input_mod', 'NDI004', 2, 2, 0, 6, 0 )
    24442508          ENDIF
     
    24552519          ENDIF
    24562520          IF ( .NOT. check_passed )  THEN
    2457              message_string = 'NetCDF input for v_init must not contain ' //   &
    2458                               'any _FillValues'
     2521             message_string = 'NetCDF input for init_atmosphere_v must ' //    &
     2522                              'not contain any _FillValues'
    24592523             CALL message( 'netcdf_data_input_mod', 'NDI005', 2, 2, 0, 6, 0 )
    24602524          ENDIF
     
    24712535          ENDIF
    24722536          IF ( .NOT. check_passed )  THEN
    2473              message_string = 'NetCDF input for w_init must not contain ' //   &
    2474                               'any _FillValues'
     2537             message_string = 'NetCDF input for init_atmosphere_w must ' //    &
     2538                              'not contain any _FillValues'
    24752539             CALL message( 'netcdf_data_input_mod', 'NDI006', 2, 2, 0, 6, 0 )
    24762540          ENDIF
     
    24872551          ENDIF
    24882552          IF ( .NOT. check_passed )  THEN
    2489              message_string = 'NetCDF input for pt_init must not contain ' //  &
    2490                               'any _FillValues'
     2553             message_string = 'NetCDF input for init_atmosphere_pt must ' //   &
     2554                              'not contain any _FillValues'
    24912555             CALL message( 'netcdf_data_input_mod', 'NDI007', 2, 2, 0, 6, 0 )
    24922556          ENDIF
     
    25032567          ENDIF
    25042568          IF ( .NOT. check_passed )  THEN
    2505              message_string = 'NetCDF input for q_init must not contain ' //   &
    2506                               'any _FillValues'
     2569             message_string = 'NetCDF input for init_atmosphere_q must ' //    &
     2570                              'not contain any _FillValues'
    25072571             CALL message( 'netcdf_data_input_mod', 'NDI008', 2, 2, 0, 6, 0 )
    25082572          ENDIF
     
    25242588
    25252589       USE control_parameters,                                                 &
    2526            ONLY:  bc_lr_cyc, bc_ns_cyc, force_bound_l, force_bound_n,          &
    2527                   force_bound_r, force_bound_s,                                &
    2528                   forcing, humidity, message_string, neutral, simulated_time
    2529 
     2590           ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,              &
     2591                  bc_dirichlet_s, bc_lr_cyc, bc_ns_cyc, humidity,              &
     2592                  message_string, neutral, nesting_offline,                    &
     2593                  time_since_reference_point
    25302594
    25312595       USE indices,                                                            &
     
    25332597
    25342598       IMPLICIT NONE
    2535 
    2536        LOGICAL      ::  dynamic_3d = .TRUE. !< flag indicating that 3D data is read from dynamic file
    25372599       
    25382600       INTEGER(iwp) ::  i          !< running index along x-direction
     
    25452607       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
    25462608
    2547        force%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic )
     2609       nest_offl%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic )
    25482610!
    25492611!--    Skip input if no forcing from larger-scale models is applied.
    2550        IF ( .NOT. forcing )  RETURN
     2612       IF ( .NOT. nesting_offline )  RETURN
    25512613
    25522614!
     
    25602622                            TRIM( coupling_char ), id_dynamic )
    25612623!
    2562 !--    Initialize INIFOR forcing.
    2563        IF ( .NOT. force%init )  THEN
     2624!--    Initialize INIFOR forcing. 
     2625       IF ( .NOT. nest_offl%init )  THEN
    25642626!
    25652627!--       At first, inquire all variable names.
     
    25672629!
    25682630!--       Allocate memory to store variable names.
    2569           ALLOCATE( force%var_names(1:num_vars) )
    2570           CALL inquire_variable_names( id_dynamic, force%var_names )
     2631          ALLOCATE( nest_offl%var_names(1:num_vars) )
     2632          CALL inquire_variable_names( id_dynamic, nest_offl%var_names )
    25712633!
    25722634!--       Read time dimension, allocate memory and finally read time array
    2573           CALL get_dimension_length( id_dynamic, force%nt, 'time' )
    2574 
    2575           IF ( check_existence( force%var_names, 'time' ) )  THEN
    2576              ALLOCATE( force%time(0:force%nt-1) )
    2577              CALL get_variable( id_dynamic, 'time', force%time )
     2635          CALL get_dimension_length( id_dynamic, nest_offl%nt, 'time' )
     2636
     2637          IF ( check_existence( nest_offl%var_names, 'time' ) )  THEN
     2638             ALLOCATE( nest_offl%time(0:nest_offl%nt-1) )
     2639             CALL get_variable( id_dynamic, 'time', nest_offl%time )
    25782640          ENDIF
    25792641!
    25802642!--       Read vertical dimension of scalar und w grid
    2581           CALL get_dimension_length( id_dynamic, force%nzu, 'z' )
    2582           CALL get_dimension_length( id_dynamic, force%nzw, 'zw' )
    2583 
    2584           IF ( check_existence( force%var_names, 'z' ) )  THEN
    2585              ALLOCATE( force%zu_atmos(1:force%nzu) )
    2586              CALL get_variable( id_dynamic, 'z', force%zu_atmos )
    2587           ENDIF
    2588           IF ( check_existence( force%var_names, 'zw' ) )  THEN
    2589              ALLOCATE( force%zw_atmos(1:force%nzw) )
    2590              CALL get_variable( id_dynamic, 'zw', force%zw_atmos )
     2643          CALL get_dimension_length( id_dynamic, nest_offl%nzu, 'z' )
     2644          CALL get_dimension_length( id_dynamic, nest_offl%nzw, 'zw' )
     2645
     2646          IF ( check_existence( nest_offl%var_names, 'z' ) )  THEN
     2647             ALLOCATE( nest_offl%zu_atmos(1:nest_offl%nzu) )
     2648             CALL get_variable( id_dynamic, 'z', nest_offl%zu_atmos )
     2649          ENDIF
     2650          IF ( check_existence( nest_offl%var_names, 'zw' ) )  THEN
     2651             ALLOCATE( nest_offl%zw_atmos(1:nest_offl%nzw) )
     2652             CALL get_variable( id_dynamic, 'zw', nest_offl%zw_atmos )
    25912653          ENDIF
    25922654
    25932655!
    25942656!--       Read surface pressure
    2595           IF ( check_existence( force%var_names,                               &
    2596                             'surface_forcing_surface_pressure' ) )  THEN
    2597              ALLOCATE( force%surface_pressure(0:force%nt-1) )
     2657          IF ( check_existence( nest_offl%var_names,                           &
     2658                                'surface_forcing_surface_pressure' ) )  THEN
     2659             ALLOCATE( nest_offl%surface_pressure(0:nest_offl%nt-1) )
    25982660             CALL get_variable( id_dynamic,                                    &
    25992661                                'surface_forcing_surface_pressure',            &
    2600                                 force%surface_pressure )
     2662                                nest_offl%surface_pressure )
    26012663          ENDIF
    26022664!
    26032665!--       Set control flag to indicate that initialization is already done
    2604           force%init = .TRUE.
     2666          nest_offl%init = .TRUE.
    26052667
    26062668       ENDIF
     
    26102672!--    @todo: At the moment time, in INIFOR and simulated time correspond
    26112673!--           to each other. If required, adjust to daytime.
    2612        force%tind = MINLOC( ABS( force%time - simulated_time ), DIM = 1 )      &
    2613                     - 1
    2614        force%tind_p = force%tind + 1       
     2674       nest_offl%tind = MINLOC( ABS( nest_offl%time -                          &
     2675                                     time_since_reference_point ), DIM = 1 )   &
     2676                        - 1
     2677       nest_offl%tind_p = nest_offl%tind + 1       
    26152678!
    26162679!--    Read geostrophic wind components. In case of forcing, this is only
    26172680!--    required if cyclic boundary conditions are applied.
    26182681       IF ( bc_lr_cyc  .AND.  bc_ns_cyc )  THEN
    2619           DO  t = force%tind, force%tind_p
     2682          DO  t = nest_offl%tind, nest_offl%tind_p
    26202683!              CALL get_variable_pr( id_dynamic, 'tend_ug', t+1,           &
    2621 !                                    force%ug(t-force%tind,:) )
     2684!                                    nest_offl%ug(t-nest_offl%tind,:) )
    26222685!              CALL get_variable_pr( id_dynamic, 'tend_vg', t+1,           &
    2623 !                                    force%ug(t-force%tind,:) )
     2686!                                    nest_offl%ug(t-nest_offl%tind,:) )
    26242687             CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1,           &
    2625                                    force%ug(t-force%tind,:) )
     2688                                   nest_offl%ug(t-nest_offl%tind,:) )
    26262689             CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1,           &
    2627                                    force%ug(t-force%tind,:) )
     2690                                   nest_offl%ug(t-nest_offl%tind,:) )
    26282691          ENDDO
    26292692       ENDIF
     
    26332696!--    For the v-component, the data starts at nysv, while for the other
    26342697!--    quantities the data starts at nys. This is equivalent at the north
    2635 !--    and south domain boundary for the u-component.
    2636        IF ( force_bound_l )  THEN
     2698!--    and south domain boundary for the u-component.
     2699!--    Further, lateral data is not accessed by parallel IO, indicated by the
     2700!--    last passed flag in the subroutine get_variable(). This is because
     2701!--    not every PE participates in this collective blocking read operation.
     2702       IF ( bc_dirichlet_l )  THEN
    26372703          CALL get_variable( id_dynamic, 'ls_forcing_left_u',                  &
    2638                            force%u_left(0:1,nzb+1:nzt+1,nys:nyn),              &
    2639                            nys+1, nzb+1, force%tind+1,                         &
    2640                            nyn-nys+1, force%nzu, 2, dynamic_3d )
    2641          
     2704                           nest_offl%u_left(0:1,nzb+1:nzt,nys:nyn),            &
     2705                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2706                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     2707     
    26422708          CALL get_variable( id_dynamic, 'ls_forcing_left_v',                  &
    2643                            force%v_left(0:1,nzb+1:nzt+1,nysv:nyn),             &
    2644                            nysv, nzb+1, force%tind+1,                          &
    2645                            nyn-nysv+1, force%nzu, 2, dynamic_3d )
     2709                           nest_offl%v_left(0:1,nzb+1:nzt,nysv:nyn),           &
     2710                           nysv, nzb+1, nest_offl%tind+1,                      &
     2711                           nyn-nysv+1, nest_offl%nzu, 2, .FALSE. )
    26462712
    26472713          CALL get_variable( id_dynamic, 'ls_forcing_left_w',                  &
    2648                            force%w_left(0:1,nzb+1:nzt,nys:nyn),                &
    2649                            nys+1, nzb+1, force%tind+1,                         &
    2650                            nyn-nys+1, force%nzw, 2, dynamic_3d )
     2714                           nest_offl%w_left(0:1,nzb+1:nzt-1,nys:nyn),          &
     2715                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2716                           nyn-nys+1, nest_offl%nzw, 2, .FALSE. )
    26512717
    26522718          IF ( .NOT. neutral )  THEN
    26532719             CALL get_variable( id_dynamic, 'ls_forcing_left_pt',              &
    2654                            force%pt_left(0:1,nzb+1:nzt+1,nys:nyn),             &
    2655                            nys+1, nzb+1, force%tind+1,                         &
    2656                            nyn-nys+1, force%nzu, 2, dynamic_3d )
    2657           ENDIF
     2720                           nest_offl%pt_left(0:1,nzb+1:nzt,nys:nyn),           &
     2721                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2722                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     2723          ENDIF
     2724
    26582725          IF ( humidity )  THEN
    26592726             CALL get_variable( id_dynamic, 'ls_forcing_left_qv',              &
    2660                            force%q_left(0:1,nzb+1:nzt+1,nys:nyn),              &
    2661                            nys+1, nzb+1, force%tind+1,                         &
    2662                            nyn-nys+1, force%nzu, 2, dynamic_3d )
    2663           ENDIF
    2664        ENDIF
    2665 
    2666        IF ( force_bound_r )  THEN
     2727                           nest_offl%q_left(0:1,nzb+1:nzt,nys:nyn),            &
     2728                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2729                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     2730          ENDIF
     2731
     2732       ENDIF
     2733
     2734       IF ( bc_dirichlet_r )  THEN
    26672735          CALL get_variable( id_dynamic, 'ls_forcing_right_u',                 &
    2668                            force%u_right(0:1,nzb+1:nzt+1,nys:nyn),             &
    2669                            nys+1, nzb+1, force%tind+1,                         &
    2670                            nyn-nys+1, force%nzu, 2, dynamic_3d )
     2736                           nest_offl%u_right(0:1,nzb+1:nzt,nys:nyn),           &
     2737                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2738                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
    26712739                           
    26722740          CALL get_variable( id_dynamic, 'ls_forcing_right_v',                 &
    2673                            force%v_right(0:1,nzb+1:nzt+1,nysv:nyn),            &
    2674                            nysv, nzb+1, force%tind+1,                          &
    2675                            nyn-nysv+1, force%nzu, 2, dynamic_3d )
     2741                           nest_offl%v_right(0:1,nzb+1:nzt,nysv:nyn),          &
     2742                           nysv, nzb+1, nest_offl%tind+1,                      &
     2743                           nyn-nysv+1, nest_offl%nzu, 2, .FALSE. )
    26762744                           
    26772745          CALL get_variable( id_dynamic, 'ls_forcing_right_w',                 &
    2678                            force%w_right(0:1,nzb+1:nzt,nys:nyn),               &
    2679                            nys+1, nzb+1, force%tind+1,                         &
    2680                            nyn-nys+1, force%nzw, 2, dynamic_3d )
     2746                           nest_offl%w_right(0:1,nzb+1:nzt-1,nys:nyn),         &
     2747                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2748                           nyn-nys+1, nest_offl%nzw, 2, .FALSE. )
    26812749                           
    26822750          IF ( .NOT. neutral )  THEN
    26832751             CALL get_variable( id_dynamic, 'ls_forcing_right_pt',             &
    2684                            force%pt_right(0:1,nzb+1:nzt+1,nys:nyn),            &
    2685                            nys+1, nzb+1, force%tind+1,                         &
    2686                            nyn-nys+1, force%nzu, 2, dynamic_3d )
     2752                           nest_offl%pt_right(0:1,nzb+1:nzt,nys:nyn),          &
     2753                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2754                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
    26872755          ENDIF
    26882756          IF ( humidity )  THEN
    26892757             CALL get_variable( id_dynamic, 'ls_forcing_right_qv',             &
    2690                            force%q_right(0:1,nzb+1:nzt+1,nys:nyn),             &
    2691                            nys+1, nzb+1, force%tind+1,                         &
    2692                            nyn-nys+1, force%nzu, 2, dynamic_3d )
    2693           ENDIF
    2694        ENDIF
    2695 
    2696        IF ( force_bound_n )  THEN
     2758                           nest_offl%q_right(0:1,nzb+1:nzt,nys:nyn),           &
     2759                           nys+1, nzb+1, nest_offl%tind+1,                     &
     2760                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     2761          ENDIF
     2762       ENDIF
     2763
     2764       IF ( bc_dirichlet_n )  THEN
    26972765       
    26982766          CALL get_variable( id_dynamic, 'ls_forcing_north_u',                 &
    2699                            force%u_north(0:1,nzb+1:nzt+1,nxlu:nxr),            &
    2700                            nxlu, nzb+1, force%tind+1,                          &
    2701                            nxr-nxlu+1, force%nzu, 2, dynamic_3d )
    2702 
     2767                           nest_offl%u_north(0:1,nzb+1:nzt,nxlu:nxr),          &
     2768                           nxlu, nzb+1, nest_offl%tind+1,                      &
     2769                           nxr-nxlu+1, nest_offl%nzu, 2, .FALSE. )
     2770                           
    27032771          CALL get_variable( id_dynamic, 'ls_forcing_north_v',                 &
    2704                            force%v_north(0:1,nzb+1:nzt+1,nxl:nxr),             &
    2705                            nxl+1, nzb+1, force%tind+1,                         &
    2706                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
     2772                           nest_offl%v_north(0:1,nzb+1:nzt,nxl:nxr),           &
     2773                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2774                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    27072775                           
    27082776          CALL get_variable( id_dynamic, 'ls_forcing_north_w',                 &
    2709                            force%w_north(0:1,nzb+1:nzt,nxl:nxr),               &
    2710                            nxl+1, nzb+1, force%tind+1,                         &
    2711                            nxr-nxl+1, force%nzw, 2, dynamic_3d )
     2777                           nest_offl%w_north(0:1,nzb+1:nzt-1,nxl:nxr),         &
     2778                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2779                           nxr-nxl+1, nest_offl%nzw, 2, .FALSE. )
    27122780                           
    27132781          IF ( .NOT. neutral )  THEN
    27142782             CALL get_variable( id_dynamic, 'ls_forcing_north_pt',             &
    2715                            force%pt_north(0:1,nzb+1:nzt+1,nxl:nxr),            &
    2716                            nxl+1, nzb+1, force%tind+1,                         &
    2717                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
     2783                           nest_offl%pt_north(0:1,nzb+1:nzt,nxl:nxr),          &
     2784                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2785                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    27182786          ENDIF
    27192787          IF ( humidity )  THEN
    27202788             CALL get_variable( id_dynamic, 'ls_forcing_north_qv',             &
    2721                            force%q_north(0:1,nzb+1:nzt+1,nxl:nxr),             &
    2722                            nxl+1, nzb+1, force%tind+1,                         &
    2723                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
    2724           ENDIF
    2725        ENDIF
    2726 
    2727        IF ( force_bound_s )  THEN
     2789                           nest_offl%q_north(0:1,nzb+1:nzt,nxl:nxr),           &
     2790                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2791                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
     2792          ENDIF
     2793       ENDIF
     2794
     2795       IF ( bc_dirichlet_s )  THEN
    27282796          CALL get_variable( id_dynamic, 'ls_forcing_south_u',                 &
    2729                            force%u_south(0:1,nzb+1:nzt+1,nxlu:nxr),            &
    2730                            nxlu, nzb+1, force%tind+1,                          &
    2731                            nxr-nxlu+1, force%nzu, 2, dynamic_3d )
     2797                           nest_offl%u_south(0:1,nzb+1:nzt,nxlu:nxr),          &
     2798                           nxlu, nzb+1, nest_offl%tind+1,                      &
     2799                           nxr-nxlu+1, nest_offl%nzu, 2, .FALSE. )
    27322800
    27332801          CALL get_variable( id_dynamic, 'ls_forcing_south_v',                 &
    2734                            force%v_south(0:1,nzb+1:nzt+1,nxl:nxr),             &
    2735                            nxl+1, nzb+1, force%tind+1,                         &
    2736                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
     2802                           nest_offl%v_south(0:1,nzb+1:nzt,nxl:nxr),           &
     2803                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2804                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    27372805                           
    27382806          CALL get_variable( id_dynamic, 'ls_forcing_south_w',                 &
    2739                            force%w_south(0:1,nzb+1:nzt,nxl:nxr),               &
    2740                            nxl+1, nzb+1, force%tind+1,                         &
    2741                            nxr-nxl+1, force%nzw, 2, dynamic_3d )
     2807                           nest_offl%w_south(0:1,nzb+1:nzt-1,nxl:nxr),         &
     2808                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2809                           nxr-nxl+1, nest_offl%nzw, 2, .FALSE. )
    27422810                           
    27432811          IF ( .NOT. neutral )  THEN
    27442812             CALL get_variable( id_dynamic, 'ls_forcing_south_pt',             &
    2745                            force%pt_south(0:1,nzb+1:nzt+1,nxl:nxr),            &
    2746                            nxl+1, nzb+1, force%tind+1,                         &
    2747                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
     2813                           nest_offl%pt_south(0:1,nzb+1:nzt,nxl:nxr),          &
     2814                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2815                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    27482816          ENDIF
    27492817          IF ( humidity )  THEN
    27502818             CALL get_variable( id_dynamic, 'ls_forcing_south_qv',             &
    2751                            force%q_south(0:1,nzb+1:nzt+1,nxl:nxr),             &
    2752                            nxl+1, nzb+1, force%tind+1,                         &
    2753                            nxr-nxl+1, force%nzu, 2, dynamic_3d )
    2754           ENDIF
    2755        ENDIF
     2819                           nest_offl%q_south(0:1,nzb+1:nzt,nxl:nxr),           &
     2820                           nxl+1, nzb+1, nest_offl%tind+1,                     &
     2821                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
     2822          ENDIF
     2823       ENDIF
     2824
    27562825!
    27572826!--    Top boundary
    27582827       CALL get_variable( id_dynamic, 'ls_forcing_top_u',                      &
    2759                              force%u_top(0:1,nys:nyn,nxlu:nxr),                &
    2760                              nxlu, nys+1, force%tind+1,                        &
    2761                              nxr-nxlu+1, nyn-nys+1, 2, dynamic_3d )
     2828                             nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),            &
     2829                             nxlu, nys+1, nest_offl%tind+1,                    &
     2830                             nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
    27622831
    27632832       CALL get_variable( id_dynamic, 'ls_forcing_top_v',                      &
    2764                              force%v_top(0:1,nysv:nyn,nxl:nxr),                &
    2765                              nxl+1, nysv, force%tind+1,                        &
    2766                              nxr-nxl+1, nyn-nysv+1, 2, dynamic_3d )
     2833                             nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),            &
     2834                             nxl+1, nysv, nest_offl%tind+1,                    &
     2835                             nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
    27672836                             
    27682837       CALL get_variable( id_dynamic, 'ls_forcing_top_w',                      &
    2769                              force%w_top(0:1,nys:nyn,nxl:nxr),                 &
    2770                              nxl+1, nys+1, force%tind+1,                       &
    2771                              nxr-nxl+1, nyn-nys+1, 2, dynamic_3d )
     2838                             nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
     2839                             nxl+1, nys+1, nest_offl%tind+1,                   &
     2840                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    27722841                             
    27732842       IF ( .NOT. neutral )  THEN
    27742843          CALL get_variable( id_dynamic, 'ls_forcing_top_pt',                  &
    2775                                 force%pt_top(0:1,nys:nyn,nxl:nxr),             &
    2776                                 nxl+1, nys+1, force%tind+1,                    &
    2777                                 nxr-nxl+1, nyn-nys+1, 2, dynamic_3d )
     2844                                nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),         &
     2845                                nxl+1, nys+1, nest_offl%tind+1,                &
     2846                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    27782847       ENDIF
    27792848       IF ( humidity )  THEN
    27802849          CALL get_variable( id_dynamic, 'ls_forcing_top_qv',                  &
    2781                                 force%q_top(0:1,nys:nyn,nxl:nxr),              &
    2782                                 nxl+1, nys+1, force%tind+1,                    &
    2783                                 nxr-nxl+1, nyn-nys+1, 2, dynamic_3d )
     2850                                nest_offl%q_top(0:1,nys:nyn,nxl:nxr),          &
     2851                                nxl+1, nys+1, nest_offl%tind+1,                &
     2852                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    27842853       ENDIF
    27852854
     
    27922861       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
    27932862
    2794 !
    2795 !--    Finally, after data input set control flag indicating that vertical
    2796 !--    inter- and/or extrapolation is required.
    2797 !--    Please note, inter/extrapolation of INIFOR data is only a workaroud,
    2798 !--    as long as INIFOR delivers vertically equidistant data.
    2799        force%interpolated = .FALSE.
    2800 
    28012863    END SUBROUTINE netcdf_data_input_lsf
    28022864
     
    28102872
    28112873       USE control_parameters,                                                 &
    2812            ONLY:  initializing_actions, forcing, message_string
     2874           ONLY:  initializing_actions, message_string, nesting_offline
    28132875
    28142876       IMPLICIT NONE
     
    28162878!
    28172879!--    In case of forcing, check whether dynamic input file is present
    2818        IF ( .NOT. input_pids_dynamic  .AND.  forcing )  THEN
    2819           message_string = 'forcing = .TRUE. requires dynamic input file ' //  &
     2880       IF ( .NOT. input_pids_dynamic  .AND.  nesting_offline  )  THEN
     2881          message_string = 'nesting_offline = .TRUE. requires dynamic '  //    &
     2882                            'input file ' //                                   &
    28202883                            TRIM( input_file_dynamic ) // TRIM( coupling_char )
    28212884          CALL message( 'netcdf_data_input_mod', 'NDI009', 1, 2, 0, 6, 0 )
     
    45144577!------------------------------------------------------------------------------!
    45154578    SUBROUTINE get_variable_3d_real_dynamic( id, variable_name, var,           &
    4516                             i1s, i2s, i3s, count_1, count_2, count_3, dynamic)
     4579                                             i1s, i2s, i3s,                    &
     4580                                             count_1, count_2, count_3,        &
     4581                                             par_access )
    45174582                               
    45184583       USE indices
     
    45234588       CHARACTER(LEN=*)              ::  variable_name   !< variable name
    45244589
    4525        LOGICAL                       ::  dynamic         !< additional flag just used to select correct overloaded routine from interface block
     4590       LOGICAL                       ::  par_access      !< additional flag indicating whether parallel read operations should be performed or not
    45264591       
    45274592       INTEGER(iwp)                  ::  count_1         !< number of elements to be read along 1st dimension (with respect to file)
     
    45504615#if defined( __netcdf )
    45514616!
    4552 !--    Inquire variable id
     4617!--    Inquire variable id.
    45534618       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    45544619!
    45554620!--    Check for collective read-operation and set respective NetCDF flags if
    45564621!--    required.
    4557        IF ( collective_read )  THEN
     4622!--    Please note, in contrast to the other input routines where each PEs
     4623!--    reads its subdomain data, dynamic input data not by all PEs, only
     4624!--    by those which encompass lateral model boundaries. Hence, collective
     4625!--    read operations are only enabled for top-boundary data.
     4626       IF ( collective_read  .AND.  par_access )  THEN
    45584627          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
    45594628       ENDIF   
Note: See TracChangeset for help on using the changeset viewer.