Changeset 3036


Ignore:
Timestamp:
May 24, 2018 10:18:26 AM (6 years ago)
Author:
gronemeier
Message:

renamed input variables according to UC2 data standard

File:
1 edited

Legend:

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

    r3019 r3036  
    2525! -----------------
    2626! $Id$
     27! Revision of input vars according to UC2 data standard
     28!  - renamed 'orography_2D' to 'zt'
     29!  - renamed 'buildings_2D' to 'buildings_2d'
     30!  - renamed 'buildings_3D' to 'buildings_3d'
     31!  - renamed 'leaf_are_density' to 'lad'
     32!  - renamed 'basal_are_density' to 'bad'
     33!  - renamed 'root_are_density_lad' to 'root_area_dens_r'
     34!  - renamed 'root_are_density_lsm' to 'root_area_dens_s'
     35!  - renamed 'ls_forcing_ug' to 'tend_ug'
     36!  - renamed 'ls_forcing_vg' to 'tend_vg'
     37!
     38! 3019 2018-05-13 07:05:43Z maronga
    2739! Improved reading speed of large NetCDF files
    28 ! 
     40!
    2941! 2963 2018-04-12 14:47:44Z suehring
    3042! - Revise checks for static input variables.
    31 ! - Introduce index for vegetation/wall, pavement/green-wall and water/window 
     43! - Introduce index for vegetation/wall, pavement/green-wall and water/window
    3244!   surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
    33 ! 
     45!
    3446! 2958 2018-04-11 15:38:13Z suehring
    3547! Synchronize longitude and latitude between nested model domains, values are
    3648! taken from the root model.
    37 ! 
     49!
    3850! 2955 2018-04-09 15:14:01Z suehring
    39 ! Extend checks for consistent setting of buildings, its ID and type. 
     51! Extend checks for consistent setting of buildings, its ID and type.
    4052! Add log-points to measure CPU time of NetCDF data input.
    41 ! 
     53!
    4254! 2953 2018-04-09 11:26:02Z suehring
    4355! Bugfix in checks for initialization data
    44 ! 
     56!
    4557! 2947 2018-04-04 18:01:41Z suehring
    4658! Checks for dynamic input revised
    47 ! 
     59!
    4860! 2946 2018-04-04 17:01:23Z suehring
    49 ! Bugfix for revision 2945, perform checks only if dynamic input file is 
     61! Bugfix for revision 2945, perform checks only if dynamic input file is
    5062! available.
    51 ! 
     63!
    5264! 2945 2018-04-04 16:27:14Z suehring
    53 ! - Mimic for topography input slightly revised, in order to enable consistency 
     65! - Mimic for topography input slightly revised, in order to enable consistency
    5466!   checks
    5567! - Add checks for dimensions in dynamic input file and move already existing
    56 !   checks 
    57 ! 
     68!   checks
     69!
    5870! 2938 2018-03-27 15:52:42Z suehring
    59 ! Initial read of geostrophic wind components from dynamic driver. 
    60 ! 
     71! Initial read of geostrophic wind components from dynamic driver.
     72!
    6173! 2773 2018-01-30 14:12:54Z suehring
    6274! Revise checks for surface_fraction.
    63 ! 
     75!
    6476! 2925 2018-03-23 14:54:11Z suehring
    65 ! Check for further inconsistent settings of surface_fractions. 
     77! Check for further inconsistent settings of surface_fractions.
    6678! Some messages slightly rephrased and error numbers renamed.
    67 ! 
     79!
    6880! 2898 2018-03-15 13:03:01Z suehring
    69 ! Check if each building has a type. Further, check if dimensions in static 
    70 ! input file match the model dimensions. 
    71 ! 
     81! Check if each building has a type. Further, check if dimensions in static
     82! input file match the model dimensions.
     83!
    7284! 2897 2018-03-15 11:47:16Z suehring
    7385! Relax restrictions for topography input, terrain and building heights can be
    74 ! input separately and are not mandatory any more. 
    75 ! 
     86! input separately and are not mandatory any more.
     87!
    7688! 2874 2018-03-13 10:55:42Z knoop
    7789! Bugfix: wrong placement of netcdf cpp-macros fixed
    78 ! 
     90!
    7991! 2794 2018-02-07 14:09:43Z knoop
    8092! Check if 3D building input is consistent to numeric grid.
    81 ! 
     93!
    8294! 2773 2018-01-30 14:12:54Z suehring
    8395! - Enable initialization with 3D topography.
    8496! - Move check for correct initialization in nesting mode to check_parameters.
    85 ! 
     97!
    8698! 2772 2018-01-29 13:10:35Z suehring
    8799! Initialization of simulation independent on land-surface model.
    88 ! 
     100!
    89101! 2746 2018-01-15 12:06:04Z suehring
    90102! Read plant-canopy variables independently on land-surface model usage
    91 ! 
     103!
    92104! 2718 2018-01-02 08:49:38Z maronga
    93105! Corrected "Former revisions" section
    94 ! 
     106!
    95107! 2711 2017-12-20 17:04:49Z suehring
    96 ! Rename subroutine close_file to avoid double-naming. 
    97 ! 
     108! Rename subroutine close_file to avoid double-naming.
     109!
    98110! 2700 2017-12-15 14:12:35Z suehring
    99111!
    100112! 2696 2017-12-14 17:12:51Z kanani
    101113! Initial revision (suehring)
    102 ! 
    103 ! 
     114!
     115!
    104116!
    105117!
     
    107119! --------
    108120! @author Matthias Suehring
    109 ! 
     121!
    110122! Description:
    111123! ------------
    112 !> Modulue contains routines to input data according to Palm input data       
    113 !> standart using dynamic and static input files. 
     124!> Modulue contains routines to input data according to Palm input data
     125!> standart using dynamic and static input files.
    114126!>
    115127!> @todo - Order input alphabetically
     
    120132!------------------------------------------------------------------------------!
    121133 MODULE netcdf_data_input_mod
    122  
     134
    123135    USE control_parameters,                                                    &
    124136        ONLY:  coupling_char, io_blocks, io_group
     
    138150        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win
    139151!
    140 !-- Define type for dimensions. 
     152!-- Define type for dimensions.
    141153    TYPE dims_xy
    142154       INTEGER(iwp) :: nx                             !< dimension length in x
     
    149161!
    150162!-- Define data type for nesting in larger-scale models like COSMO.
    151 !-- Data type comprises u, v, w, pt, and q at lateral and top boundaries. 
     163!-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
    152164    TYPE force_type
    153165
     
    206218    TYPE init_type
    207219
    208        INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture 
     220       INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture
    209221       INTEGER(iwp) ::  lod_pt    !< level of detail - pt
    210222       INTEGER(iwp) ::  lod_q     !< level of detail - q
    211        INTEGER(iwp) ::  lod_tsoil !< level of detail - soil temperature 
     223       INTEGER(iwp) ::  lod_tsoil !< level of detail - soil temperature
    212224       INTEGER(iwp) ::  lod_u     !< level of detail - u-component
    213225       INTEGER(iwp) ::  lod_v     !< level of detail - v-component
     
    221233       INTEGER(iwp) ::  nzw       !< number of vertical levels on w grid in dynamic input file
    222234
    223        LOGICAL ::  from_file_msoil  = .FALSE. !< flag indicating whether soil moisture is already initialized from file 
     235       LOGICAL ::  from_file_msoil  = .FALSE. !< flag indicating whether soil moisture is already initialized from file
    224236       LOGICAL ::  from_file_pt     = .FALSE. !< flag indicating whether pt is already initialized from file
    225        LOGICAL ::  from_file_q      = .FALSE. !< flag indicating whether q is already initialized from file 
    226        LOGICAL ::  from_file_tsoil  = .FALSE. !< flag indicating whether soil temperature is already initialized from file 
    227        LOGICAL ::  from_file_u      = .FALSE. !< flag indicating whether u is already initialized from file 
    228        LOGICAL ::  from_file_ug     = .FALSE. !< flag indicating whether ug is already initialized from file 
    229        LOGICAL ::  from_file_v      = .FALSE. !< flag indicating whether v is already initialized from file 
    230        LOGICAL ::  from_file_vg     = .FALSE. !< flag indicating whether ug is already initialized from file 
     237       LOGICAL ::  from_file_q      = .FALSE. !< flag indicating whether q is already initialized from file
     238       LOGICAL ::  from_file_tsoil  = .FALSE. !< flag indicating whether soil temperature is already initialized from file
     239       LOGICAL ::  from_file_u      = .FALSE. !< flag indicating whether u is already initialized from file
     240       LOGICAL ::  from_file_ug     = .FALSE. !< flag indicating whether ug is already initialized from file
     241       LOGICAL ::  from_file_v      = .FALSE. !< flag indicating whether v is already initialized from file
     242       LOGICAL ::  from_file_vg     = .FALSE. !< flag indicating whether ug is already initialized from file
    231243       LOGICAL ::  from_file_w      = .FALSE. !< flag indicating whether w is already initialized from file
    232244
     
    262274
    263275!
    264 !-- Define data structures for different input data types. 
     276!-- Define data structures for different input data types.
    265277!-- 8-bit Integer 2D
    266278    TYPE int_2d_8bit
    267279       INTEGER(KIND=1) ::  fill = -127                      !< fill value
    268280       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
    269        
    270        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     281
     282       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    271283    END TYPE int_2d_8bit
    272284!
     
    276288       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  var  !< respective variable
    277289
    278        LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used 
     290       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
    279291    END TYPE int_2d_32bit
    280292
     
    282294!-- Define data type to read 2D real variables
    283295    TYPE real_2d
    284        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     296       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    285297
    286298       REAL(wp) ::  fill = -9999.9_wp                !< fill value
     
    291303!-- Define data type to read 2D real variables
    292304    TYPE real_3d
    293        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
    294 
    295        INTEGER(iwp) ::  nz   !< number of grid points along vertical dimension                     
     305       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
     306
     307       INTEGER(iwp) ::  nz   !< number of grid points along vertical dimension
    296308
    297309       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
     
    299311    END TYPE real_3d
    300312!
    301 !-- Define data structure where the dimension and type of the input depends 
    302 !-- on the given level of detail. 
    303 !-- For buildings, the input is either 2D float, or 3d byte. 
     313!-- Define data structure where the dimension and type of the input depends
     314!-- on the given level of detail.
     315!-- For buildings, the input is either 2D float, or 3d byte.
    304316    TYPE build_in
    305        INTEGER(iwp)    ::  lod = 1                               !< level of detail                 
     317       INTEGER(iwp)    ::  lod = 1                               !< level of detail
    306318       INTEGER(KIND=1) ::  fill2 = -127                          !< fill value for lod = 2
    307319       INTEGER(iwp)    ::  nz                                    !< number of vertical layers in file
     
    310322       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z                 !< vertical coordinate for 3D building, used for consistency check
    311323
    312        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     324       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    313325
    314326       REAL(wp)                              ::  fill1 = -9999.9_wp !< fill values for lod = 1
     
    317329
    318330!
    319 !-- For soil_type, the input is either 2D or 3D one-byte integer. 
     331!-- For soil_type, the input is either 2D or 3D one-byte integer.
    320332    TYPE soil_in
    321        INTEGER(iwp)                                   ::  lod = 1      !< level of detail                 
     333       INTEGER(iwp)                                   ::  lod = 1      !< level of detail
    322334       INTEGER(KIND=1)                                ::  fill = -127  !< fill value for lod = 2
    323335       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE   ::  var_2d       !< 2d variable (lod = 1)
    324336       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d       !< 3d variable (lod = 2)
    325337
    326        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     338       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    327339    END TYPE soil_in
    328340
     
    333345       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nfracs         !< dimension array for fraction
    334346
    335        LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used 
     347       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
    336348
    337349       REAL(wp)                                ::  fill = -9999.9_wp !< fill value
     
    339351    END TYPE fracs
    340352!
    341 !-- Data type for parameter lists, Depending on the given level of detail, 
     353!-- Data type for parameter lists, Depending on the given level of detail,
    342354!-- the input is 3D or 4D
    343355    TYPE pars
     
    345357       INTEGER(iwp)                            ::  np              !< total number of parameters
    346358       INTEGER(iwp)                            ::  nz              !< vertical dimension - number of soil layers
    347        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  layers          !< dimension array for soil layers 
     359       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  layers          !< dimension array for soil layers
    348360       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  pars            !< dimension array for parameters
    349361
    350        LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     362       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    351363
    352364       REAL(wp)                                  ::  fill = -9999.9_wp !< fill value
     
    358370    TYPE(dims_xy)    ::  dim_static  !< data structure for x, y-dimension in static input file
    359371
    360     TYPE(force_type) ::  force     !< data structure for data input at lateral and top boundaries (provided by Inifor) 
     372    TYPE(force_type) ::  force     !< data structure for data input at lateral and top boundaries (provided by Inifor)
    361373
    362374    TYPE(init_type) ::  init_3d    !< data structure for the initialization of the 3D flow and soil fields
    363     TYPE(init_type) ::  init_model !< data structure for the initialization of the model 
     375    TYPE(init_type) ::  init_model !< data structure for the initialization of the model
    364376
    365377!
     
    511523! Description:
    512524! ------------
    513 !> Inquires whether NetCDF input files according to Palm-input-data standard 
     525!> Inquires whether NetCDF input files according to Palm-input-data standard
    514526!> exist. Moreover, basic checks are performed.
    515527!------------------------------------------------------------------------------!
     
    531543
    532544!
    533 !--    As long as topography can be input via ASCII format, no distinction 
     545!--    As long as topography can be input via ASCII format, no distinction
    534546!--    between building and terrain can be made. This case, classify all
    535547!--    surfaces as default type. Same in case land-surface and urban-surface
    536548!--    model are not applied.
    537549       IF ( .NOT. input_pids_static )  THEN
    538           topo_no_distinct = .TRUE. 
     550          topo_no_distinct = .TRUE.
    539551       ENDIF
    540552
     
    553565       INTEGER(iwp) ::  ii       !< running index for IO blocks
    554566
    555        IF ( .NOT. input_pids_static )  RETURN 
     567       IF ( .NOT. input_pids_static )  RETURN
    556568
    557569       DO  ii = 0, io_blocks-1
     
    579591       ENDDO
    580592!
    581 !--    In case of nested runs, each model domain might have different longitude 
    582 !--    and latitude, which would result in different Coriolis parameters and 
    583 !--    sun-zenith angles. To avoid this, longitude and latitude in each model 
    584 !--    domain will be set to the values of the root model. Please note, this 
     593!--    In case of nested runs, each model domain might have different longitude
     594!--    and latitude, which would result in different Coriolis parameters and
     595!--    sun-zenith angles. To avoid this, longitude and latitude in each model
     596!--    domain will be set to the values of the root model. Please note, this
    585597!--    synchronization is required already here.
    586598#if defined( __parallel )
     
    647659                                     TRIM( coupling_char ) , id_surf )
    648660!
    649 !--             At first, inquire all variable names. 
     661!--             At first, inquire all variable names.
    650662!--             This will be used to check whether an optional input variable
    651 !--             exist or not. 
     663!--             exist or not.
    652664                CALL inquire_num_variables( id_surf, num_vars )
    653665
     
    657669!
    658670!--             Read leaf area density - resolved vegetation
    659                 IF ( check_existence( var_names, 'leaf_area_density' ) )  THEN
    660                    leaf_area_density_f%from_file = .TRUE. 
     671                IF ( check_existence( var_names, 'lad' ) )  THEN
     672                   leaf_area_density_f%from_file = .TRUE.
    661673                   CALL get_attribute( id_surf, char_fill,                     &
    662674                                       leaf_area_density_f%fill,               &
    663                                        .FALSE., 'leaf_area_density' ) 
     675                                       .FALSE., 'lad' )
    664676!
    665677!--                Inquire number of vertical vegetation layer
    666678                   CALL get_dimension_length( id_surf, leaf_area_density_f%nz, &
    667679                                              'zlad' )
    668 !           
     680!
    669681!--                Allocate variable for leaf-area density
    670682                   ALLOCATE( leaf_area_density_f%var(                          &
     
    672684                                                   nys:nyn,nxl:nxr) )
    673685
    674                    CALL get_variable( id_surf, 'leaf_area_density',      &
     686                   CALL get_variable( id_surf, 'lad',      &
    675687                                      nxl, nxr, nys, nyn,                &
    676688                                      leaf_area_density_f%var(:,nys:nyn, nxl:nxr) )
    677689
    678690                ELSE
    679                    leaf_area_density_f%from_file = .FALSE. 
     691                   leaf_area_density_f%from_file = .FALSE.
    680692                ENDIF
    681693
    682694!
    683695!--             Read basal area density - resolved vegetation
    684                 IF ( check_existence( var_names, 'basal_area_density' ) )  THEN
    685                    basal_area_density_f%from_file = .TRUE. 
     696                IF ( check_existence( var_names, 'bad' ) )  THEN
     697                   basal_area_density_f%from_file = .TRUE.
    686698                   CALL get_attribute( id_surf, char_fill,                     &
    687699                                       basal_area_density_f%fill,              &
    688                                        .FALSE., 'basal_area_density' ) 
     700                                       .FALSE., 'bad' )
    689701!
    690702!--                Inquire number of vertical vegetation layer
     
    692704                                              basal_area_density_f%nz,         &
    693705                                              'zlad' )
    694 !           
     706!
    695707!--                Allocate variable
    696708                   ALLOCATE( basal_area_density_f%var(                         &
     
    698710                                                  nys:nyn,nxl:nxr) )
    699711
    700                    CALL get_variable( id_surf, 'basal_area_density',     &
     712                   CALL get_variable( id_surf, 'bad',                    &
    701713                                      nxl, nxr, nys, nyn,                &
    702714                                      basal_area_density_f%var(:,nys:nyn, nxl:nxr) )
    703715                ELSE
    704                    basal_area_density_f%from_file = .FALSE. 
     716                   basal_area_density_f%from_file = .FALSE.
    705717                ENDIF
    706718
    707719!
    708720!--             Read root area density - resolved vegetation
    709                 IF ( check_existence( var_names, 'root_area_density_lad' ) )  THEN
    710                    root_area_density_lad_f%from_file = .TRUE. 
     721                IF ( check_existence( var_names, 'root_area_dens_r' ) )  THEN
     722                   root_area_density_lad_f%from_file = .TRUE.
    711723                   CALL get_attribute( id_surf, char_fill,                     &
    712724                                       root_area_density_lad_f%fill,           &
    713                                        .FALSE., 'root_area_density_lad' ) 
     725                                       .FALSE., 'root_area_dens_r' )
    714726!
    715727!--                Inquire number of vertical soil layers
     
    717729                                              root_area_density_lad_f%nz,      &
    718730                                              'zsoil' )
    719 !           
     731!
    720732!--                Allocate variable
    721733                   ALLOCATE( root_area_density_lad_f%var                       &
     
    723735                                                nys:nyn,nxl:nxr) )
    724736
    725                    CALL get_variable( id_surf, 'root_area_density_lad',  &
    726                                       nxl, nxr, nys, nyn,                              &
     737                   CALL get_variable( id_surf, 'root_area_dens_r',  &
     738                                      nxl, nxr, nys, nyn,           &
    727739                                      root_area_density_lad_f%var(:,nys:nyn, nxl:nxr) )
    728740                ELSE
    729                    root_area_density_lad_f%from_file = .FALSE. 
     741                   root_area_density_lad_f%from_file = .FALSE.
    730742                ENDIF
    731743!
     
    739751          ENDDO
    740752!
    741 !--       Deallocate variable list. Will be re-allocated in case further 
    742 !--       variables are read from file.         
     753!--       Deallocate variable list. Will be re-allocated in case further
     754!--       variables are read from file.
    743755          IF ( ALLOCATED( var_names ) )  DEALLOCATE( var_names )
    744756
    745757       ENDIF
    746758!
    747 !--    Skip the following if no land-surface or urban-surface module are 
    748 !--    applied. This case, no one of the following variables is used anyway. 
     759!--    Skip the following if no land-surface or urban-surface module are
     760!--    applied. This case, no one of the following variables is used anyway.
    749761       IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN
    750762!
     
    762774
    763775!
    764 !--          Inquire all variable names. 
    765 !--          This will be used to check whether an optional input variable exist 
    766 !--          or not. 
     776!--          Inquire all variable names.
     777!--          This will be used to check whether an optional input variable exist
     778!--          or not.
    767779             CALL inquire_num_variables( id_surf, num_vars )
    768780
     
    792804!--          Read soil type and required attributes
    793805             IF ( check_existence( var_names, 'soil_type' ) )  THEN
    794                    soil_type_f%from_file = .TRUE. 
     806                   soil_type_f%from_file = .TRUE.
    795807!
    796808!--             Note, lod is currently not on file; skip for the moment
     
    800812                CALL get_attribute( id_surf, char_fill,                        &
    801813                                    soil_type_f%fill,                          &
    802                                     .FALSE., 'soil_type' ) 
     814                                    .FALSE., 'soil_type' )
    803815
    804816                IF ( soil_type_f%lod == 1 )  THEN
     
    808820                   DO  i = nxl, nxr
    809821                      CALL get_variable( id_surf, 'soil_type',                 &
    810                                          i, soil_type_f%var_2d(:,i) ) 
     822                                         i, soil_type_f%var_2d(:,i) )
    811823                   ENDDO
    812824                ELSEIF ( soil_type_f%lod == 2 )  THEN
     
    820832                      DO  j = nys, nyn
    821833                         CALL get_variable( id_surf, 'soil_type', i, j,        &
    822                                             soil_type_f%var_3d(:,j,i) )   
     834                                            soil_type_f%var_3d(:,j,i) )
    823835                      ENDDO
    824                    ENDDO 
     836                   ENDDO
    825837                ENDIF
    826838             ELSE
     
    831843!--          Read pavement type and required attributes
    832844             IF ( check_existence( var_names, 'pavement_type' ) )  THEN
    833                 pavement_type_f%from_file = .TRUE. 
     845                pavement_type_f%from_file = .TRUE.
    834846                CALL get_attribute( id_surf, char_fill,                        &
    835847                                    pavement_type_f%fill, .FALSE.,             &
    836                                     'pavement_type' ) 
     848                                    'pavement_type' )
    837849!
    838850!--             PE-wise reading of 2D pavement type.
     
    840852                DO  i = nxl, nxr
    841853                   CALL get_variable( id_surf, 'pavement_type',                &
    842                                       i, pavement_type_f%var(:,i) ) 
     854                                      i, pavement_type_f%var(:,i) )
    843855                ENDDO
    844856             ELSE
     
    849861!--          Read water type and required attributes
    850862             IF ( check_existence( var_names, 'water_type' ) )  THEN
    851                 water_type_f%from_file = .TRUE. 
     863                water_type_f%from_file = .TRUE.
    852864                CALL get_attribute( id_surf, char_fill, water_type_f%fill,     &
    853865                                    .FALSE., 'water_type' )
     
    857869                DO  i = nxl, nxr
    858870                   CALL get_variable( id_surf, 'water_type', i,                &
    859                                       water_type_f%var(:,i) ) 
     871                                      water_type_f%var(:,i) )
    860872                ENDDO
    861873             ELSE
     
    865877!--          Read surface fractions and related information
    866878             IF ( check_existence( var_names, 'surface_fraction' ) )  THEN
    867                 surface_fraction_f%from_file = .TRUE. 
     879                surface_fraction_f%from_file = .TRUE.
    868880                CALL get_attribute( id_surf, char_fill,                        &
    869881                                    surface_fraction_f%fill,                   &
     
    874886                                           surface_fraction_f%nf,              &
    875887                                           'nsurface_fraction' )
    876 !           
     888!
    877889!--             Allocate dimension array and input array for surface fractions
    878890                ALLOCATE( surface_fraction_f%nfracs(0:surface_fraction_f%nf-1) )
     
    889901                                   surface_fraction_f%frac(:,nys:nyn, nxl:nxr))
    890902             ELSE
    891                 surface_fraction_f%from_file = .FALSE. 
     903                surface_fraction_f%from_file = .FALSE.
    892904             ENDIF
    893905!
    894906!--          Read building parameters and related information
    895907             IF ( check_existence( var_names, 'building_pars' ) )  THEN
    896                 building_pars_f%from_file = .TRUE. 
     908                building_pars_f%from_file = .TRUE.
    897909                CALL get_attribute( id_surf, char_fill,                        &
    898910                                    building_pars_f%fill,                      &
    899                                     .FALSE., 'building_pars' ) 
     911                                    .FALSE., 'building_pars' )
    900912!
    901913!--             Inquire number of building parameters
     
    903915                                           building_pars_f%np,                 &
    904916                                           'nbuilding_pars' )
    905 !           
     917!
    906918!--             Allocate dimension array and input array for building parameters
    907919                ALLOCATE( building_pars_f%pars(0:building_pars_f%np-1) )
     
    918930                                   building_pars_f%pars_xy(:,nys:nyn, nxl:nxr) )
    919931             ELSE
    920                 building_pars_f%from_file = .FALSE. 
     932                building_pars_f%from_file = .FALSE.
    921933             ENDIF
    922934
     
    924936!--          Read albedo type and required attributes
    925937             IF ( check_existence( var_names, 'albedo_type' ) )  THEN
    926                 albedo_type_f%from_file = .TRUE. 
     938                albedo_type_f%from_file = .TRUE.
    927939                CALL get_attribute( id_surf, char_fill, albedo_type_f%fill,    &
    928                                     .FALSE.,  'albedo_type' ) 
     940                                    .FALSE.,  'albedo_type' )
    929941!
    930942!--             PE-wise reading of 2D water type.
     
    932944                DO  i = nxl, nxr
    933945                   CALL get_variable( id_surf, 'albedo_type',                  &
    934                                       i, albedo_type_f%var(:,i) ) 
     946                                      i, albedo_type_f%var(:,i) )
    935947                ENDDO
    936948             ELSE
     
    940952!--          Read albedo parameters and related information
    941953             IF ( check_existence( var_names, 'albedo_pars' ) )  THEN
    942                 albedo_pars_f%from_file = .TRUE. 
     954                albedo_pars_f%from_file = .TRUE.
    943955                CALL get_attribute( id_surf, char_fill, albedo_pars_f%fill,    &
    944                                     .FALSE., 'albedo_pars' ) 
     956                                    .FALSE., 'albedo_pars' )
    945957!
    946958!--             Inquire number of albedo parameters
    947959                CALL get_dimension_length( id_surf, albedo_pars_f%np,          &
    948960                                           'nalbedo_pars' )
    949 !           
     961!
    950962!--             Allocate dimension array and input array for albedo parameters
    951963                ALLOCATE( albedo_pars_f%pars(0:albedo_pars_f%np-1) )
     
    959971                   DO  j = nys, nyn
    960972                      CALL get_variable( id_surf, 'albedo_pars', i, j,         &
    961                                          albedo_pars_f%pars_xy(:,j,i) )   
     973                                         albedo_pars_f%pars_xy(:,j,i) )
    962974                   ENDDO
    963975                ENDDO
    964976             ELSE
    965                 albedo_pars_f%from_file = .FALSE. 
     977                albedo_pars_f%from_file = .FALSE.
    966978             ENDIF
    967979
     
    969981!--          Read pavement parameters and related information
    970982             IF ( check_existence( var_names, 'pavement_pars' ) )  THEN
    971                 pavement_pars_f%from_file = .TRUE. 
     983                pavement_pars_f%from_file = .TRUE.
    972984                CALL get_attribute( id_surf, char_fill,                        &
    973985                                    pavement_pars_f%fill,                      &
    974                                     .FALSE., 'pavement_pars' ) 
     986                                    .FALSE., 'pavement_pars' )
    975987!
    976988!--             Inquire number of pavement parameters
    977989                CALL get_dimension_length( id_surf, pavement_pars_f%np,        &
    978990                                           'npavement_pars' )
    979 !           
     991!
    980992!--             Allocate dimension array and input array for pavement parameters
    981993                ALLOCATE( pavement_pars_f%pars(0:pavement_pars_f%np-1) )
     
    986998                CALL get_variable( id_surf, 'npavement_pars',                  &
    987999                                   pavement_pars_f%pars )
    988    
     1000
    9891001                DO  i = nxl, nxr
    9901002                   DO  j = nys, nyn
    9911003                      CALL get_variable( id_surf, 'pavement_pars', i, j,       &
    992                                          pavement_pars_f%pars_xy(:,j,i) )   
     1004                                         pavement_pars_f%pars_xy(:,j,i) )
    9931005                   ENDDO
    9941006                ENDDO
    9951007             ELSE
    996                 pavement_pars_f%from_file = .FALSE. 
     1008                pavement_pars_f%from_file = .FALSE.
    9971009             ENDIF
    9981010
     
    10011013             IF ( check_existence( var_names, 'pavement_subsurface_pars' ) )   &
    10021014             THEN
    1003                 pavement_subsurface_pars_f%from_file = .TRUE. 
     1015                pavement_subsurface_pars_f%from_file = .TRUE.
    10041016                CALL get_attribute( id_surf, char_fill,                        &
    10051017                                    pavement_subsurface_pars_f%fill,           &
    1006                                     .FALSE., 'pavement_subsurface_pars' ) 
     1018                                    .FALSE., 'pavement_subsurface_pars' )
    10071019!
    10081020!--             Inquire number of parameters
     
    10111023                                           'npavement_subsurface_pars' )
    10121024!
    1013 !--             Inquire number of soil layers 
     1025!--             Inquire number of soil layers
    10141026                CALL get_dimension_length( id_surf,                            &
    10151027                                           pavement_subsurface_pars_f%nz,      &
    10161028                                           'zsoil' )
    1017 !           
     1029!
    10181030!--             Allocate dimension array and input array for pavement parameters
    10191031                ALLOCATE( pavement_subsurface_pars_f%pars                      &
     
    10271039                CALL get_variable( id_surf, 'npavement_subsurface_pars',       &
    10281040                                   pavement_subsurface_pars_f%pars )
    1029    
     1041
    10301042                DO  i = nxl, nxr
    10311043                   DO  j = nys, nyn
     
    10351047                                  pavement_subsurface_pars_f%pars_xyz(:,:,j,i),&
    10361048                                  pavement_subsurface_pars_f%nz,               &
    1037                                   pavement_subsurface_pars_f%np )   
     1049                                  pavement_subsurface_pars_f%np )
    10381050                   ENDDO
    10391051                ENDDO
    10401052             ELSE
    1041                 pavement_subsurface_pars_f%from_file = .FALSE. 
     1053                pavement_subsurface_pars_f%from_file = .FALSE.
    10421054             ENDIF
    10431055
     
    10461058!--          Read vegetation parameters and related information
    10471059             IF ( check_existence( var_names, 'vegetation_pars' ) )  THEN
    1048                 vegetation_pars_f%from_file = .TRUE. 
     1060                vegetation_pars_f%from_file = .TRUE.
    10491061                CALL get_attribute( id_surf, char_fill,                        &
    10501062                                    vegetation_pars_f%fill,                    &
     
    10541066                CALL get_dimension_length( id_surf, vegetation_pars_f%np,      &
    10551067                                           'nvegetation_pars' )
    1056 !           
     1068!
    10571069!--             Allocate dimension array and input array for surface fractions
    10581070                ALLOCATE( vegetation_pars_f%pars(0:vegetation_pars_f%np-1) )
     
    10681080                                   vegetation_pars_f%pars_xy(:,nys:nyn,nxl:nxr ) )
    10691081             ELSE
    1070                 vegetation_pars_f%from_file = .FALSE. 
     1082                vegetation_pars_f%from_file = .FALSE.
    10711083             ENDIF
    10721084
     
    10741086!--          Read root parameters/distribution and related information
    10751087             IF ( check_existence( var_names, 'soil_pars' ) )  THEN
    1076                 soil_pars_f%from_file = .TRUE. 
     1088                soil_pars_f%from_file = .TRUE.
    10771089                CALL get_attribute( id_surf, char_fill,                        &
    1078                                     soil_pars_f%fill,                          & 
    1079                                     .FALSE., 'soil_pars' ) 
     1090                                    soil_pars_f%fill,                          &
     1091                                    .FALSE., 'soil_pars' )
    10801092
    10811093                CALL get_attribute( id_surf, char_lod,                         &
    10821094                                    soil_pars_f%lod,                           &
    1083                                     .FALSE., 'soil_pars' ) 
     1095                                    .FALSE., 'soil_pars' )
    10841096
    10851097!
     
    11061118!
    11071119!--             Read soil parameters, depending on level of detail
    1108                 IF ( soil_pars_f%lod == 1 )  THEN     
     1120                IF ( soil_pars_f%lod == 1 )  THEN
    11091121                   ALLOCATE( soil_pars_f%pars_xy(0:soil_pars_f%np-1,           &
    1110                                                  nys:nyn,nxl:nxr) )       
     1122                                                 nys:nyn,nxl:nxr) )
    11111123                   DO  i = nxl, nxr
    11121124                      DO  j = nys, nyn
    11131125                         CALL get_variable( id_surf, 'soil_pars', i, j,        &
    1114                                             soil_pars_f%pars_xy(:,j,i) ) 
     1126                                            soil_pars_f%pars_xy(:,j,i) )
    11151127                      ENDDO
    11161128                   ENDDO
     
    11241136                         CALL get_variable( id_surf, 'soil_pars', i, j,        &
    11251137                                            soil_pars_f%pars_xyz(:,:,j,i),     &
    1126                                             soil_pars_f%nz, soil_pars_f%np ) 
     1138                                            soil_pars_f%nz, soil_pars_f%np )
    11271139                      ENDDO
    11281140                   ENDDO
    11291141                ENDIF
    11301142             ELSE
    1131                 soil_pars_f%from_file = .FALSE. 
     1143                soil_pars_f%from_file = .FALSE.
    11321144             ENDIF
    11331145
     
    11351147!--          Read water parameters and related information
    11361148             IF ( check_existence( var_names, 'water_pars' ) )  THEN
    1137                 water_pars_f%from_file = .TRUE. 
     1149                water_pars_f%from_file = .TRUE.
    11381150                CALL get_attribute( id_surf, char_fill,                        &
    11391151                                    water_pars_f%fill,                         &
    1140                                     .FALSE., 'water_pars' ) 
     1152                                    .FALSE., 'water_pars' )
    11411153!
    11421154!--             Inquire number of water parameters
    1143                 CALL get_dimension_length( id_surf,                            & 
     1155                CALL get_dimension_length( id_surf,                            &
    11441156                                           water_pars_f%np,                    &
    11451157                                           'nwater_pars' )
    1146 !           
     1158!
    11471159!--             Allocate dimension array and input array for water parameters
    11481160                ALLOCATE( water_pars_f%pars(0:water_pars_f%np-1) )
     
    11561168                   DO  j = nys, nyn
    11571169                      CALL get_variable( id_surf, 'water_pars', i, j,          &
    1158                                          water_pars_f%pars_xy(:,j,i) )   
     1170                                         water_pars_f%pars_xy(:,j,i) )
    11591171                   ENDDO
    11601172                ENDDO
    11611173             ELSE
    1162                 water_pars_f%from_file = .FALSE. 
     1174                water_pars_f%from_file = .FALSE.
    11631175             ENDIF
    11641176!
    11651177!--          Read root area density - parametrized vegetation
    1166              IF ( check_existence( var_names, 'root_area_density_lsm' ) )  THEN
     1178             IF ( check_existence( var_names, 'root_area_dens_s' ) )  THEN
    11671179                root_area_density_lsm_f%from_file = .TRUE.
    11681180                CALL get_attribute( id_surf, char_fill,                        &
    11691181                                    root_area_density_lsm_f%fill,              &
    1170                                     .FALSE., 'root_area_density_lsm' )
     1182                                    .FALSE., 'root_area_dens_s' )
    11711183!
    11721184!--             Obtain number of soil layers from file and allocate variable
     
    11811193                DO  i = nxl, nxr
    11821194                   DO  j = nys, nyn
    1183                       CALL get_variable( id_surf, 'root_area_density_lsm',     &
     1195                      CALL get_variable( id_surf, 'root_area_dens_s',          &
    11841196                                         i, j,                                 &
    1185                                          root_area_density_lsm_f%var(:,j,i) )   
     1197                                         root_area_density_lsm_f%var(:,j,i) )
    11861198                   ENDDO
    11871199                ENDDO
     
    11931205!--          Read street type and street crossing
    11941206             IF ( check_existence( var_names, 'street_type' ) )  THEN
    1195                 street_type_f%from_file = .TRUE. 
     1207                street_type_f%from_file = .TRUE.
    11961208                CALL get_attribute( id_surf, char_fill,                        &
    11971209                                    street_type_f%fill, .FALSE.,               &
    1198                                     'street_type' ) 
     1210                                    'street_type' )
    11991211!
    12001212!--             PE-wise reading of 2D pavement type.
     
    12021214                DO  i = nxl, nxr
    12031215                   CALL get_variable( id_surf, 'street_type',                  &
    1204                                       i, street_type_f%var(:,i) ) 
     1216                                      i, street_type_f%var(:,i) )
    12051217                ENDDO
    12061218             ELSE
     
    12091221
    12101222             IF ( check_existence( var_names, 'street_crossing' ) )  THEN
    1211                 street_crossing_f%from_file = .TRUE. 
     1223                street_crossing_f%from_file = .TRUE.
    12121224                CALL get_attribute( id_surf, char_fill,                        &
    12131225                                    street_crossing_f%fill, .FALSE.,           &
    1214                                     'street_crossing' ) 
     1226                                    'street_crossing' )
    12151227!
    12161228!--             PE-wise reading of 2D pavement type.
     
    12181230                DO  i = nxl, nxr
    12191231                   CALL get_variable( id_surf, 'street_crossing',              &
    1220                                       i, street_crossing_f%var(:,i) ) 
     1232                                      i, street_crossing_f%var(:,i) )
    12211233                ENDDO
    12221234             ELSE
     
    12441256!--    MPI datatypes or rewriting exchange_horiz.
    12451257!--    Moreover, varialbes will be resized in the following, including ghost
    1246 !--    points. 
    1247 !--    Start with 2D Integer variables. Please note, for 8-bit integer 
     1258!--    points.
     1259!--    Start with 2D Integer variables. Please note, for 8-bit integer
    12481260!--    variables must be swapt to 32-bit integer before calling exchange_horiz.
    12491261       IF ( albedo_type_f%from_file )  THEN
     
    12941306!
    12951307!--    Exchange 1 ghost point for 3/4-D variables. For the sake of simplicity,
    1296 !--    loop further dimensions to use 2D exchange routines. 
     1308!--    loop further dimensions to use 2D exchange routines.
    12971309!--    This should be revised later by introducing new MPI datatypes.
    12981310       IF ( soil_type_f%from_file  .AND.  ALLOCATED( soil_type_f%var_3d ) )    &
    12991311       THEN
    1300           ALLOCATE( var_dum_int_3d(0:nz_soil,nys:nyn,nxl:nxr) ) 
     1312          ALLOCATE( var_dum_int_3d(0:nz_soil,nys:nyn,nxl:nxr) )
    13011313          var_dum_int_3d = soil_type_f%var_3d
    13021314          DEALLOCATE( soil_type_f%var_3d )
     
    14631475             ENDDO
    14641476             DEALLOCATE( var_dum_real_4d )
    1465           ENDIF 
     1477          ENDIF
    14661478       ENDIF
    14671479
     
    16951707       USE indices,                                                            &
    16961708           ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb, nzt
    1697                  
     1709
    16981710
    16991711       IMPLICIT NONE
     
    17121724       INTEGER(iwp), DIMENSION(nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp) ::  var_exchange_int !< dummy variables used to exchange 32-bit Integer arrays
    17131725
    1714        REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file   
     1726       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
    17151727!
    17161728!--    CPU measurement
     
    17201732          IF ( ii == io_group )  THEN
    17211733!
    1722 !--          Input via palm-input data standard 
     1734!--          Input via palm-input data standard
    17231735             IF ( input_pids_static )  THEN
    17241736#if defined ( __netcdf )
     
    17261738!--             Open file in read-only mode
    17271739                CALL open_read_file( TRIM( input_file_static ) //              &
    1728                                      TRIM( coupling_char ), id_topo ) 
    1729 
    1730 !
    1731 !--             At first, inquire all variable names. 
    1732 !--             This will be used to check whether an  input variable exist 
    1733 !--             or not. 
     1740                                     TRIM( coupling_char ), id_topo )
     1741
     1742!
     1743!--             At first, inquire all variable names.
     1744!--             This will be used to check whether an  input variable exist
     1745!--             or not.
    17341746                CALL inquire_num_variables( id_topo, num_vars )
    17351747!
     
    17471759!
    17481760!--             Terrain height. First, get variable-related _FillValue attribute
    1749                 IF ( check_existence( var_names, 'orography_2D' ) )  THEN
    1750                    terrain_height_f%from_file = .TRUE. 
     1761                IF ( check_existence( var_names, 'zt' ) )  THEN
     1762                   terrain_height_f%from_file = .TRUE.
    17511763                   CALL get_attribute( id_topo, char_fill,                     &
    17521764                                       terrain_height_f%fill,                  &
    1753                                        .FALSE., 'orography_2D' )
     1765                                       .FALSE., 'zt' )
    17541766!
    17551767!--                PE-wise reading of 2D terrain height.
    17561768                   ALLOCATE ( terrain_height_f%var(nys:nyn,nxl:nxr)  )
    17571769                   DO  i = nxl, nxr
    1758                       CALL get_variable( id_topo, 'orography_2D',              &
    1759                                          i, terrain_height_f%var(:,i) ) 
     1770                      CALL get_variable( id_topo, 'zt',                        &
     1771                                         i, terrain_height_f%var(:,i) )
    17601772                   ENDDO
    17611773                ELSE
    1762                    terrain_height_f%from_file = .FALSE. 
    1763                 ENDIF
    1764 
    1765 !
    1766 !--             Read building height. First, read its _FillValue attribute, 
     1774                   terrain_height_f%from_file = .FALSE.
     1775                ENDIF
     1776
     1777!
     1778!--             Read building height. First, read its _FillValue attribute,
    17671779!--             as well as lod attribute
    1768                 buildings_f%from_file = .FALSE. 
    1769                 IF ( check_existence( var_names, 'buildings_2D' ) )  THEN
    1770                    buildings_f%from_file = .TRUE. 
     1780                buildings_f%from_file = .FALSE.
     1781                IF ( check_existence( var_names, 'buildings_2d' ) )  THEN
     1782                   buildings_f%from_file = .TRUE.
    17711783                   CALL get_attribute( id_topo, char_lod, buildings_f%lod,     &
    1772                                        .FALSE., 'buildings_2D' )     
     1784                                       .FALSE., 'buildings_2d' )
    17731785
    17741786                   CALL get_attribute( id_topo, char_fill,                     &
    17751787                                       buildings_f%fill1,                      &
    1776                                        .FALSE., 'buildings_2D' )
     1788                                       .FALSE., 'buildings_2d' )
    17771789
    17781790!
     
    17811793                      ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
    17821794                      DO  i = nxl, nxr
    1783                          CALL get_variable( id_topo, 'buildings_2D',           &
    1784                                             i, buildings_f%var_2d(:,i) ) 
     1795                         CALL get_variable( id_topo, 'buildings_2d',           &
     1796                                            i, buildings_f%var_2d(:,i) )
    17851797                      ENDDO
    1786                    ELSE 
     1798                   ELSE
    17871799                      message_string = 'NetCDF attribute lod ' //              &
    17881800                                       '(level of detail) is not set ' //      &
    1789                                        'properly for buildings_2D.'
     1801                                       'properly for buildings_2d.'
    17901802                      CALL message( 'netcdf_data_input_mod', 'NDI000',         &
    17911803                                     1, 2, 0, 6, 0 )
     
    17951807!--             If available, also read 3D building information. If both are
    17961808!--             available, use 3D information.
    1797                 IF ( check_existence( var_names, 'buildings_3D' ) )  THEN
    1798                    buildings_f%from_file = .TRUE. 
     1809                IF ( check_existence( var_names, 'buildings_3d' ) )  THEN
     1810                   buildings_f%from_file = .TRUE.
    17991811                   CALL get_attribute( id_topo, char_lod, buildings_f%lod,     &
    1800                                        .FALSE., 'buildings_3D' )     
     1812                                       .FALSE., 'buildings_3d' )
    18011813
    18021814                   CALL get_attribute( id_topo, char_fill,                     &
    18031815                                       buildings_f%fill2,                      &
    1804                                        .FALSE., 'buildings_3D' )
     1816                                       .FALSE., 'buildings_3d' )
    18051817
    18061818                   CALL get_dimension_length( id_topo, buildings_f%nz, 'z' )
    1807  
     1819
    18081820                   IF ( buildings_f%lod == 2 )  THEN
    18091821                      ALLOCATE( buildings_f%z(nzb:buildings_f%nz-1) )
     
    18171829                      DO  i = nxl, nxr
    18181830                         DO  j = nys, nyn
    1819                             CALL get_variable( id_topo, 'buildings_3D',        &
     1831                            CALL get_variable( id_topo, 'buildings_3d',        &
    18201832                                               i, j,                           &
    18211833                                               buildings_f%var_3d(:,j,i) )
    18221834                         ENDDO
    18231835                      ENDDO
    1824                    ELSE 
     1836                   ELSE
    18251837                      message_string = 'NetCDF attribute lod ' //              &
    18261838                                       '(level of detail) is not set ' //      &
    1827                                        'properly for buildings_3D.'
     1839                                       'properly for buildings_3d.'
    18281840                      CALL message( 'netcdf_data_input_mod', 'NDI001',         &
    18291841                                     1, 2, 0, 6, 0 )
     
    18311843                ENDIF
    18321844!
    1833 !--             Read building IDs and its FillValue attribute. Further required 
     1845!--             Read building IDs and its FillValue attribute. Further required
    18341846!--             for mapping buildings on top of orography.
    18351847                IF ( check_existence( var_names, 'building_id' ) )  THEN
    1836                    building_id_f%from_file = .TRUE. 
     1848                   building_id_f%from_file = .TRUE.
    18371849                   CALL get_attribute( id_topo, char_fill,                     &
    18381850                                       building_id_f%fill, .FALSE.,            &
    18391851                                       'building_id' )
    1840              
     1852
    18411853
    18421854                   ALLOCATE ( building_id_f%var(nys:nyn,nxl:nxr) )
    18431855                   DO  i = nxl, nxr
    18441856                      CALL get_variable( id_topo, 'building_id',               &
    1845                                           i, building_id_f%var(:,i) ) 
     1857                                          i, building_id_f%var(:,i) )
    18461858                   ENDDO
    18471859                ELSE
    1848                    building_id_f%from_file = .FALSE. 
    1849                 ENDIF
    1850 !
    1851 !--             Read building_type and required attributes. 
     1860                   building_id_f%from_file = .FALSE.
     1861                ENDIF
     1862!
     1863!--             Read building_type and required attributes.
    18521864                IF ( check_existence( var_names, 'building_type' ) )  THEN
    1853                    building_type_f%from_file = .TRUE. 
     1865                   building_type_f%from_file = .TRUE.
    18541866                   CALL get_attribute( id_topo, char_fill,                     &
    18551867                                       building_type_f%fill, .FALSE.,          &
    1856                                        'building_type' ) 
    1857                
     1868                                       'building_type' )
     1869
    18581870                   ALLOCATE ( building_type_f%var(nys:nyn,nxl:nxr) )
    18591871                   DO  i = nxl, nxr
     
    18821894                skip_n_rows = 0
    18831895                DO WHILE ( skip_n_rows < ny - nyn )
    1884                    READ( 90, * ) 
     1896                   READ( 90, * )
    18851897                   skip_n_rows = skip_n_rows + 1
    18861898                ENDDO
    18871899!
    1888 !--             Read data from nyn to nys and nxl to nxr. Therefore, skip 
     1900!--             Read data from nyn to nys and nxl to nxr. Therefore, skip
    18891901!--             column until nxl-1 is reached
    18901902                ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
     
    18961908
    18971909                GOTO 12
    1898          
     1910
    18991911 10             message_string = 'file TOPOGRAPHY'//TRIM( coupling_char )//    &
    19001912                                 ' does not exist'
     
    19081920                buildings_f%from_file = .TRUE.
    19091921
    1910              ENDIF 
     1922             ENDIF
    19111923
    19121924          ENDIF
     
    19201932!
    19211933!--    Check for minimum requirement to setup building topography. If buildings
    1922 !--    are provided, also an ID and a type are required. 
    1923 !--    Note, doing this check in check_parameters 
     1934!--    are provided, also an ID and a type are required.
     1935!--    Note, doing this check in check_parameters
    19241936!--    will be too late (data will be used for grid inititialization before).
    19251937       IF ( input_pids_static )  THEN
    19261938          IF ( buildings_f%from_file  .AND.                                    &
    1927                .NOT. building_id_f%from_file )  THEN                       
     1939               .NOT. building_id_f%from_file )  THEN
    19281940             message_string = 'If building heigths are prescribed in ' //      &
    19291941                              'static input file, also an ID is required.'
     
    19321944       ENDIF
    19331945!
    1934 !--    In case no terrain height is provided by static input file, allocate 
    1935 !--    array nevertheless and set terrain height to 0, which simplifies 
     1946!--    In case no terrain height is provided by static input file, allocate
     1947!--    array nevertheless and set terrain height to 0, which simplifies
    19361948!--    topography initialization.
    19371949       IF ( .NOT. terrain_height_f%from_file )  THEN
     
    19401952       ENDIF
    19411953!
    1942 !--    Finally, exchange 1 ghost point for building ID and type. 
     1954!--    Finally, exchange 1 ghost point for building ID and type.
    19431955!--    In case of non-cyclic boundary conditions set Neumann conditions at the
    19441956!--    lateral boundaries.
     
    19561968          ENDIF
    19571969          IF ( .NOT. bc_lr_cyc )  THEN
    1958              IF ( nxl == 0  )  building_id_f%var(:,-1)   = building_id_f%var(:,0) 
    1959              IF ( nxr == nx )  building_id_f%var(:,nx+1) = building_id_f%var(:,nx)       
     1970             IF ( nxl == 0  )  building_id_f%var(:,-1)   = building_id_f%var(:,0)
     1971             IF ( nxr == nx )  building_id_f%var(:,nx+1) = building_id_f%var(:,nx)
    19601972          ENDIF
    19611973       ENDIF
     
    19751987          ENDIF
    19761988          IF ( .NOT. bc_lr_cyc )  THEN
    1977              IF ( nxl == 0  )  building_type_f%var(:,-1)   = building_type_f%var(:,0) 
    1978              IF ( nxr == nx )  building_type_f%var(:,nx+1) = building_type_f%var(:,nx)       
     1989             IF ( nxl == 0  )  building_type_f%var(:,-1)   = building_type_f%var(:,0)
     1990             IF ( nxr == nx )  building_type_f%var(:,nx+1) = building_type_f%var(:,nx)
    19791991          ENDIF
    19801992       ENDIF
     
    19861998! ------------
    19871999!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
    1988 !> as well as soil moisture and soil temperature, derived from larger-scale 
     2000!> as well as soil moisture and soil temperature, derived from larger-scale
    19892001!> model (COSMO) by Inifor.
    19902002!------------------------------------------------------------------------------!
     
    20142026       INTEGER(iwp) ::  off_j      !< offset in y-direction used for reading the v-component
    20152027
    2016        LOGICAL      ::  check_passed !< flag indicating if a check passed 
     2028       LOGICAL      ::  check_passed !< flag indicating if a check passed
    20172029
    20182030!
     
    20212033!
    20222034!--    Please note, Inifor is designed to provide initial data for u and v for
    2023 !--    the prognostic grid points in case of lateral Dirichlet conditions. 
    2024 !--    This means that Inifor provides data from nxlu:nxr (for u) and 
     2035!--    the prognostic grid points in case of lateral Dirichlet conditions.
     2036!--    This means that Inifor provides data from nxlu:nxr (for u) and
    20252037!--    from nysv:nyn (for v) at the left and south domain boundary, respectively.
    2026 !--    However, as work-around for the moment, PALM will run with cyclic 
    2027 !--    conditions and will be initialized with data provided by Inifor 
    2028 !--    boundaries in case of Dirichlet. 
     2038!--    However, as work-around for the moment, PALM will run with cyclic
     2039!--    conditions and will be initialized with data provided by Inifor
     2040!--    boundaries in case of Dirichlet.
    20292041!--    Hence, simply set set nxlu/nysv to 1 (will be reset to its original value
    20302042!--    at the end of this routine.
    2031        IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = 1 
     2043       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = 1
    20322044       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = 1
    20332045
     
    20422054!--          Open file in read-only mode
    20432055             CALL open_read_file( TRIM( input_file_dynamic ) //                &
    2044                                   TRIM( coupling_char ), id_dynamic ) 
    2045 
    2046 !
    2047 !--          At first, inquire all variable names. 
     2056                                  TRIM( coupling_char ), id_dynamic )
     2057
     2058!
     2059!--          At first, inquire all variable names.
    20482060             CALL inquire_num_variables( id_dynamic, num_vars )
    20492061!
     
    20532065!
    20542066!--          Read vertical dimension of scalar und w grid. Will be used for
    2055 !--          inter- and extrapolation in case of stretched numeric grid. 
     2067!--          inter- and extrapolation in case of stretched numeric grid.
    20562068!--          This will be removed when Inifor is able to handle stretched grids.
    20572069             CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
     
    20602072!
    20612073!--          Read also the horizontal dimensions. These are used just used fo
    2062 !--          checking the compatibility with the PALM grid before reading. 
     2074!--          checking the compatibility with the PALM grid before reading.
    20632075             CALL get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
    20642076             CALL get_dimension_length( id_dynamic, init_3d%nxu, 'xu' )
     
    20682080!
    20692081!--          Check for correct horizontal and vertical dimension. Please note,
    2070 !--          checks are performed directly here and not called from 
    2071 !--          check_parameters as some varialbes are still not allocated there. 
    2072 !--          Moreover, please note, u- and v-grid has 1 grid point less on 
    2073 !--          Inifor grid. 
     2082!--          checks are performed directly here and not called from
     2083!--          check_parameters as some varialbes are still not allocated there.
     2084!--          Moreover, please note, u- and v-grid has 1 grid point less on
     2085!--          Inifor grid.
    20742086             IF ( init_3d%nx-1 /= nx  .OR.  init_3d%nxu-1 /= nx - 1  .OR.      &
    20752087                  init_3d%ny-1 /= ny  .OR.  init_3d%nyv-1 /= ny - 1 )  THEN
     
    21022114             ENDIF
    21032115!
    2104 !--          Read initial geostrophic wind components at 
    2105 !--          t = 0 (index 1 in file). 
    2106              IF ( check_existence( var_names, 'ls_forcing_ug' ) )  THEN
     2116!--          Read initial geostrophic wind components at
     2117!--          t = 0 (index 1 in file).
     2118             IF ( check_existence( var_names, 'tend_ug' ) )  THEN
    21072119                ALLOCATE( init_3d%ug_init(nzb:nzt+1) )
    2108                 CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1,          &
     2120                CALL get_variable_pr( id_dynamic, 'tend_ug', 1,                &
    21092121                                      init_3d%ug_init )
    21102122                init_3d%from_file_ug = .TRUE.
     
    21122124                init_3d%from_file_ug = .FALSE.
    21132125             ENDIF
    2114              IF ( check_existence( var_names, 'ls_forcing_vg' ) )  THEN
     2126             IF ( check_existence( var_names, 'tend_vg' ) )  THEN
    21152127                ALLOCATE( init_3d%vg_init(nzb:nzt+1) )
    2116                 CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1,          &
     2128                CALL get_variable_pr( id_dynamic, 'tend_vg', 1,                &
    21172129                                      init_3d%vg_init )
    21182130                init_3d%from_file_vg = .TRUE.
     
    21212133             ENDIF
    21222134!
    2123 !--          Read inital 3D data of u, v, w, pt and q, 
     2135!--          Read inital 3D data of u, v, w, pt and q,
    21242136!--          derived from COSMO model. Read PE-wise yz-slices.
    2125 !--          Please note, the u-, v- and w-component are defined on different 
     2137!--          Please note, the u-, v- and w-component are defined on different
    21262138!--          grids with one element less in the x-, y-,
    21272139!--          and z-direction, respectively. Hence, reading is subdivided
    2128 !--          into separate loops. Moreover, i and j are used 
     2140!--          into separate loops. Moreover, i and j are used
    21292141!--          as start index in the NF90 interface.
    2130 !--          The passed arguments for u, and v are (i,j)-1, respectively, 
     2142!--          The passed arguments for u, and v are (i,j)-1, respectively,
    21312143!--          in contrast to the remaining quantities. This is because in case
    2132 !--          of forcing is applied, the input data for u and v has one 
    2133 !--          element less along the x- and y-direction respectively. 
     2144!--          of forcing is applied, the input data for u and v has one
     2145!--          element less along the x- and y-direction respectively.
    21342146!--          Read u-component
    21352147             IF ( check_existence( var_names, 'init_u' ) )  THEN
     
    21522164                ELSEIF ( init_3d%lod_u == 2 )  THEN
    21532165!
    2154 !--                Set offset value. In case of Dirichlet conditions at the left 
    2155 !--                domain boundary, the u component starts at nxl+1. This case, 
     2166!--                Set offset value. In case of Dirichlet conditions at the left
     2167!--                domain boundary, the u component starts at nxl+1. This case,
    21562168!--                the passed start-index for reading the NetCDF data is shifted
    2157 !--                by -1. 
     2169!--                by -1.
    21582170                   off_i = 1 !MERGE( 1, 0, forcing )
    21592171
    21602172                   DO  i = nxlu, nxr
    2161                       DO  j = nys, nyn   
     2173                      DO  j = nys, nyn
    21622174                         CALL get_variable( id_dynamic, 'init_u', i-off_i, j,  &
    21632175                                            u(nzb+1:nzt+1,j,i) )
     
    21902202                ELSEIF ( init_3d%lod_v == 2 )  THEN
    21912203!
    2192 !--                Set offset value. In case of Dirichlet conditions at the south 
    2193 !--                domain boundary, the v component starts at nys+1. This case, 
     2204!--                Set offset value. In case of Dirichlet conditions at the south
     2205!--                domain boundary, the v component starts at nys+1. This case,
    21942206!--                the passed start-index for reading the NetCDF data is shifted
    2195 !--                by -1. 
     2207!--                by -1.
    21962208                   off_j = 1 !MERGE( 1, 0, forcing )
    21972209
    21982210                   DO  i = nxl, nxr
    2199                       DO  j = nysv, nyn   
     2211                      DO  j = nysv, nyn
    22002212                         CALL get_variable( id_dynamic, 'init_v', i, j-off_j,  &
    22012213                                            v(nzb+1:nzt+1,j,i) )
     
    22392251!
    22402252!--          Read potential temperature
    2241              IF ( .NOT. neutral )  THEN     
    2242                 IF ( check_existence( var_names, 'init_pt' ) )  THEN   
     2253             IF ( .NOT. neutral )  THEN
     2254                IF ( check_existence( var_names, 'init_pt' ) )  THEN
    22432255!
    22442256!--                Read attributes for the fill value and level-of-detail
     
    22672279                      ENDDO
    22682280
    2269                    ENDIF 
     2281                   ENDIF
    22702282                   init_3d%from_file_pt = .TRUE.
    22712283                ENDIF
     
    23852397       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
    23862398!
    2387 !--    Finally, check if the input data has any fill values. Please note, 
     2399!--    Finally, check if the input data has any fill values. Please note,
    23882400!--    checks depend on the LOD of the input data.
    23892401       IF ( init_3d%from_file_u )  THEN
     
    24682480!
    24692481!--    Workaround for cyclic conditions. Please see above for further explanation.
    2470        IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = nxl 
     2482       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = nxl
    24712483       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = nys
    24722484
     
    24762488! Description:
    24772489! ------------
    2478 !> Reads data at lateral and top boundaries derived from larger-scale model 
     2490!> Reads data at lateral and top boundaries derived from larger-scale model
    24792491!> (COSMO) by Inifor.
    24802492!------------------------------------------------------------------------------!
     
    25012513       INTEGER(iwp) ::  t          !< running index time dimension
    25022514
    2503        REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file   
    2504 
    2505        force%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic ) 
     2515       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
     2516
     2517       force%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic )
    25062518!
    25072519!--    Skip input if no forcing from larger-scale models is applied.
     
    25182530!--          Open file in read-only mode
    25192531             CALL open_read_file( TRIM( input_file_dynamic ) //                &
    2520                                   TRIM( coupling_char ), id_dynamic ) 
    2521 !
    2522 !--          Initialize INIFOR forcing. 
     2532                                  TRIM( coupling_char ), id_dynamic )
     2533!
     2534!--          Initialize INIFOR forcing.
    25232535             IF ( .NOT. force%init )  THEN
    25242536!
    2525 !--             At first, inquire all variable names. 
     2537!--             At first, inquire all variable names.
    25262538                CALL inquire_num_variables( id_dynamic, num_vars )
    25272539!
     
    25672579
    25682580!
    2569 !--          Obtain time index for current input starting at 0. 
    2570 !--          @todo: At the moment time, in INIFOR and simulated time correspond 
    2571 !--                 to each other. If required, adjust to daytime. 
     2581!--          Obtain time index for current input starting at 0.
     2582!--          @todo: At the moment time, in INIFOR and simulated time correspond
     2583!--                 to each other. If required, adjust to daytime.
    25722584             force%tind = MINLOC( ABS( force%time - simulated_time ), DIM = 1 )&
    25732585                          - 1
     
    25782590             IF ( bc_lr_cyc  .AND.  bc_ns_cyc )  THEN
    25792591                DO  t = force%tind, force%tind_p
    2580                    CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1,     &
     2592                   CALL get_variable_pr( id_dynamic, 'tend_ug', t+1,           &
    25812593                                         force%ug(t-force%tind,:) )
    2582                    CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1,     &
     2594                   CALL get_variable_pr( id_dynamic, 'tend_vg', t+1,           &
    25832595                                         force%ug(t-force%tind,:) )
    25842596                ENDDO
    2585              ENDIF 
    2586 !
    2587 !--          Read data at lateral and top boundaries. Please note, at left and 
    2588 !--          right domain boundary, yz-layers are read for u, v, w, pt and q. 
     2597             ENDIF
     2598!
     2599!--          Read data at lateral and top boundaries. Please note, at left and
     2600!--          right domain boundary, yz-layers are read for u, v, w, pt and q.
    25892601!--          For the v-component, the data starts at nysv, while for the other
    2590 !--          quantities the data starts at nys. This is equivalent at the north 
    2591 !--          and south domain boundary for the u-component. 
     2602!--          quantities the data starts at nys. This is equivalent at the north
     2603!--          and south domain boundary for the u-component.
    25922604!--          The function get_variable_bc assumes the start indices with respect
    2593 !--          to the netcdf file convention (data starts at index 1). For this 
    2594 !--          reason, nys+1 / nxl+1 are passed instead of nys / nxl. For the 
     2605!--          to the netcdf file convention (data starts at index 1). For this
     2606!--          reason, nys+1 / nxl+1 are passed instead of nys / nxl. For the
    25952607!--          the u- and v-component at the north/south, and left/right boundary,
    2596 !--          nxlu and nysv are passed, respectively, since these always starts 
    2597 !--          at index 1 in case of forcing. 
     2608!--          nxlu and nysv are passed, respectively, since these always starts
     2609!--          at index 1 in case of forcing.
    25982610
    25992611             IF ( force_bound_l )  THEN
     
    28812893
    28822894!
    2883 !--    Finally, after data input set control flag indicating that vertical 
    2884 !--    inter- and/or extrapolation is required. 
    2885 !--    Please note, inter/extrapolation of INIFOR data is only a workaroud, 
    2886 !--    as long as INIFOR delivers vertically equidistant data. 
    2887        force%interpolated = .FALSE. 
     2895!--    Finally, after data input set control flag indicating that vertical
     2896!--    inter- and/or extrapolation is required.
     2897!--    Please note, inter/extrapolation of INIFOR data is only a workaroud,
     2898!--    as long as INIFOR delivers vertically equidistant data.
     2899       force%interpolated = .FALSE.
    28882900
    28892901    END SUBROUTINE netcdf_data_input_lsf
     
    29112923!
    29122924!--    Dynamic input file must also be present if initialization via inifor is
    2913 !--    prescribed. 
     2925!--    prescribed.
    29142926       IF ( .NOT. input_pids_dynamic  .AND.                                    &
    29152927            TRIM( initializing_actions ) == 'inifor' )  THEN
     
    29472959       INTEGER(iwp) ::  n_surf !< number of different surface types at given location
    29482960
    2949        LOGICAL      ::  check_passed !< flag indicating if a check passed 
     2961       LOGICAL      ::  check_passed !< flag indicating if a check passed
    29502962
    29512963!
     
    29612973       ENDIF
    29622974!
    2963 !--    Check if grid spacing of provided input data matches the respective 
    2964 !--    grid spacing in the model. 
     2975!--    Check if grid spacing of provided input data matches the respective
     2976!--    grid spacing in the model.
    29652977       IF ( dim_static%x(1) - dim_static%x(0) /= dx  .OR.                      &
    29662978            dim_static%y(1) - dim_static%y(0) /= dy )  THEN
     
    29732985!--    Check orography for fill-values. For the moment, give an error message.
    29742986!--    More advanced methods, e.g. a nearest neighbor algorithm as used in GIS
    2975 !--    systems might be implemented later. 
    2976 !--    Please note, if no terrain height is provided, it is set to 0. 
     2987!--    systems might be implemented later.
     2988!--    Please note, if no terrain height is provided, it is set to 0.
    29772989       IF ( ANY( terrain_height_f%var == terrain_height_f%fill ) )  THEN
    2978           message_string = 'NetCDF variable orography_2D is not ' //           &
     2990          message_string = 'NetCDF variable zt is not ' //                     &
    29792991                           'allowed to have missing data'
    29802992          CALL message( 'netcdf_data_input_mod', 'NDI013', 2, 2, 0, 6, 0 )
    29812993       ENDIF
    29822994!
    2983 !--    If 3D buildings are read, check if building information is consistent 
    2984 !--    to numeric grid. 
     2995!--    If 3D buildings are read, check if building information is consistent
     2996!--    to numeric grid.
    29852997       IF ( buildings_f%from_file )  THEN
    29862998          IF ( buildings_f%lod == 2 )  THEN
    29872999             IF ( buildings_f%nz > SIZE( zu ) )  THEN
    29883000                message_string = 'Reading 3D building data - too much ' //     &
    2989                                  'data points along the vertical coordinate.' 
     3001                                 'data points along the vertical coordinate.'
    29903002                CALL message( 'netcdf_data_input_mod', 'NDI014', 2, 2, 0, 6, 0 )
    29913003             ENDIF
     
    30033015!--    Skip further checks concerning buildings and natural surface properties
    30043016!--    if no urban surface and land surface model are applied.
    3005        IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN 
     3017       IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN
    30063018!
    30073019!--    Check for minimum requirement of surface-classification data in case
     
    30173029                           'soil_type and water_type are '//                   &
    30183030                           'required. If urban-surface model is applied, ' //  &
    3019                            'also building_type ist required' 
     3031                           'also building_type ist required'
    30203032          CALL message( 'netcdf_data_input_mod', 'NDI016', 1, 2, 0, 6, 0 )
    30213033       ENDIF
    30223034!
    30233035!--    Check for general availability of input variables.
    3024 !--    If vegetation_type is 0 at any location, vegetation_pars as well as 
    3025 !--    root_area_density_lsm are required.
     3036!--    If vegetation_type is 0 at any location, vegetation_pars as well as
     3037!--    root_area_dens_s are required.
    30263038       IF ( vegetation_type_f%from_file )  THEN
    30273039          IF ( ANY( vegetation_type_f%var == 0 ) )  THEN
     
    30333045             IF ( .NOT. root_area_density_lsm_f%from_file )  THEN
    30343046                message_string = 'If vegegation_type = 0 at any location, ' // &
    3035                                  'root_area_density_lsm is required'
     3047                                 'root_area_dens_s is required'
    30363048                CALL message( 'netcdf_data_input_mod', 'NDI018', 2, 2, 0, 6, 0 )
    30373049             ENDIF
     
    30413053!--    If soil_type is zero at any location, soil_pars is required.
    30423054       IF ( soil_type_f%from_file )  THEN
    3043           check_passed = .TRUE. 
     3055          check_passed = .TRUE.
    30443056          IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
    30453057             IF ( ANY( soil_type_f%var_2d == 0 ) )  THEN
     
    30543066             message_string = 'If soil_type = 0 at any location, ' //          &
    30553067                              'soil_pars is required'
    3056              CALL message( 'netcdf_data_input_mod', 'NDI019', 2, 2, 0, 6, 0 )         
     3068             CALL message( 'netcdf_data_input_mod', 'NDI019', 2, 2, 0, 6, 0 )
    30573069          ENDIF
    30583070       ENDIF
     
    30643076                message_string = 'If building_type = 0 at any location, ' //   &
    30653077                                 'building_pars is required'
    3066                 CALL message( 'netcdf_data_input_mod', 'NDI020', 2, 2, 0, 6, 0 )         
     3078                CALL message( 'netcdf_data_input_mod', 'NDI020', 2, 2, 0, 6, 0 )
    30673079             ENDIF
    30683080          ENDIF
     
    30753087                message_string = 'If albedo_type = 0 at any location, ' //     &
    30763088                                 'albedo_pars is required'
    3077                 CALL message( 'netcdf_data_input_mod', 'NDI021', 2, 2, 0, 6, 0 )     
    3078              ENDIF     
     3089                CALL message( 'netcdf_data_input_mod', 'NDI021', 2, 2, 0, 6, 0 )
     3090             ENDIF
    30793091          ENDIF
    30803092       ENDIF
     
    30863098                message_string = 'If pavement_type = 0 at any location, ' //   &
    30873099                                 'pavement_pars is required'
    3088                 CALL message( 'netcdf_data_input_mod', 'NDI022', 2, 2, 0, 6, 0 )     
    3089              ENDIF     
     3100                CALL message( 'netcdf_data_input_mod', 'NDI022', 2, 2, 0, 6, 0 )
     3101             ENDIF
    30903102          ENDIF
    30913103       ENDIF
     
    30983110                message_string = 'If pavement_type = 0 at any location, ' //   &
    30993111                                 'pavement_subsurface_pars is required'
    3100                 CALL message( 'netcdf_data_input_mod', 'NDI023', 2, 2, 0, 6, 0 )     
    3101              ENDIF     
     3112                CALL message( 'netcdf_data_input_mod', 'NDI023', 2, 2, 0, 6, 0 )
     3113             ENDIF
    31023114          ENDIF
    31033115       ENDIF
     
    31093121                message_string = 'If water_type = 0 at any location, ' //      &
    31103122                                 'water_pars is required'
    3111                 CALL message( 'netcdf_data_input_mod', 'NDI024', 2, 2, 0, 6, 0 )     
    3112              ENDIF     
     3123                CALL message( 'netcdf_data_input_mod', 'NDI024', 2, 2, 0, 6, 0 )
     3124             ENDIF
    31133125          ENDIF
    31143126       ENDIF
     
    31183130          DO  j = nys, nyn
    31193131!
    3120 !--          For each (y,x)-location at least one of the parameters 
     3132!--          For each (y,x)-location at least one of the parameters
    31213133!--          vegetation_type, pavement_type, building_type, or water_type
    31223134!--          must be set to a non­missing value.
     
    31323144             ENDIF
    31333145!
    3134 !--          Note that a soil_type is required for each location (y,x) where 
     3146!--          Note that a soil_type is required for each location (y,x) where
    31353147!--          either vegetation_type or pavement_type is a non­missing value.
    31363148             IF ( ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .OR. &
     
    31543166             ENDIF
    31553167!
    3156 !--          Check for consistency of surface fraction. If more than one type 
    3157 !--          is set, surface fraction need to be given and the sum must not 
     3168!--          Check for consistency of surface fraction. If more than one type
     3169!--          is set, surface fraction need to be given and the sum must not
    31583170!--          be larger than 1.
    31593171             n_surf = 0
     
    31643176             IF ( pavement_type_f%var(j,i)   /= pavement_type_f%fill )         &
    31653177                n_surf = n_surf + 1
    3166              
     3178
    31673179             IF ( n_surf > 1 )  THEN
    31683180                IF ( ANY ( surface_fraction_f%frac(:,j,i) ==                   &
     
    31813193             ENDIF
    31823194!
    3183 !--          Check for further mismatches, e.g. vegetation_type is set but 
    3184 !--          surface vegetation fraction is zero. 
     3195!--          Check for further mismatches, e.g. vegetation_type is set but
     3196!--          surface vegetation fraction is zero.
    31853197             IF ( ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .AND.&
    31863198                 ( surface_fraction_f%frac(ind_veg_wall,j,i) == 0.0_wp .OR.    &
     
    31973209                   surface_fraction_f%frac(ind_wat_win,j,i) ==                 &
    31983210                                                     surface_fraction_f%fill ) &
    3199                   ) )  THEN 
     3211                  ) )  THEN
    32003212                WRITE( message_string, * ) 'Mismatch in setting of '     //    &
    32013213                             'surface_fraction. Vegetation-, pavement-, or '// &
     
    32063218             ENDIF
    32073219!
    3208 !--          Check for further mismatches, e.g. vegetation_type is not set       
    3209 !--          surface vegetation fraction is non-zero. 
     3220!--          Check for further mismatches, e.g. vegetation_type is not set
     3221!--          surface vegetation fraction is non-zero.
    32103222             IF ( ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.&
    32113223                 ( surface_fraction_f%frac(ind_veg_wall,j,i) /= 0.0_wp .AND.   &
     
    32223234                   surface_fraction_f%frac(ind_wat_win,j,i) /=                 &
    32233235                                                     surface_fraction_f%fill ) &
    3224                   ) )  THEN 
     3236                  ) )  THEN
    32253237                WRITE( message_string, * ) 'Mismatch in setting of '     //    &
    32263238                             'surface_fraction. Vegetation-, pavement-, or '// &
     
    32323244             ENDIF
    32333245!
    3234 !--          Check vegetation_pars. If vegetation_type is 0, all parameters 
    3235 !--          need to be set, otherwise, single parameters set by 
     3246!--          Check vegetation_pars. If vegetation_type is 0, all parameters
     3247!--          need to be set, otherwise, single parameters set by
    32363248!--          vegetation_type can be overwritten.
    32373249             IF ( vegetation_type_f%from_file )  THEN
     
    32403252                             vegetation_pars_f%fill ) )  THEN
    32413253                      message_string = 'If vegetation_type(y,x) = 0, all '  // &
    3242                                        'parameters of vegetation_pars at '//   & 
    3243                                        'this location must be set.' 
     3254                                       'parameters of vegetation_pars at '//   &
     3255                                       'this location must be set.'
    32443256                      CALL message( 'netcdf_data_input_mod', 'NDI031',         &
    32453257                                     2, 2, 0, 6, 0 )
     
    32483260             ENDIF
    32493261!
    3250 !--          Check root distribution. If vegetation_type is 0, all levels must 
     3262!--          Check root distribution. If vegetation_type is 0, all levels must
    32513263!--          be set.
    32523264             IF ( vegetation_type_f%from_file )  THEN
     
    32553267                             root_area_density_lsm_f%fill ) )  THEN
    32563268                      message_string = 'If vegetation_type(y,x) = 0, all ' //  &
    3257                                        'levels of root_area_density_lsm ' //   &
    3258                                        'must be set at this location.' 
     3269                                       'levels of root_area_dens_s ' //        &
     3270                                       'must be set at this location.'
    32593271                      CALL message( 'netcdf_data_input_mod', 'NDI032',         &
    32603272                                     2, 2, 0, 6, 0 )
     
    32633275             ENDIF
    32643276!
    3265 !--          Check soil parameters. If soil_type is 0, all parameters 
     3277!--          Check soil parameters. If soil_type is 0, all parameters
    32663278!--          must be set.
    32673279             IF ( soil_type_f%from_file )  THEN
     
    32793291                ENDIF
    32803292                IF ( .NOT. check_passed )  THEN
    3281                    message_string = 'If soil_type(y,x) = 0, all levels of '  //& 
    3282                                     'soil_pars at this location must be set.' 
     3293                   message_string = 'If soil_type(y,x) = 0, all levels of '  //&
     3294                                    'soil_pars at this location must be set.'
    32833295                   CALL message( 'netcdf_data_input_mod', 'NDI033',            &
    32843296                                  2, 2, 0, 6, 0 )
     
    32873299
    32883300!
    3289 !--          Check building parameters. If building_type is 0, all parameters 
     3301!--          Check building parameters. If building_type is 0, all parameters
    32903302!--          must be set.
    32913303             IF ( building_type_f%from_file )  THEN
     
    32953307                      message_string = 'If building_type(y,x) = 0, all ' //    &
    32963308                                       'parameters of building_pars at this '//&
    3297                                        'location must be set.' 
     3309                                       'location must be set.'
    32983310                      CALL message( 'netcdf_data_input_mod', 'NDI034',         &
    32993311                                     2, 2, 0, 6, 0 )
     
    33323344!
    33333345!--          Check if at each location where a building is present also an ID
    3334 !--          is set and vice versa. 
     3346!--          is set and vice versa.
    33353347             IF ( buildings_f%from_file )  THEN
    33363348                IF ( buildings_f%lod == 1 )  THEN
     
    33563368!
    33573369!--          Check if at each location where a building ID or a -type is set
    3358 !--          also a bulding is defined. 
     3370!--          also a bulding is defined.
    33593371             IF ( buildings_f%from_file )  THEN
    33603372                IF ( buildings_f%lod == 1 )  THEN
     
    33773389             ENDIF
    33783390!
    3379 !--          Check albedo parameters. If albedo_type is 0, all parameters 
     3391!--          Check albedo parameters. If albedo_type is 0, all parameters
    33803392!--          must be set.
    33813393             IF ( albedo_type_f%from_file )  THEN
     
    33853397                      message_string = 'If albedo_type(y,x) = 0, all ' //      &
    33863398                                       'parameters of albedo_pars at this ' // &
    3387                                        'location must be set.' 
     3399                                       'location must be set.'
    33883400                      CALL message( 'netcdf_data_input_mod', 'NDI037',         &
    33893401                                     2, 2, 0, 6, 0 )
     
    33933405
    33943406!
    3395 !--          Check pavement parameters. If pavement_type is 0, all parameters 
     3407!--          Check pavement parameters. If pavement_type is 0, all parameters
    33963408!--          of pavement_pars must be set at this location.
    33973409             IF ( pavement_type_f%from_file )  THEN
     
    34013413                      message_string = 'If pavement_type(y,x) = 0, all ' //    &
    34023414                                       'parameters of pavement_pars at this '//&
    3403                                        'location must be set.' 
     3415                                       'location must be set.'
    34043416                      CALL message( 'netcdf_data_input_mod', 'NDI038',         &
    34053417                                     2, 2, 0, 6, 0 )
     
    34083420             ENDIF
    34093421!
    3410 !--          Check pavement-subsurface parameters. If pavement_type is 0, 
    3411 !--          all parameters of pavement_subsurface_pars must be set  at this 
     3422!--          Check pavement-subsurface parameters. If pavement_type is 0,
     3423!--          all parameters of pavement_subsurface_pars must be set  at this
    34123424!--          location.
    34133425             IF ( pavement_type_f%from_file )  THEN
     
    34183430                                       'parameters of '                  //    &
    34193431                                       'pavement_subsurface_pars at this '//   &
    3420                                        'location must be set.' 
     3432                                       'location must be set.'
    34213433                      CALL message( 'netcdf_data_input_mod', 'NDI039',         &
    34223434                                     2, 2, 0, 6, 0 )
     
    34263438
    34273439!
    3428 !--          Check water parameters. If water_type is 0, all parameters 
     3440!--          Check water parameters. If water_type is 0, all parameters
    34293441!--          must be set  at this location.
    34303442             IF ( water_type_f%from_file )  THEN
     
    34343446                      message_string = 'If water_type(y,x) = 0, all ' //       &
    34353447                                       'parameters of water_pars at this ' //  &
    3436                                        'location must be set.' 
     3448                                       'location must be set.'
    34373449                      CALL message( 'netcdf_data_input_mod', 'NDI040',         &
    34383450                                     2, 2, 0, 6, 0 )
     
    34613473       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    34623474       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3463        INTEGER(iwp) ::  nz_file !< number of vertical levels on file 
    3464 
    3465 
    3466        REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid 
    3467        REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid 
     3475       INTEGER(iwp) ::  nz_file !< number of vertical levels on file
     3476
     3477
     3478       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
     3479       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
    34683480       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var      !< treated variable
    34693481       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
     
    34833495                                       ( var(kk+1)        - var(kk)    ) /     &
    34843496                                       ( z_file(kk+1)     - z_file(kk) ) *     &
    3485                                        ( z_grid(k)        - z_file(kk) ) 
     3497                                       ( z_grid(k)        - z_file(kk) )
    34863498
    34873499             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
     
    34893501                                         ( var(kk)     - var(kk-1)    ) /      &
    34903502                                         ( z_file(kk)  - z_file(kk-1) ) *      &
    3491                                          ( z_grid(k)   - z_file(kk-1) ) 
     3503                                         ( z_grid(k)   - z_file(kk-1) )
    34923504             ENDIF
    34933505!
    34943506!--       Extrapolate
    34953507          ELSE
    3496      
     3508
    34973509             var_tmp(k) = var(ku) +   ( var(ku)    - var(ku-1)      ) /        &
    34983510                                      ( z_file(ku) - z_file(ku-1)   ) *        &
    3499                                       ( z_grid(k)  - z_file(ku)     ) 
    3500    
     3511                                      ( z_grid(k)  - z_file(ku)     )
     3512
    35013513          ENDIF
    35023514
     
    35193531    SUBROUTINE netcdf_data_input_interpolate_1d_soil( var, var_file,           &
    35203532                                                      z_grid, z_file,          &
    3521                                                       nzb_var, nzt_var,        & 
     3533                                                      nzb_var, nzt_var,        &
    35223534                                                      nzb_file, nzt_file )
    35233535
     
    35293541       INTEGER(iwp) ::  kk       !< running index z-direction stretched model grid
    35303542       INTEGER(iwp) ::  ku       !< upper index bound along z-direction for varialbe from file
    3531        INTEGER(iwp) ::  nzb_var  !< lower bound of final array 
    3532        INTEGER(iwp) ::  nzt_var  !< upper bound of final array 
    3533        INTEGER(iwp) ::  nzb_file !< lower bound of file array 
    3534        INTEGER(iwp) ::  nzt_file !< upper bound of file array 
     3543       INTEGER(iwp) ::  nzb_var  !< lower bound of final array
     3544       INTEGER(iwp) ::  nzt_var  !< upper bound of final array
     3545       INTEGER(iwp) ::  nzb_file !< lower bound of file array
     3546       INTEGER(iwp) ::  nzt_file !< upper bound of file array
    35353547
    35363548!        LOGICAL, OPTIONAL ::  depth !< flag indicating reverse z-axis, i.e. depth instead of height, e.g. in case of ocean or soil
    35373549
    3538        REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  z_grid   !< grid levels on numeric grid 
    3539        REAL(wp), DIMENSION(nzb_file:nzt_file) ::  z_file   !< grid levels on file grid 
     3550       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  z_grid   !< grid levels on numeric grid
     3551       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  z_file   !< grid levels on file grid
    35403552       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  var      !< treated variable
    35413553       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  var_file !< temporary variable
     
    35483560          kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
    35493561!
    3550 !--       If closest index on Inifor grid is smaller than top index, 
     3562!--       If closest index on Inifor grid is smaller than top index,
    35513563!--       interpolate the data
    35523564          IF ( kk < nzt_file )  THEN
     
    35543566                var(k) = var_file(kk) + ( var_file(kk+1) - var_file(kk) ) /    &
    35553567                                        ( z_file(kk+1)   - z_file(kk)   ) *    &
    3556                                         ( z_grid(k)      - z_file(kk)   ) 
     3568                                        ( z_grid(k)      - z_file(kk)   )
    35573569
    35583570             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
    35593571                var(k) = var_file(kk-1) + ( var_file(kk) - var_file(kk-1) ) /  &
    35603572                                          ( z_file(kk)   - z_file(kk-1)   ) *  &
    3561                                           ( z_grid(k)    - z_file(kk-1)   ) 
     3573                                          ( z_grid(k)    - z_file(kk-1)   )
    35623574             ENDIF
    35633575!
     
    35663578             var(k) = var_file(ku) + ( var_file(ku) - var_file(ku-1) ) /       &
    35673579                                     ( z_file(ku)   - z_file(ku-1)   ) *       &
    3568                                      ( z_grid(k)    - z_file(ku)     ) 
     3580                                     ( z_grid(k)    - z_file(ku)     )
    35693581
    35703582          ENDIF
     
    35923604       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    35933605       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3594        INTEGER(iwp) ::  nz_file !< number of vertical levels on file 
    3595 
    3596 
    3597        REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid 
    3598        REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid 
     3606       INTEGER(iwp) ::  nz_file !< number of vertical levels on file
     3607
     3608
     3609       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
     3610       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
    35993611       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var    !< treated variable
    36003612       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
     
    36173629                                          ( var(kk+1,i)      - var(kk,i)  ) /  &
    36183630                                          ( z_file(kk+1)     - z_file(kk) ) *  &
    3619                                           ( z_grid(k)        - z_file(kk) ) 
     3631                                          ( z_grid(k)        - z_file(kk) )
    36203632
    36213633                ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
     
    36233635                                            ( var(kk,i)   - var(kk-1,i)  ) /   &
    36243636                                            ( z_file(kk)  - z_file(kk-1) ) *   &
    3625                                             ( z_grid(k)   - z_file(kk-1) ) 
     3637                                            ( z_grid(k)   - z_file(kk-1) )
    36263638                ENDIF
    36273639!
    36283640!--          Extrapolate
    36293641             ELSE
    3630      
     3642
    36313643                var_tmp(k) = var(ku,i) + ( var(ku,i)  - var(ku-1,i)    ) /     &
    36323644                                         ( z_file(ku) - z_file(ku-1)   ) *     &
    3633                                          ( z_grid(k)  - z_file(ku)     ) 
    3634    
     3645                                         ( z_grid(k)  - z_file(ku)     )
     3646
    36353647             ENDIF
    36363648
     
    36643676       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    36653677       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3666        INTEGER(iwp) ::  nz_file !< number of vertical levels on file 
    3667 
    3668        REAL(wp), DIMENSION(:) ::  z_grid                      !< grid levels on numeric grid 
     3678       INTEGER(iwp) ::  nz_file !< number of vertical levels on file
     3679
     3680       REAL(wp), DIMENSION(:) ::  z_grid                      !< grid levels on numeric grid
    36693681       REAL(wp), DIMENSION(:) ::  z_file                      !< grid levels on file grid
    36703682       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var      !< treated variable
     
    36843696             DO  k = kl, ku
    36853697
    3686                 kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 ) 
     3698                kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
    36873699
    36883700                IF ( kk < ku )  THEN
     
    36913703                                             ( var(kk+1,j,i) - var(kk,j,i) ) / &
    36923704                                             ( z_file(kk+1)  - z_file(kk)  ) * &
    3693                                              ( z_grid(k)     - z_file(kk)  ) 
     3705                                             ( z_grid(k)     - z_file(kk)  )
    36943706
    36953707                   ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
     
    36973709                                             ( var(kk,j,i) - var(kk-1,j,i) ) / &
    36983710                                             ( z_file(kk)  - z_file(kk-1)  ) * &
    3699                                              ( z_grid(k)   - z_file(kk-1)  ) 
     3711                                             ( z_grid(k)   - z_file(kk-1)  )
    37003712                   ENDIF
    37013713!
     
    37053717                                       ( var(ku,j,i)  - var(ku-1,j,i)   ) /    &
    37063718                                       ( z_file(ku)   - z_file(ku-1)    ) *    &
    3707                                        ( z_grid(k)    - z_file(ku)      ) 
     3719                                       ( z_grid(k)    - z_file(ku)      )
    37083720
    37093721                ENDIF
     
    38173829
    38183830       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
    3819        CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name 
     3831       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
    38203832
    38213833       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
     
    38323844          CALL handle_error( 'get_attribute_int32 global', 522 )
    38333845!
    3834 !--    Read attributes referring to a single variable. Therefore, first inquire 
     3846!--    Read attributes referring to a single variable. Therefore, first inquire
    38353847!--    variable id
    38363848       ELSE
     
    38383850          CALL handle_error( 'get_attribute_int32', 522 )
    38393851          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    3840           CALL handle_error( 'get_attribute_int32', 522 )       
     3852          CALL handle_error( 'get_attribute_int32', 522 )
    38413853       ENDIF
    38423854#endif
     
    38563868
    38573869       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
    3858        CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name 
     3870       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
    38593871
    38603872       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
     
    38713883          CALL handle_error( 'get_attribute_int8 global', 523 )
    38723884!
    3873 !--    Read attributes referring to a single variable. Therefore, first inquire 
     3885!--    Read attributes referring to a single variable. Therefore, first inquire
    38743886!--    variable id
    38753887       ELSE
     
    38773889          CALL handle_error( 'get_attribute_int8', 523 )
    38783890          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    3879           CALL handle_error( 'get_attribute_int8', 523 )       
     3891          CALL handle_error( 'get_attribute_int8', 523 )
    38803892       ENDIF
    38813893#endif
     
    38953907
    38963908       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
    3897        CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name 
     3909       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
    38983910
    38993911       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
     
    39123924          CALL handle_error( 'get_attribute_real global', 524 )
    39133925!
    3914 !-- Read attributes referring to a single variable. Therefore, first inquire 
     3926!-- Read attributes referring to a single variable. Therefore, first inquire
    39153927!-- variable id
    39163928       ELSE
     
    39183930          CALL handle_error( 'get_attribute_real', 524 )
    39193931          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    3920           CALL handle_error( 'get_attribute_real', 524 )       
     3932          CALL handle_error( 'get_attribute_real', 524 )
    39213933       ENDIF
    39223934#endif
     
    39383950
    39393951       CHARACTER(LEN=*)                ::  attribute_name   !< attribute name
    3940        CHARACTER(LEN=*), OPTIONAL      ::  variable_name    !< variable name 
     3952       CHARACTER(LEN=*), OPTIONAL      ::  variable_name    !< variable name
    39413953       CHARACTER(LEN=*), INTENT(INOUT) ::  value            !< read value
    39423954
     
    39533965          CALL handle_error( 'get_attribute_string global', 525 )
    39543966!
    3955 !--    Read attributes referring to a single variable. Therefore, first inquire 
     3967!--    Read attributes referring to a single variable. Therefore, first inquire
    39563968!--    variable id
    39573969       ELSE
     
    39603972
    39613973          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    3962           CALL handle_error( 'get_attribute_string',525 ) 
     3974          CALL handle_error( 'get_attribute_string',525 )
    39633975
    39643976       ENDIF
     
    39803992       IMPLICIT NONE
    39813993
    3982        CHARACTER(LEN=*)            ::  variable_name    !< dimension name 
     3994       CHARACTER(LEN=*)            ::  variable_name    !< dimension name
    39833995       CHARACTER(LEN=100)          ::  dum              !< dummy variable to receive return character
    39843996
     
    39944006!--    Inquire dimension length
    39954007       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, dum, LEN = dim_len )
    3996        CALL handle_error( 'get_dimension_length', 526 ) 
     4008       CALL handle_error( 'get_dimension_length', 526 )
    39974009
    39984010#endif
     
    40024014! Description:
    40034015! ------------
    4004 !> Reads a 1D integer variable from file. 
     4016!> Reads a 1D integer variable from file.
    40054017!------------------------------------------------------------------------------!
    40064018     SUBROUTINE get_variable_1d_int( id, variable_name, var )
     
    40104022       IMPLICIT NONE
    40114023
    4012        CHARACTER(LEN=*)            ::  variable_name    !< variable name 
     4024       CHARACTER(LEN=*)            ::  variable_name    !< variable name
    40134025
    40144026       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
     
    40254037!--    Inquire dimension length
    40264038       nc_stat = NF90_GET_VAR( id, id_var, var )
    4027        CALL handle_error( 'get_variable_1d_int', 527 ) 
     4039       CALL handle_error( 'get_variable_1d_int', 527 )
    40284040
    40294041#endif
     
    40334045! Description:
    40344046! ------------
    4035 !> Reads a 1D float variable from file. 
     4047!> Reads a 1D float variable from file.
    40364048!------------------------------------------------------------------------------!
    40374049     SUBROUTINE get_variable_1d_real( id, variable_name, var )
     
    40414053       IMPLICIT NONE
    40424054
    4043        CHARACTER(LEN=*)            ::  variable_name    !< variable name 
     4055       CHARACTER(LEN=*)            ::  variable_name    !< variable name
    40444056
    40454057       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
     
    40564068!--    Inquire dimension length
    40574069       nc_stat = NF90_GET_VAR( id, id_var, var )
    4058        CALL handle_error( 'get_variable_1d_real', 527 ) 
     4070       CALL handle_error( 'get_variable_1d_real', 527 )
    40594071
    40604072#endif
     
    40654077! Description:
    40664078! ------------
    4067 !> Reads a time-dependent 1D float variable from file. 
     4079!> Reads a time-dependent 1D float variable from file.
    40684080!------------------------------------------------------------------------------!
    40694081    SUBROUTINE get_variable_pr( id, variable_name, t, var )
     
    40744086       IMPLICIT NONE
    40754087
    4076        CHARACTER(LEN=*)                      ::  variable_name    !< variable name 
     4088       CHARACTER(LEN=*)                      ::  variable_name    !< variable name
    40774089
    40784090       INTEGER(iwp), INTENT(IN)              ::  id               !< file id
     
    40924104       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = n_file )
    40934105!
    4094 !--    Read variable. 
     4106!--    Read variable.
    40954107       nc_stat = NF90_GET_VAR( id, id_var, var,                                &
    40964108                               start = (/ 1,      t     /),                    &
    40974109                               count = (/ n_file, 1     /) )
    4098        CALL handle_error( 'get_variable_pr', 527 ) 
     4110       CALL handle_error( 'get_variable_pr', 527 )
    40994111
    41004112#endif
     
    41054117! Description:
    41064118! ------------
    4107 !> Reads a 2D REAL variable from a file. Reading is done processor-wise, 
    4108 !> i.e. each core reads its own domain in slices along x. 
    4109 !------------------------------------------------------------------------------! 
     4119!> Reads a 2D REAL variable from a file. Reading is done processor-wise,
     4120!> i.e. each core reads its own domain in slices along x.
     4121!------------------------------------------------------------------------------!
    41104122    SUBROUTINE get_variable_2d_real( id, variable_name, i, var )
    41114123
     
    41394151! Description:
    41404152! ------------
    4141 !> Reads a 2D 32-bit INTEGER variable from file. Reading is done processor-wise, 
    4142 !> i.e. each core reads its own domain in slices along x. 
     4153!> Reads a 2D 32-bit INTEGER variable from file. Reading is done processor-wise,
     4154!> i.e. each core reads its own domain in slices along x.
    41434155!------------------------------------------------------------------------------!
    41444156    SUBROUTINE get_variable_2d_int32( id, variable_name, i, var )
     
    41724184! Description:
    41734185! ------------
    4174 !> Reads a 2D 8-bit INTEGER variable from file. Reading is done processor-wise, 
    4175 !> i.e. each core reads its own domain in slices along x. 
     4186!> Reads a 2D 8-bit INTEGER variable from file. Reading is done processor-wise,
     4187!> i.e. each core reads its own domain in slices along x.
    41764188!------------------------------------------------------------------------------!
    41774189    SUBROUTINE get_variable_2d_int8( id, variable_name, i, var )
     
    42494261! Description:
    42504262! ------------
    4251 !> Reads a 3D float variable from file. 
     4263!> Reads a 3D float variable from file.
    42524264!------------------------------------------------------------------------------!
    42534265    SUBROUTINE get_variable_3d_real( id, variable_name, i, j, var )
     
    43694381! Description:
    43704382! ------------
    4371 !> Reads a 4D float variable from file. Note, in constrast to 3D versions, 
     4383!> Reads a 4D float variable from file. Note, in constrast to 3D versions,
    43724384!> dimensions are already inquired and passed so that they are known here.
    43734385!------------------------------------------------------------------------------!
     
    44114423! Description:
    44124424! ------------
    4413 !> Reads a 3D float variable at left, right, north, south and top boundaries. 
     4425!> Reads a 3D float variable at left, right, north, south and top boundaries.
    44144426!------------------------------------------------------------------------------!
    44154427    SUBROUTINE get_variable_bc( id, variable_name, t_start,                    &
     
    44314443       INTEGER(iwp)                  ::  t_start         !< start index at time dimension with respect to netcdf convention
    44324444
    4433        REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var     !< input variable 
     4445       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var     !< input variable
    44344446#if defined( __netcdf )
    44354447
     
    44404452!--    Get variable
    44414453       nc_stat = NF90_GET_VAR( id, id_var, var,                              &
    4442                                start = (/ i3_s, i2_s, t_start /),            & 
    4443                                count = (/ count_3, count_2, 1 /) )       
     4454                               start = (/ i3_s, i2_s, t_start /),            &
     4455                               count = (/ count_3, count_2, 1 /) )
    44444456
    44454457       CALL handle_error( 'get_variable_bc', 532 )
     
    44524464! Description:
    44534465! ------------
    4454 !> Inquires the number of variables in a file 
     4466!> Inquires the number of variables in a file
    44554467!------------------------------------------------------------------------------!
    44564468    SUBROUTINE inquire_num_variables( id, num_vars )
     
    44754487! Description:
    44764488! ------------
    4477 !> Inquires the variable names belonging to a file. 
     4489!> Inquires the variable names belonging to a file.
    44784490!------------------------------------------------------------------------------!
    44794491    SUBROUTINE inquire_variable_names( id, var_names )
Note: See TracChangeset for help on using the changeset viewer.