Ignore:
Timestamp:
Sep 10, 2019 5:03:24 PM (5 years ago)
Author:
suehring
Message:

Offline nesting: data input modularized; time variable is defined relative to time_utc_init, so that input data is correctly mapped to actual model time; checks rephrased and new checks for the time dimension added; Netcdf input: routine to retrieve dimension length renamed

File:
1 edited

Legend:

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

    r4190 r4226  
    2525! -----------------
    2626! $Id$
     27! - Netcdf input routine for dimension length renamed
     28! - Move offline-nesting-specific checks to nesting_offl_mod
     29! - Module-specific input of boundary data for offline nesting moved to
     30!   nesting_offl_mod
     31! - Define module specific data type for offline nesting in nesting_offl_mod
     32!
     33! 4190 2019-08-27 15:42:37Z suehring
    2734! type real_1d changed to real_1d_3d
    2835!
     
    169176       REAL(wp), DIMENSION(:), ALLOCATABLE :: z       !< dimension array in z
    170177    END TYPE dims_xy
    171 !
    172 !-- Define data type for nesting in larger-scale models like COSMO.
    173 !-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
    174     TYPE nest_offl_type
    175 
    176        CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'  !< leading substring for variables at left boundary
    177        CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_' !< leading substring for variables at north boundary 
    178        CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_' !< leading substring for variables at right boundary 
    179        CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring for variables at south boundary
    180        CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring for variables at top boundary
    181 
    182        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names         !< list of variable in dynamic input file
    183        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_l  !< names of mesoscale nested chemistry variables at left boundary
    184        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_n  !< names of mesoscale nested chemistry variables at north boundary
    185        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_r  !< names of mesoscale nested chemistry variables at right boundary
    186        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_s  !< names of mesoscale nested chemistry variables at south boundary
    187        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_t  !< names of mesoscale nested chemistry variables at top boundary
    188 
    189        INTEGER(iwp) ::  nt     !< number of time levels in dynamic input file
    190        INTEGER(iwp) ::  nzu    !< number of vertical levels on scalar grid in dynamic input file
    191        INTEGER(iwp) ::  nzw    !< number of vertical levels on w grid in dynamic input file
    192        INTEGER(iwp) ::  tind   !< time index for reference time in mesoscale-offline nesting
    193        INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
    194 
    195        LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
    196 
    197        LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 
    198        LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_n !< flags inidicating whether north boundary data for chemistry is in dynamic input file
    199        LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_r !< flags inidicating whether right boundary data for chemistry is in dynamic input file
    200        LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_s !< flags inidicating whether south boundary data for chemistry is in dynamic input file
    201        LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_t !< flags inidicating whether top boundary data for chemistry is in dynamic input file
    202 
    203        REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure !< time dependent surface pressure
    204        REAL(wp), DIMENSION(:), ALLOCATABLE ::  time             !< time levels in dynamic input file
    205        REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos         !< vertical levels at scalar grid in dynamic input file
    206        REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos         !< vertical levels at w grid in dynamic input file
    207 
    208        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ug         !< domain-averaged geostrophic component
    209        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vg         !< domain-averaged geostrophic component
    210 
    211        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_left   !< u-component at left boundary
    212        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_left   !< v-component at left boundary
    213        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_left   !< w-component at left boundary
    214        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_left   !< mixing ratio at left boundary
    215        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_left  !< potentital temperautre at left boundary
    216 
    217        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_north  !< u-component at north boundary
    218        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_north  !< v-component at north boundary
    219        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_north  !< w-component at north boundary
    220        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_north  !< mixing ratio at north boundary
    221        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_north !< potentital temperautre at north boundary
    222 
    223        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_right  !< u-component at right boundary
    224        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_right  !< v-component at right boundary
    225        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_right  !< w-component at right boundary
    226        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_right  !< mixing ratio at right boundary
    227        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_right !< potentital temperautre at right boundary
    228 
    229        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_south  !< u-component at south boundary
    230        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_south  !< v-component at south boundary
    231        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_south  !< w-component at south boundary
    232        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_south  !< mixing ratio at south boundary
    233        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_south !< potentital temperautre at south boundary
    234 
    235        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_top    !< u-component at top boundary
    236        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_top    !< v-component at top boundary
    237        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_top    !< w-component at top boundary
    238        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
    239        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
    240        
    241        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_left   !< chemical species at left boundary
    242        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_north  !< chemical species at left boundary
    243        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_right  !< chemical species at left boundary
    244        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_south  !< chemical species at left boundary
    245        REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top    !< chemical species at left boundary
    246 
    247     END TYPE nest_offl_type
    248 
    249178    TYPE init_type
    250179
     
    571500    TYPE(crs_type)   ::  coord_ref_sys  !< coordinate reference system
    572501
    573     TYPE(dims_xy)    ::  dim_static     !< data structure for x, y-dimension in static input file
    574 
    575     TYPE(nest_offl_type) ::  nest_offl  !< data structure for data input at lateral and top boundaries (provided by Inifor) 
     502    TYPE(dims_xy)    ::  dim_static     !< data structure for x, y-dimension in static input file
    576503
    577504    TYPE(init_type) ::  init_3d    !< data structure for the initialization of the 3D flow and soil fields
     
    679606    END INTERFACE netcdf_data_input_chemistry_data
    680607   
    681     INTERFACE netcdf_data_input_get_dimension_length                       
    682        MODULE PROCEDURE netcdf_data_input_get_dimension_length
    683     END INTERFACE netcdf_data_input_get_dimension_length
     608    INTERFACE get_dimension_length                       
     609       MODULE PROCEDURE get_dimension_length
     610    END INTERFACE get_dimension_length
    684611
    685612    INTERFACE netcdf_data_input_inquire_file
     
    705632       MODULE PROCEDURE netcdf_data_input_init_lsm
    706633    END INTERFACE netcdf_data_input_init_lsm
    707 
    708     INTERFACE netcdf_data_input_offline_nesting
    709        MODULE PROCEDURE netcdf_data_input_offline_nesting
    710     END INTERFACE netcdf_data_input_offline_nesting
    711634
    712635    INTERFACE netcdf_data_input_surface_data
     
    770693           input_pids_static,                                                  &
    771694           input_pids_dynamic, input_pids_vm, input_file_vm,                   &
    772            leaf_area_density_f, nest_offl,                                     &
     695           leaf_area_density_f,                                                &
    773696           num_var_pids,                                                       &
    774697           pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,       &
     
    790713    PUBLIC netcdf_data_input_check_dynamic, netcdf_data_input_check_static,    &
    791714           netcdf_data_input_chemistry_data,                                   &
    792            netcdf_data_input_get_dimension_length,                             &
     715           get_dimension_length,                                               &
    793716           netcdf_data_input_inquire_file,                                     &
    794717           netcdf_data_input_init, netcdf_data_input_init_lsm,                 &
    795718           netcdf_data_input_init_3d, netcdf_data_input_att,                   &
    796            netcdf_data_input_interpolate, netcdf_data_input_offline_nesting,   &
     719           netcdf_data_input_interpolate,                                      &
    797720           netcdf_data_input_surface_data, netcdf_data_input_topo,             &
    798            netcdf_data_input_var, get_attribute, get_variable, open_read_file, &
    799            check_existence, inquire_num_variables, inquire_variable_names,     &
     721           netcdf_data_input_var,                                              &
     722           get_attribute,                                                      &
     723           get_variable,                                                       &
     724           get_variable_pr,                                                    &
     725           open_read_file,                                                     &
     726           check_existence,                                                    &
     727           inquire_num_variables,                                              &
     728           inquire_variable_names,                                             &
    800729           close_input_file
    801730
     
    13471276!-- Tther dimensions depend on the emission mode or specific components
    13481277
    1349           CALL netcdf_data_input_get_dimension_length (    &
    1350                                  id_emis, emt_att%n_emiss_species, 'nspecies' )
     1278          CALL get_dimension_length ( id_emis, emt_att%n_emiss_species, 'nspecies' )
    13511279
    13521280!
     
    14081336!-- get number of emission categories
    14091337
    1410              CALL netcdf_data_input_get_dimension_length (           &
    1411                                     id_emis, emt_att%ncat, 'ncat' )
     1338             CALL get_dimension_length ( id_emis, emt_att%ncat, 'ncat' )
    14121339
    14131340!-- READING IN EMISSION CATEGORIES INDICES
     
    14451372!
    14461373!-- VOC name
    1447                    CALL netcdf_data_input_get_dimension_length (     &
    1448                                           id_emis, emt_att%nvoc, 'nvoc' )
     1374                   CALL get_dimension_length ( id_emis, emt_att%nvoc, 'nvoc' )
    14491375                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
    14501376                   CALL get_variable ( id_emis,"emission_voc_name",  &
     
    14711397!-- PM name
    14721398
    1473                    CALL netcdf_data_input_get_dimension_length (     &
    1474                                           id_emis, emt_att%npm, 'npm' )
     1399                   CALL get_dimension_length ( id_emis, emt_att%npm, 'npm' )
    14751400                   ALLOCATE ( emt_att%pm_name(emt_att%npm) )
    14761401                   CALL get_variable ( id_emis, "pm_name", string_values, emt_att%npm )
     
    15221447                   TRIM(time_fac_type) == "hour" )  THEN
    15231448
    1524                 CALL netcdf_data_input_get_dimension_length (                  &
    1525                                        id_emis, emt_att%nhoursyear, 'nhoursyear' )
     1449                CALL get_dimension_length ( id_emis, emt_att%nhoursyear, 'nhoursyear' )
    15261450                ALLOCATE ( emt_att%hourly_emis_time_factor(emt_att%ncat,emt_att%nhoursyear) )
    15271451                CALL get_variable ( id_emis, "emission_time_factors",          &
     
    15351459                        TRIM(time_fac_type)  ==  "mdh" )  THEN
    15361460
    1537                 CALL netcdf_data_input_get_dimension_length (                  &
    1538                                        id_emis, emt_att%nmonthdayhour, 'nmonthdayhour' )
     1461                CALL get_dimension_length ( id_emis, emt_att%nmonthdayhour, 'nmonthdayhour' )
    15391462                ALLOCATE ( emt_att%mdh_emis_time_factor(emt_att%ncat,emt_att%nmonthdayhour) )
    15401463                CALL get_variable ( id_emis, "emission_time_factors",          &
     
    16521575!
    16531576!-- VOC name
    1654                    CALL netcdf_data_input_get_dimension_length (                         &
    1655                                           id_emis, emt_att%nvoc, 'nvoc' )
     1577                   CALL get_dimension_length ( id_emis, emt_att%nvoc, 'nvoc' )
    16561578                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
    16571579                   CALL get_variable ( id_emis, "emission_voc_name",                     &
     
    16731595!-- EMISSION DATA
    16741596
    1675              CALL netcdf_data_input_get_dimension_length (                               &
    1676                                     id_emis, emt_att%dt_emission, 'time' )   
     1597             CALL get_dimension_length ( id_emis, emt_att%dt_emission, 'time' )   
    16771598 
    16781599!
     
    18051726!
    18061727!--          Inquire number of vertical vegetation layer
    1807              CALL netcdf_data_input_get_dimension_length( id_surf,             &
    1808                                                  leaf_area_density_f%nz,       &
    1809                                                  'zlad' )
     1728             CALL get_dimension_length( id_surf,                               &
     1729                                        leaf_area_density_f%nz,                &
     1730                                        'zlad' )
    18101731!
    18111732!--          Allocate variable for leaf-area density
     
    18301751!
    18311752!--          Inquire number of vertical vegetation layer
    1832              CALL netcdf_data_input_get_dimension_length( id_surf,             &
    1833                                                  basal_area_density_f%nz,      &
    1834                                                  'zlad' )
     1753             CALL get_dimension_length( id_surf,                               &
     1754                                        basal_area_density_f%nz,               &
     1755                                        'zlad' )
    18351756!
    18361757!--          Allocate variable
     
    18541775!
    18551776!--          Inquire number of vertical soil layers
    1856              CALL netcdf_data_input_get_dimension_length( id_surf,             &
     1777             CALL get_dimension_length( id_surf,             &
    18571778                                                   root_area_density_lad_f%nz, &
    18581779                                                  'zsoil' )
     
    19361857!
    19371858!--          Obtain number of soil layers from file.
    1938              CALL netcdf_data_input_get_dimension_length( id_surf, nz_soil,    &
    1939                                                           'zsoil' )
     1859             CALL get_dimension_length( id_surf, nz_soil, 'zsoil' )
    19401860
    19411861             ALLOCATE ( soil_type_f%var_3d(0:nz_soil,nys:nyn,nxl:nxr) )
     
    19891909!
    19901910!--       Inquire number of surface fractions
    1991           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    1992                                                        surface_fraction_f%nf,  &
    1993                                                        'nsurface_fraction' )
     1911          CALL get_dimension_length( id_surf,                                  &
     1912                                     surface_fraction_f%nf,                    &
     1913                                     'nsurface_fraction' )
    19941914!
    19951915!--       Allocate dimension array and input array for surface fractions
     
    20181938!
    20191939!--       Inquire number of building parameters
    2020           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2021                                                        building_pars_f%np,     &
    2022                                                        'nbuilding_pars' )
     1940          CALL get_dimension_length( id_surf,                                  &
     1941                                      building_pars_f%np,                      &
     1942                                      'nbuilding_pars' )
    20231943!
    20241944!--       Allocate dimension array and input array for building parameters
     
    20611981!
    20621982!--       Inquire number of albedo parameters
    2063           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2064                                                        albedo_pars_f%np,       &
    2065                                                        'nalbedo_pars' )
     1983          CALL get_dimension_length( id_surf,                                  &
     1984                                     albedo_pars_f%np,                         &
     1985                                     'nalbedo_pars' )
    20661986!
    20671987!--       Allocate dimension array and input array for albedo parameters
     
    20892009!
    20902010!--       Inquire number of pavement parameters
    2091           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2092                                                        pavement_pars_f%np,     &
    2093                                                        'npavement_pars' )
     2011          CALL get_dimension_length( id_surf,                                  &
     2012                                     pavement_pars_f%np,                       &
     2013                                     'npavement_pars' )
    20942014!
    20952015!--       Allocate dimension array and input array for pavement parameters
     
    21182038!
    21192039!--       Inquire number of parameters
    2120           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2121                                                 pavement_subsurface_pars_f%np, &
    2122                                                'npavement_subsurface_pars' )
     2040          CALL get_dimension_length( id_surf,                                  &
     2041                                     pavement_subsurface_pars_f%np,            &
     2042                                     'npavement_subsurface_pars' )
    21232043!
    21242044!--       Inquire number of soil layers
    2125           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2126                                                 pavement_subsurface_pars_f%nz, &
    2127                                                 'zsoil' )
     2045          CALL get_dimension_length( id_surf,                                  &
     2046                                     pavement_subsurface_pars_f%nz,            &
     2047                                     'zsoil' )
    21282048!
    21292049!--       Allocate dimension array and input array for pavement parameters
     
    21582078!
    21592079!--       Inquire number of vegetation parameters
    2160           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2161                                                        vegetation_pars_f%np,   &
    2162                                                        'nvegetation_pars' )
     2080          CALL get_dimension_length( id_surf,                                  &
     2081                                     vegetation_pars_f%np,                     &
     2082                                     'nvegetation_pars' )
    21632083!
    21642084!--       Allocate dimension array and input array for surface fractions
     
    21922112!
    21932113!--       Inquire number of soil parameters
    2194           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2195                                                        soil_pars_f%np,         &
    2196                                                        'nsoil_pars' )
     2114          CALL get_dimension_length( id_surf,                                  &
     2115                                     soil_pars_f%np,                           &
     2116                                     'nsoil_pars' )
    21972117!
    21982118!--       Read parameters array
     
    22042124!--       soil layers, allocate memory and read the respective dimension
    22052125          IF ( soil_pars_f%lod == 2 )  THEN
    2206              CALL netcdf_data_input_get_dimension_length( id_surf,             &
    2207                                                           soil_pars_f%nz,      &
    2208                                                           'zsoil' )
     2126             CALL get_dimension_length( id_surf,                               &
     2127                                        soil_pars_f%nz,                        &
     2128                                        'zsoil' )
    22092129
    22102130             ALLOCATE( soil_pars_f%layers(0:soil_pars_f%nz-1) )
     
    22452165!
    22462166!--       Inquire number of water parameters
    2247           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2248                                                        water_pars_f%np,        &
    2249                                                        'nwater_pars' )
     2167          CALL get_dimension_length( id_surf,                                  &
     2168                                     water_pars_f%np,                          &
     2169                                     'nwater_pars' )
    22502170!
    22512171!--       Allocate dimension array and input array for water parameters
     
    22712191!
    22722192!--       Obtain number of soil layers from file and allocate variable
    2273           CALL netcdf_data_input_get_dimension_length( id_surf,                &
    2274                                                    root_area_density_lsm_f%nz, &
    2275                                                    'zsoil' )
     2193          CALL get_dimension_length( id_surf,                                  &
     2194                                     root_area_density_lsm_f%nz,              &
     2195                                     'zsoil' )
    22762196          ALLOCATE( root_area_density_lsm_f%var                                &
    22772197                                        (0:root_area_density_lsm_f%nz-1,       &
     
    26452565!
    26462566!--       Read x, y - dimensions. Only required for consistency checks.
    2647           CALL netcdf_data_input_get_dimension_length( id_topo, dim_static%nx, 'x' )
    2648           CALL netcdf_data_input_get_dimension_length( id_topo, dim_static%ny, 'y' )
     2567          CALL get_dimension_length( id_topo, dim_static%nx, 'x' )
     2568          CALL get_dimension_length( id_topo, dim_static%ny, 'y' )
    26492569          ALLOCATE( dim_static%x(0:dim_static%nx-1) )
    26502570          ALLOCATE( dim_static%y(0:dim_static%ny-1) )
     
    27252645                                 .FALSE., 'buildings_3d' )
    27262646
    2727              CALL netcdf_data_input_get_dimension_length( id_topo,             &
    2728                                                           buildings_f%nz, 'z' )
     2647             CALL get_dimension_length( id_topo, buildings_f%nz, 'z' )
    27292648!
    27302649!--          Read 3D buildings
     
    29412860!
    29422861!--    Read vertical dimension of scalar und w grid.
    2943        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
    2944        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
     2862       CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
     2863       CALL get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
    29452864!
    29462865!--    Read also the horizontal dimensions. These are used just used fo
    29472866!--    checking the compatibility with the PALM grid before reading.
    2948        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
    2949        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nxu, 'xu' )
    2950        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
    2951        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nyv, 'yv' )
     2867       CALL get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
     2868       CALL get_dimension_length( id_dynamic, init_3d%nxu, 'xu' )
     2869       CALL get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
     2870       CALL get_dimension_length( id_dynamic, init_3d%nyv, 'yv' )
    29522871
    29532872!
     
    34443363!--    Read vertical dimension for soil depth.
    34453364       IF ( check_existence( var_names, 'zsoil' ) )                            &
    3446           CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzs,&
    3447                                                        'zsoil' )
     3365          CALL get_dimension_length( id_dynamic, init_3d%nzs, 'zsoil' )
    34483366!
    34493367!--    Read also the horizontal dimensions required for soil initialization.
     
    34513369!--    these data is already available, but will be read again for the sake
    34523370!--    of clearness.
    3453        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nx,    &
    3454                                                     'x'  )
    3455        CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%ny,    &
    3456                                                     'y'  )
     3371       CALL get_dimension_length( id_dynamic, init_3d%nx, 'x'  )
     3372       CALL get_dimension_length( id_dynamic, init_3d%ny, 'y'  )
    34573373!
    34583374!--    Check for correct horizontal and vertical dimension. Please note,
     
    35443460! Description:
    35453461! ------------
    3546 !> Reads data at lateral and top boundaries derived from larger-scale model
    3547 !> (COSMO) by Inifor.
    3548 !------------------------------------------------------------------------------!
    3549     SUBROUTINE netcdf_data_input_offline_nesting
     3462!> Checks input file for consistency and minimum requirements.
     3463!------------------------------------------------------------------------------!
     3464    SUBROUTINE netcdf_data_input_check_dynamic
    35503465
    35513466       USE control_parameters,                                                 &
    3552            ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n,               &
    3553                   bc_dirichlet_r, bc_dirichlet_s, humidity, neutral,           &
    3554                   nesting_offline, time_since_reference_point
    3555 
    3556        USE indices,                                                            &
    3557            ONLY:  nxl, nxlu, nxr, nyn, nys, nysv, nzb, nzt
     3467           ONLY:  initializing_actions, message_string
    35583468
    35593469       IMPLICIT NONE
    3560        
    3561        INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
    3562        INTEGER(iwp) ::  n          !< running index for chemistry variables
    3563        INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    3564        INTEGER(iwp) ::  t          !< running index time dimension
    3565 !
    3566 !--    Skip input if no forcing from larger-scale models is applied.
    3567        IF ( .NOT. nesting_offline )  RETURN
    3568 
    3569 !
    3570 !--    CPU measurement
    3571        CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'start' )
    3572 
    3573 #if defined ( __netcdf )
    3574 !
    3575 !--    Open file in read-only mode
    3576        CALL open_read_file( TRIM( input_file_dynamic ) //                      &
    3577                             TRIM( coupling_char ), id_dynamic )
    3578 !
    3579 !--    Initialize INIFOR forcing.
    3580        IF ( .NOT. nest_offl%init )  THEN
    3581 !
    3582 !--       At first, inquire all variable names.
    3583           CALL inquire_num_variables( id_dynamic, num_vars )
    3584 !
    3585 !--       Allocate memory to store variable names.
    3586           ALLOCATE( nest_offl%var_names(1:num_vars) )
    3587           CALL inquire_variable_names( id_dynamic, nest_offl%var_names )
    3588 !
    3589 !--       Read time dimension, allocate memory and finally read time array
    3590           CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
    3591                                                        nest_offl%nt, 'time' )
    3592 
    3593           IF ( check_existence( nest_offl%var_names, 'time' ) )  THEN
    3594              ALLOCATE( nest_offl%time(0:nest_offl%nt-1) )
    3595              CALL get_variable( id_dynamic, 'time', nest_offl%time )
    3596           ENDIF
    3597 !
    3598 !--       Read vertical dimension of scalar und w grid
    3599           CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
    3600                                                        nest_offl%nzu, 'z' )
    3601           CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
    3602                                                        nest_offl%nzw, 'zw' )
    3603 
    3604           IF ( check_existence( nest_offl%var_names, 'z' ) )  THEN
    3605              ALLOCATE( nest_offl%zu_atmos(1:nest_offl%nzu) )
    3606              CALL get_variable( id_dynamic, 'z', nest_offl%zu_atmos )
    3607           ENDIF
    3608           IF ( check_existence( nest_offl%var_names, 'zw' ) )  THEN
    3609              ALLOCATE( nest_offl%zw_atmos(1:nest_offl%nzw) )
    3610              CALL get_variable( id_dynamic, 'zw', nest_offl%zw_atmos )
    3611           ENDIF
    3612 
    3613 !
    3614 !--       Read surface pressure
    3615           IF ( check_existence( nest_offl%var_names,                           &
    3616                                 'surface_forcing_surface_pressure' ) )  THEN
    3617              ALLOCATE( nest_offl%surface_pressure(0:nest_offl%nt-1) )
    3618              CALL get_variable( id_dynamic,                                    &
    3619                                 'surface_forcing_surface_pressure',            &
    3620                                 nest_offl%surface_pressure )
    3621           ENDIF
    3622 !
    3623 !--       Set control flag to indicate that initialization is already done
    3624           nest_offl%init = .TRUE.
    3625 
    3626        ENDIF
    3627 
    3628 !
    3629 !--    Obtain time index for current input starting at 0.
    3630 !--    @todo: At the moment INIFOR and simulated time correspond
    3631 !--           to each other. If required, adjust to daytime.
    3632        nest_offl%tind = MINLOC( ABS( nest_offl%time -                          &
    3633                                      time_since_reference_point ), DIM = 1 )   &
    3634                         - 1
    3635        nest_offl%tind_p = nest_offl%tind + 1       
    3636 !
    3637 !--    Read geostrophic wind components
    3638        DO  t = nest_offl%tind, nest_offl%tind_p
    3639           CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1,              &
    3640                                 nest_offl%ug(t-nest_offl%tind,nzb+1:nzt) )
    3641           CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1,              &
    3642                                 nest_offl%vg(t-nest_offl%tind,nzb+1:nzt) )
    3643        ENDDO
    3644 !
    3645 !--    Read data at lateral and top boundaries. Please note, at left and
    3646 !--    right domain boundary, yz-layers are read for u, v, w, pt and q.
    3647 !--    For the v-component, the data starts at nysv, while for the other
    3648 !--    quantities the data starts at nys. This is equivalent at the north
    3649 !--    and south domain boundary for the u-component.
    3650 !--    Note, lateral data is also accessed by parallel IO, which is the reason
    3651 !--    why different arguments are passed depending on the boundary control
    3652 !--    flags. Cores that do not belong to the respective boundary just make
    3653 !--    a dummy read with count = 0, just in order to participate the collective
    3654 !--    operation.
    3655 !--    Read data for western boundary   
    3656        CALL get_variable( id_dynamic, 'ls_forcing_left_u',                     &
    3657                           nest_offl%u_left,                                    & ! array to be read
    3658                           MERGE( nys+1, 1, bc_dirichlet_l),                    & ! start index y direction
    3659                           MERGE( nzb+1, 1, bc_dirichlet_l),                    & ! start index z direction
    3660                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         & ! start index time dimension
    3661                           MERGE( nyn-nys+1, 0, bc_dirichlet_l),                & ! number of elements along y
    3662                           MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            & ! number of elements alogn z
    3663                           MERGE( 2, 0, bc_dirichlet_l),                        & ! number of time steps (2 or 0)
    3664                           .TRUE. )                                               ! parallel IO when compiled accordingly
    3665      
    3666        CALL get_variable( id_dynamic, 'ls_forcing_left_v',                     &
    3667                           nest_offl%v_left,                                    &
    3668                           MERGE( nysv, 1, bc_dirichlet_l),                     &
    3669                           MERGE( nzb+1, 1, bc_dirichlet_l),                    &
    3670                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
    3671                           MERGE( nyn-nysv+1, 0, bc_dirichlet_l),               &
    3672                           MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            &
    3673                           MERGE( 2, 0, bc_dirichlet_l),                        &
    3674                           .TRUE. )                                       
    3675 
    3676        CALL get_variable( id_dynamic, 'ls_forcing_left_w',                     &
    3677                           nest_offl%w_left,                                    &
    3678                           MERGE( nys+1, 1, bc_dirichlet_l),                    &
    3679                           MERGE( nzb+1, 1, bc_dirichlet_l),                    &
    3680                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
    3681                           MERGE( nyn-nys+1, 0, bc_dirichlet_l),                &
    3682                           MERGE( nest_offl%nzw, 0, bc_dirichlet_l),            &
    3683                           MERGE( 2, 0, bc_dirichlet_l),                        &
    3684                           .TRUE. )   
    3685 
    3686        IF ( .NOT. neutral )  THEN
    3687           CALL get_variable( id_dynamic, 'ls_forcing_left_pt',                 &
    3688                              nest_offl%pt_left,                                &
    3689                              MERGE( nys+1, 1, bc_dirichlet_l),                 &
    3690                              MERGE( nzb+1, 1, bc_dirichlet_l),                 &
    3691                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
    3692                              MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
    3693                              MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
    3694                              MERGE( 2, 0, bc_dirichlet_l),                     &
    3695                              .TRUE. )
    3696        ENDIF
    3697 
    3698        IF ( humidity )  THEN
    3699           CALL get_variable( id_dynamic, 'ls_forcing_left_qv',                 &
    3700                              nest_offl%q_left,                                 &
    3701                              MERGE( nys+1, 1, bc_dirichlet_l),                 &
    3702                              MERGE( nzb+1, 1, bc_dirichlet_l),                 &
    3703                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
    3704                              MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
    3705                              MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
    3706                              MERGE( 2, 0, bc_dirichlet_l),                     &
    3707                              .TRUE. )
    3708        ENDIF
    3709        
    3710        IF ( air_chemistry )  THEN
    3711           DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
    3712              IF ( check_existence( nest_offl%var_names,                        &
    3713                                    nest_offl%var_names_chem_l(n) ) )  THEN 
    3714                 CALL get_variable( id_dynamic,                                 &
    3715                            TRIM( nest_offl%var_names_chem_l(n) ),              &
    3716                            nest_offl%chem_left(:,:,:,n),                       &
    3717                            MERGE( nys+1, 1, bc_dirichlet_l),                   &
    3718                            MERGE( nzb+1, 1, bc_dirichlet_l),                   &
    3719                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),        &
    3720                            MERGE( nyn-nys+1, 0, bc_dirichlet_l),               &
    3721                            MERGE( nest_offl%nzu, 0, bc_dirichlet_l),           &
    3722                            MERGE( 2, 0, bc_dirichlet_l),                       &
    3723                            .TRUE. )
    3724                 nest_offl%chem_from_file_l(n) = .TRUE.
    3725              ENDIF
    3726           ENDDO
    3727        ENDIF
    3728 !
    3729 !--    Read data for eastern boundary   
    3730        CALL get_variable( id_dynamic, 'ls_forcing_right_u',                    &
    3731                           nest_offl%u_right,                                   &
    3732                           MERGE( nys+1, 1, bc_dirichlet_r),                    &
    3733                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    3734                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    3735                           MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
    3736                           MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
    3737                           MERGE( 2, 0, bc_dirichlet_r),                        &
    3738                           .TRUE. )                                             
    3739      
    3740        CALL get_variable( id_dynamic, 'ls_forcing_right_v',                    &
    3741                           nest_offl%v_right,                                   &
    3742                           MERGE( nysv, 1, bc_dirichlet_r),                     &
    3743                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    3744                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    3745                           MERGE( nyn-nysv+1, 0, bc_dirichlet_r),               &
    3746                           MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
    3747                           MERGE( 2, 0, bc_dirichlet_r),                        &
    3748                           .TRUE. )                                             
    3749 
    3750        CALL get_variable( id_dynamic, 'ls_forcing_right_w',                    &
    3751                           nest_offl%w_right,                                   &
    3752                           MERGE( nys+1, 1, bc_dirichlet_r),                    &
    3753                           MERGE( nzb+1, 1, bc_dirichlet_r),                    &
    3754                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
    3755                           MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
    3756                           MERGE( nest_offl%nzw, 0, bc_dirichlet_r),            &
    3757                           MERGE( 2, 0, bc_dirichlet_r),                        &
    3758                           .TRUE. )   
    3759 
    3760        IF ( .NOT. neutral )  THEN
    3761           CALL get_variable( id_dynamic, 'ls_forcing_right_pt',                &
    3762                              nest_offl%pt_right,                               &
    3763                              MERGE( nys+1, 1, bc_dirichlet_r),                 &
    3764                              MERGE( nzb+1, 1, bc_dirichlet_r),                 &
    3765                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
    3766                              MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
    3767                              MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
    3768                              MERGE( 2, 0, bc_dirichlet_r),                     &
    3769                              .TRUE. )
    3770        ENDIF
    3771 
    3772        IF ( humidity )  THEN
    3773           CALL get_variable( id_dynamic, 'ls_forcing_right_qv',                &
    3774                              nest_offl%q_right,                                &
    3775                              MERGE( nys+1, 1, bc_dirichlet_r),                 &
    3776                              MERGE( nzb+1, 1, bc_dirichlet_r),                 &
    3777                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
    3778                              MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
    3779                              MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
    3780                              MERGE( 2, 0, bc_dirichlet_r),                     &
    3781                              .TRUE. )
    3782        ENDIF
    3783        
    3784        IF ( air_chemistry )  THEN
    3785           DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
    3786              IF ( check_existence( nest_offl%var_names,                        &
    3787                                    nest_offl%var_names_chem_r(n) ) )  THEN     
    3788                 CALL get_variable( id_dynamic,                                 &
    3789                            TRIM( nest_offl%var_names_chem_r(n) ),              &
    3790                            nest_offl%chem_right(:,:,:,n),                      &
    3791                            MERGE( nys+1, 1, bc_dirichlet_r),                   &
    3792                            MERGE( nzb+1, 1, bc_dirichlet_r),                   &
    3793                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),        &
    3794                            MERGE( nyn-nys+1, 0, bc_dirichlet_r),               &
    3795                            MERGE( nest_offl%nzu, 0, bc_dirichlet_r),           &
    3796                            MERGE( 2, 0, bc_dirichlet_r),                       &
    3797                            .TRUE. )
    3798                 nest_offl%chem_from_file_r(n) = .TRUE.
    3799              ENDIF
    3800           ENDDO
    3801        ENDIF
    3802 !
    3803 !--    Read data for northern boundary
    3804        CALL get_variable( id_dynamic, 'ls_forcing_north_u',                    & ! array to be read
    3805                           nest_offl%u_north,                                   & ! start index x direction
    3806                           MERGE( nxlu, 1, bc_dirichlet_n ),                    & ! start index z direction
    3807                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    3808                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    3809                           MERGE( nxr-nxlu+1, 0, bc_dirichlet_n ),              & ! number of elements alogn z
    3810                           MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    3811                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    3812                           .TRUE. )                                             
    3813                                                                                
    3814        CALL get_variable( id_dynamic, 'ls_forcing_north_v',                    & ! array to be read
    3815                           nest_offl%v_north,                                   & ! start index x direction
    3816                           MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
    3817                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    3818                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    3819                           MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
    3820                           MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    3821                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    3822                           .TRUE. )                                             
    3823                                                                                
    3824        CALL get_variable( id_dynamic, 'ls_forcing_north_w',                    & ! array to be read
    3825                           nest_offl%w_north,                                   & ! start index x direction
    3826                           MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
    3827                           MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
    3828                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
    3829                           MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
    3830                           MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    3831                           MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    3832                           .TRUE. )                                             
    3833                                                                                
    3834        IF ( .NOT. neutral )  THEN                                             
    3835           CALL get_variable( id_dynamic, 'ls_forcing_north_pt',                & ! array to be read
    3836                              nest_offl%pt_north,                               & ! start index x direction
    3837                              MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
    3838                              MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
    3839                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
    3840                              MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
    3841                              MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    3842                              MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
    3843                              .TRUE. )                                             
    3844        ENDIF                                                                   
    3845        IF ( humidity )  THEN                                                   
    3846           CALL get_variable( id_dynamic, 'ls_forcing_north_qv',                & ! array to be read
    3847                              nest_offl%q_north,                                & ! start index x direction
    3848                              MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
    3849                              MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
    3850                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
    3851                              MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
    3852                              MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    3853                              MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
    3854                              .TRUE. )                                             
    3855        ENDIF                                                                   
    3856                                                                                
    3857        IF ( air_chemistry )  THEN                                             
    3858           DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)                     
    3859              IF ( check_existence( nest_offl%var_names,                        &
    3860                                    nest_offl%var_names_chem_n(n) ) )  THEN     
    3861                 CALL get_variable( id_dynamic,                                 &
    3862                            TRIM( nest_offl%var_names_chem_n(n) ),              &
    3863                            nest_offl%chem_north(:,:,:,n),                      &
    3864                            MERGE( nxl+1, 1, bc_dirichlet_n ),                  &
    3865                            MERGE( nzb+1, 1, bc_dirichlet_n ),                  &
    3866                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),       &
    3867                            MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),              &
    3868                            MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),          &
    3869                            MERGE( 2, 0, bc_dirichlet_n ),                      &
    3870                            .TRUE. )
    3871                 nest_offl%chem_from_file_n(n) = .TRUE.
    3872              ENDIF
    3873           ENDDO
    3874        ENDIF
    3875 !
    3876 !--    Read data for southern boundary
    3877        CALL get_variable( id_dynamic, 'ls_forcing_south_u',                    & ! array to be read
    3878                           nest_offl%u_south,                                   & ! start index x direction
    3879                           MERGE( nxlu, 1, bc_dirichlet_s ),                    & ! start index z direction
    3880                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    3881                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    3882                           MERGE( nxr-nxlu+1, 0, bc_dirichlet_s ),              & ! number of elements alogn z
    3883                           MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    3884                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    3885                           .TRUE. )                                             
    3886                                                                                
    3887        CALL get_variable( id_dynamic, 'ls_forcing_south_v',                    & ! array to be read
    3888                           nest_offl%v_south,                                   & ! start index x direction
    3889                           MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
    3890                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    3891                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    3892                           MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
    3893                           MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    3894                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    3895                           .TRUE. )                                             
    3896                                                                                
    3897        CALL get_variable( id_dynamic, 'ls_forcing_south_w',                    & ! array to be read
    3898                           nest_offl%w_south,                                   & ! start index x direction
    3899                           MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
    3900                           MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
    3901                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
    3902                           MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
    3903                           MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    3904                           MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    3905                           .TRUE. )                                             
    3906                                                                                
    3907        IF ( .NOT. neutral )  THEN                                             
    3908           CALL get_variable( id_dynamic, 'ls_forcing_south_pt',                & ! array to be read
    3909                              nest_offl%pt_south,                               & ! start index x direction
    3910                              MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
    3911                              MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
    3912                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
    3913                              MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
    3914                              MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    3915                              MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
    3916                              .TRUE. )                                             
    3917        ENDIF                                                                   
    3918        IF ( humidity )  THEN                                                   
    3919           CALL get_variable( id_dynamic, 'ls_forcing_south_qv',                & ! array to be read
    3920                              nest_offl%q_south,                                & ! start index x direction
    3921                              MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
    3922                              MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
    3923                              MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
    3924                              MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
    3925                              MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    3926                              MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
    3927                              .TRUE. )                                             
    3928        ENDIF                                                                   
    3929                                                                                
    3930        IF ( air_chemistry )  THEN                                             
    3931           DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)                     
    3932              IF ( check_existence( nest_offl%var_names,                        &
    3933                                    nest_offl%var_names_chem_s(n) ) )  THEN     
    3934                 CALL get_variable( id_dynamic,                                 &
    3935                            TRIM( nest_offl%var_names_chem_s(n) ),              &
    3936                            nest_offl%chem_south(:,:,:,n),                      &
    3937                            MERGE( nxl+1, 1, bc_dirichlet_s ),                  &
    3938                            MERGE( nzb+1, 1, bc_dirichlet_s ),                  &
    3939                            MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),       &
    3940                            MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),              &
    3941                            MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),          &
    3942                            MERGE( 2, 0, bc_dirichlet_s ),                      &
    3943                            .TRUE. )
    3944                 nest_offl%chem_from_file_s(n) = .TRUE.
    3945              ENDIF
    3946           ENDDO
    3947        ENDIF
    3948 !
    3949 !--    Top boundary
    3950        CALL get_variable( id_dynamic, 'ls_forcing_top_u',                      &
    3951                              nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),            &
    3952                              nxlu, nys+1, nest_offl%tind+1,                    &
    3953                              nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
    3954 
    3955        CALL get_variable( id_dynamic, 'ls_forcing_top_v',                      &
    3956                              nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),            &
    3957                              nxl+1, nysv, nest_offl%tind+1,                    &
    3958                              nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
    3959                              
    3960        CALL get_variable( id_dynamic, 'ls_forcing_top_w',                      &
    3961                              nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
    3962                              nxl+1, nys+1, nest_offl%tind+1,                   &
    3963                              nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    3964                              
    3965        IF ( .NOT. neutral )  THEN
    3966           CALL get_variable( id_dynamic, 'ls_forcing_top_pt',                  &
    3967                                 nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),         &
    3968                                 nxl+1, nys+1, nest_offl%tind+1,                &
    3969                                 nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    3970        ENDIF
    3971        IF ( humidity )  THEN
    3972           CALL get_variable( id_dynamic, 'ls_forcing_top_qv',                  &
    3973                                 nest_offl%q_top(0:1,nys:nyn,nxl:nxr),          &
    3974                                 nxl+1, nys+1, nest_offl%tind+1,                &
    3975                                 nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    3976        ENDIF
    3977        
    3978        IF ( air_chemistry )  THEN
    3979           DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
    3980              IF ( check_existence( nest_offl%var_names,                     &
    3981                                    nest_offl%var_names_chem_t(n) ) )  THEN     
    3982                 CALL get_variable( id_dynamic,                                 &
    3983                               TRIM( nest_offl%var_names_chem_t(n) ),           &
    3984                               nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),       &
    3985                               nxl+1, nys+1, nest_offl%tind+1,                  &
    3986                               nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    3987                 nest_offl%chem_from_file_t(n) = .TRUE.
    3988              ENDIF
    3989           ENDDO
    3990        ENDIF
    3991 
    3992 !
    3993 !--    Close input file
    3994        CALL close_input_file( id_dynamic )
    3995 #endif
    3996 !
    3997 !--    End of CPU measurement
    3998        CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
    3999 
    4000     END SUBROUTINE netcdf_data_input_offline_nesting
    4001 
    4002 
    4003 !------------------------------------------------------------------------------!
    4004 ! Description:
    4005 ! ------------
    4006 !> Checks input file for consistency and minimum requirements.
    4007 !------------------------------------------------------------------------------!
    4008     SUBROUTINE netcdf_data_input_check_dynamic
    4009 
    4010        USE control_parameters,                                                 &
    4011            ONLY:  initializing_actions, message_string, nesting_offline
    4012 
    4013        IMPLICIT NONE
    4014 
    4015 !
    4016 !--    In case of forcing, check whether dynamic input file is present
    4017        IF ( .NOT. input_pids_dynamic  .AND.  nesting_offline  )  THEN
    4018           message_string = 'nesting_offline = .TRUE. requires dynamic '  //    &
    4019                             'input file ' //                                   &
    4020                             TRIM( input_file_dynamic ) // TRIM( coupling_char )
    4021           CALL message( 'netcdf_data_input_mod', 'PA0546', 1, 2, 0, 6, 0 )
    4022        ENDIF
    40233470!
    40243471!--    Dynamic input file must also be present if initialization via inifor is
     
    52694716!> Get dimension array for a given dimension
    52704717!------------------------------------------------------------------------------!
    5271      SUBROUTINE netcdf_data_input_get_dimension_length( id, dim_len,           &
    5272                                                         variable_name )
     4718     SUBROUTINE get_dimension_length( id, dim_len, variable_name )
    52734719       USE pegrid
    52744720
     
    52864732!--    First, inquire dimension ID
    52874733       nc_stat = NF90_INQ_DIMID( id, TRIM( variable_name ), id_dim )
    5288        CALL handle_error( 'netcdf_data_input_get_dimension_length', 526,       &
    5289                           variable_name )
     4734       CALL handle_error( 'get_dimension_length', 526, variable_name )
    52904735!
    52914736!--    Inquire dimension length
    52924737       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, dum, LEN = dim_len )
    5293        CALL handle_error( 'netcdf_data_input_get_dimension_length', 526,       &
    5294                           variable_name )
     4738       CALL handle_error( 'get_dimension_length', 526, variable_name )
    52954739
    52964740#endif
    5297     END SUBROUTINE netcdf_data_input_get_dimension_length
     4741    END SUBROUTINE get_dimension_length
    52984742
    52994743!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.