Ignore:
Timestamp:
Nov 23, 2020 1:02:38 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4742 r4792  
    11!> @file netcdf_interface_mod.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4742 2020-10-14 15:11:02Z schwenkel
    2729! Implement snow and graupel (bulk microphysics)
    28 ! 
     30!
    2931! 4502 2020-04-17 16:14:16Z schwenkel
    3032! Implementation of ice microphysics
    31 ! 
     33!
    3234! 4455 2020-03-11 12:20:29Z Giersch
    3335! Axis attribute added to netcdf output
    34 ! 
     36!
    3537! 4400 2020-02-10 20:32:41Z suehring
    36 ! Move routine to transform coordinates from netcdf_interface_mod to 
     38! Move routine to transform coordinates from netcdf_interface_mod to
    3739! basic_constants_and_equations_mod
    38 ! 
     40!
    3941! 4360 2020-01-07 11:25:50Z suehring
    4042! Adjusted output of multi-agent system for biometeorology
    41 ! 
     43!
    4244! 4227 2019-09-10 18:04:34Z gronemeier
    4345! Replace function date_time_string by call to get_date_time
    44 ! 
     46!
    4547! 4223 2019-09-10 09:20:47Z gronemeier
    46 ! replaced rotation angle from input-netCDF file
    47 ! by namelist parameter 'rotation_angle'
    48 !
     48! replaced rotation angle from input-netCDF file by namelist parameter 'rotation_angle'
     49!
    4950! 4182 2019-08-22 15:20:23Z scharf
    5051! Corrected "Former revisions" section
    51 ! 
     52!
    5253! 4127 2019-07-30 14:47:10Z suehring
    53 ! -Introduce new vertical dimension for plant-canopy output.
    54 ! -Temporarlily disable masked output for soil (merge from branch resler)
    55 ! 
     54! - Introduce new vertical dimension for plant-canopy output.
     55! - Temporarlily disable masked output for soil (merge from branch resler)
     56!
    5657! 4069 2019-07-01 14:05:51Z Giersch
    57 ! Masked output running index mid has been introduced as a local variable to
    58 ! avoid runtime error (Loop variable has been modified) in time_integration
    59 ! 
     58! Masked output running index mid has been introduced as a local variable to avoid runtime error
     59! (Loop variable has been modified) in time_integration
     60!
    6061! 4046 2019-06-21 17:32:04Z knoop
    6162! removal of special treatment for usm_define_netcdf_grid call
    62 ! 
     63!
    6364! 4039 2019-06-18 10:32:41Z suehring
    6465! Rename subroutines in module for diagnostic quantities
     
    7172!
    7273! 3994 2019-05-22 18:08:09Z suehring
    73 ! remove origin time from time unit, compose origin_time_string within
    74 ! subroutine netcdf_create_global_atts
     74! remove origin time from time unit, compose origin_time_string within subroutine
     75! netcdf_create_global_atts
    7576!
    7677! 3954 2019-05-06 12:49:42Z gronemeier
     
    7879!
    7980! 3953 2019-05-06 12:11:55Z gronemeier
    80 ! bugfix: set origin_time and starting point of time coordinate according to
    81 !         day_of_year_init and time_utc_init
     81! bugfix: set origin_time and starting point of time coordinate according to day_of_year_init and
     82!         time_utc_init
    8283!
    8384! 3942 2019-04-30 13:08:30Z kanani
     
    9293!
    9394! 3744 2019-02-15 18:38:58Z suehring
    94 ! Bugfix: - initialize return values to ensure they are set before returning
    95 !           (routine define_geo_coordinates)
     95! Bugfix: - initialize return values to ensure they are set before returning (routine
     96!           define_geo_coordinates)
    9697!         - change order of dimensions for some variables
    9798!
     
    103104!
    104105! 3655 2019-01-07 16:51:22Z knoop
    105 ! Move the control parameter "salsa" from salsa_mod to control_parameters
    106 ! (M. Kurppa)
     106! Move the control parameter "salsa" from salsa_mod to control_parameters (M. Kurppa)
    107107!
    108108! Revision 1.1  2005/05/18 15:37:16  raasch
     
    113113! ------------
    114114!> In case of extend = .FALSE.:
    115 !> Define all necessary dimensions, axes and variables for the different
    116 !> netCDF datasets. This subroutine is called from check_open after a new
    117 !> dataset is created. It leaves the open netCDF files ready to write.
     115!> Define all necessary dimensions, axes and variables for the different netCDF datasets. This
     116!> subroutine is called from check_open after a new dataset is created. It leaves the open netCDF
     117!> files ready to write.
    118118!>
    119119!> In case of extend = .TRUE.:
    120 !> Find out if dimensions and variables of an existing file match the values
    121 !> of the actual run. If so, get all necessary information (ids, etc.) from
    122 !> this file.
     120!> Find out if dimensions and variables of an existing file match the values of the actual run. If
     121!> so, get all necessary information (ids, etc.) from this file.
    123122!>
    124 !> Parameter av can assume values 0 (non-averaged data) and 1 (time averaged
    125 !> data)
     123!> Parameter av can assume values 0 (non-averaged data) and 1 (time averaged data)
    126124!>
    127 !> @todo calculation of output time levels for parallel NetCDF still does not
    128 !>       cover every exception (change of dt_do, end_time in restart)
    129 !> @todo timeseries and profile output still needs to be rewritten to allow
    130 !>       modularization
     125!> @todo calculation of output time levels for parallel NetCDF still does not cover every exception
     126!        (change of dt_do, end_time in restart)
     127!> @todo timeseries and profile output still needs to be rewritten to allow modularization
    131128!> @todo output 2d UTM coordinates without global arrays
    132129!> @todo output longitude/latitude also with non-parallel output (3d and xy)
    133 !------------------------------------------------------------------------------!
     130!--------------------------------------------------------------------------------------------------!
    134131 MODULE netcdf_interface
    135132
    136     USE control_parameters,                                                    &
    137         ONLY:  biometeorology, fl_max,                                         &
    138                max_masks, multi_agent_system_end,                              &
    139                multi_agent_system_start,                                       &
    140                rotation_angle,                                                 &
    141                var_fl_max, varnamelength
     133    USE control_parameters,                                                                        &
     134        ONLY:  biometeorology,                                                                     &
     135               fl_max,                                                                             &
     136               max_masks,                                                                          &
     137               multi_agent_system_end,                                                             &
     138               multi_agent_system_start,                                                           &
     139               rotation_angle,                                                                     &
     140               var_fl_max,                                                                         &
     141               varnamelength
    142142    USE kinds
    143143#if defined( __netcdf )
    144144    USE NETCDF
    145145#endif
    146     USE mas_global_attributes,                                                 &
     146    USE mas_global_attributes,                                                                     &
    147147        ONLY:  dim_size_agtnum
    148148
    149     USE netcdf_data_input_mod,                                                 &
    150         ONLY: coord_ref_sys,                                                   &
    151               crs_list,                                                        &
     149    USE netcdf_data_input_mod,                                                                     &
     150        ONLY: coord_ref_sys,                                                                       &
     151              crs_list,                                                                            &
    152152              init_model
    153153
    154154    PRIVATE
    155155
    156     CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_names =                      &
    157           (/ 'ag_id           ', 'ag_x            ', 'ag_y            ',       &
    158              'ag_wind         ', 'ag_temp         ', 'ag_group        ',       &
    159              'ag_iPT          ', 'ag_PM10         ', 'ag_PM25         ',       &
    160              'not_used        ', 'not_used        ', 'not_used        ',       &
    161              'not_used        ' /)
    162 
    163     CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_units = &
    164           (/ 'dim_less        ', 'meters          ', 'meters          ',       &
    165              'm/s             ', 'K               ', 'dim_less        ',       &
    166              'C               ', 'tbd             ', 'tbd             ',       &
    167              'tbd             ', 'not_used        ', 'not_used        ',       &
    168              'not_used        ' /)
    169 
    170156    INTEGER(iwp), PARAMETER ::  dopr_norm_num = 7, dopts_num = 29, dots_max = 100
    171 
    172     CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_names =          &
    173          (/ 'wtheta0', 'ws2    ', 'tsw2   ', 'ws3    ', 'ws2tsw ', 'wstsw2 ',  &
    174             'z_i    ' /)
    175 
    176     CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames =      &
    177          (/ 'wtheta0', 'w*2    ', 't*w2   ', 'w*3    ', 'w*2t*w ', 'w*t*w2 ',  &
    178             'z_i    ' /)
    179 
    180     CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_label =                   &
    181           (/ 'tnpt   ', 'x_     ', 'y_     ', 'z_     ', 'z_abs  ', 'u      ', &
    182              'v      ', 'w      ', 'u"     ', 'v"     ', 'w"     ', 'npt_up ', &
    183              'w_up   ', 'w_down ', 'radius ', 'r_min  ', 'r_max  ', 'npt_max', &
    184              'npt_min', 'x*2    ', 'y*2    ', 'z*2    ', 'u*2    ', 'v*2    ', &
    185              'w*2    ', 'u"2    ', 'v"2    ', 'w"2    ', 'npt*2  ' /)
    186 
    187     CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_unit =                    &
    188           (/ 'number ', 'm      ', 'm      ', 'm      ', 'm      ', 'm/s    ', &
    189              'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'number ', &
    190              'm/s    ', 'm/s    ', 'm      ', 'm      ', 'm      ', 'number ', &
    191              'number ', 'm2     ', 'm2     ', 'm2     ', 'm2/s2  ', 'm2/s2  ', &
    192              'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'number2' /)
    193 
    194157    INTEGER(iwp) ::  dots_num  = 25  !< number of timeseries defined by default
    195158    INTEGER(iwp) ::  dots_soil = 26  !< starting index for soil-timeseries
    196159    INTEGER(iwp) ::  dots_rad  = 32  !< starting index for radiation-timeseries
    197160
    198     CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label =                    &
    199           (/ 'E            ', 'E*           ', 'dt           ',                &
    200              'us*          ', 'th*          ', 'umax         ',                &
    201              'vmax         ', 'wmax         ', 'div_new      ',                &
    202              'div_old      ', 'zi_wtheta    ', 'zi_theta     ',                &
    203              'w*           ', 'w"theta"0    ', 'w"theta"     ',                &
    204              'wtheta       ', 'theta(0)     ', 'theta(z_mo)  ',                &
    205              'w"u"0        ', 'w"v"0        ', 'w"q"0        ',                &
    206              'ol           ', 'q*           ', 'w"s"         ',                &
    207              's*           ', 'ghf          ', 'qsws_liq     ',                &
    208              'qsws_soil    ', 'qsws_veg     ', 'r_a          ',                &
    209              'r_s          ',                                                  &
    210              'rad_net      ', 'rad_lw_in    ', 'rad_lw_out   ',                &
    211              'rad_sw_in    ', 'rad_sw_out   ', 'rrtm_aldif   ',                &
    212              'rrtm_aldir   ', 'rrtm_asdif   ', 'rrtm_asdir   ',                &
     161    CHARACTER (LEN=16) :: heatflux_output_unit       !< unit for heatflux output
     162    CHARACTER (LEN=16) :: waterflux_output_unit      !< unit for waterflux output
     163    CHARACTER (LEN=16) :: momentumflux_output_unit   !< unit for momentumflux output
     164    CHARACTER (LEN=40) :: netcdf_data_format_string
     165
     166    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_names =                                          &
     167          (/ 'ag_id           ', 'ag_x            ', 'ag_y            ',                           &
     168             'ag_wind         ', 'ag_temp         ', 'ag_group        ',                           &
     169             'ag_iPT          ', 'ag_PM10         ', 'ag_PM25         ',                           &
     170             'not_used        ', 'not_used        ', 'not_used        ',                           &
     171             'not_used        ' /)
     172
     173    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_units =                                          &
     174          (/ 'dim_less        ', 'meters          ', 'meters          ',                           &
     175             'm/s             ', 'K               ', 'dim_less        ',                           &
     176             'C               ', 'tbd             ', 'tbd             ',                           &
     177             'tbd             ', 'not_used        ', 'not_used        ',                           &
     178             'not_used        ' /)
     179
     180    CHARACTER (LEN=20), DIMENSION(fl_max)            :: dofl_dim_label_x
     181    CHARACTER (LEN=20), DIMENSION(fl_max)            :: dofl_dim_label_y
     182    CHARACTER (LEN=20), DIMENSION(fl_max)            :: dofl_dim_label_z
     183    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_label
     184    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_unit
     185
     186    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_names =                              &
     187         (/ 'wtheta0', 'ws2    ', 'tsw2   ', 'ws3    ', 'ws2tsw ', 'wstsw2 ', 'z_i    ' /)
     188
     189    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames =                          &
     190         (/ 'wtheta0', 'w*2    ', 't*w2   ', 'w*3    ', 'w*2t*w ', 'w*t*w2 ', 'z_i    ' /)
     191
     192    CHARACTER (LEN=9), DIMENSION(300) ::  dopr_unit = 'unknown'
     193
     194    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_label =                                       &
     195          (/ 'tnpt   ', 'x_     ', 'y_     ', 'z_     ', 'z_abs  ', 'u      ',                     &
     196             'v      ', 'w      ', 'u"     ', 'v"     ', 'w"     ', 'npt_up ',                     &
     197             'w_up   ', 'w_down ', 'radius ', 'r_min  ', 'r_max  ', 'npt_max',                     &
     198             'npt_min', 'x*2    ', 'y*2    ', 'z*2    ', 'u*2    ', 'v*2    ',                     &
     199             'w*2    ', 'u"2    ', 'v"2    ', 'w"2    ', 'npt*2  ' /)
     200
     201    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_unit =                                        &
     202          (/ 'number ', 'm      ', 'm      ', 'm      ', 'm      ', 'm/s    ',                     &
     203             'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'number ',                     &
     204             'm/s    ', 'm/s    ', 'm      ', 'm      ', 'm      ', 'number ',                     &
     205             'number ', 'm2     ', 'm2     ', 'm2     ', 'm2/s2  ', 'm2/s2  ',                     &
     206             'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'number2' /)
     207
     208    CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label =                                        &
     209          (/ 'E            ', 'E*           ', 'dt           ',                                    &
     210             'us*          ', 'th*          ', 'umax         ',                                    &
     211             'vmax         ', 'wmax         ', 'div_new      ',                                    &
     212             'div_old      ', 'zi_wtheta    ', 'zi_theta     ',                                    &
     213             'w*           ', 'w"theta"0    ', 'w"theta"     ',                                    &
     214             'wtheta       ', 'theta(0)     ', 'theta(z_mo)  ',                                    &
     215             'w"u"0        ', 'w"v"0        ', 'w"q"0        ',                                    &
     216             'ol           ', 'q*           ', 'w"s"         ',                                    &
     217             's*           ', 'ghf          ', 'qsws_liq     ',                                    &
     218             'qsws_soil    ', 'qsws_veg     ', 'r_a          ',                                    &
     219             'r_s          ',                                                                      &
     220             'rad_net      ', 'rad_lw_in    ', 'rad_lw_out   ',                                    &
     221             'rad_sw_in    ', 'rad_sw_out   ', 'rrtm_aldif   ',                                    &
     222             'rrtm_aldir   ', 'rrtm_asdif   ', 'rrtm_asdir   ',                                    &
    213223             ( 'unknown      ', i9 = 1, dots_max-40 ) /)
    214224
    215     CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_unit =                     &
    216           (/ 'm2/s2        ', 'm2/s2        ', 's            ',                &
    217              'm/s          ', 'K            ', 'm/s          ',                &
    218              'm/s          ', 'm/s          ', 's-1          ',                &
    219              's-1          ', 'm            ', 'm            ',                &
    220              'm/s          ', 'K m/s        ', 'K m/s        ',                &
    221              'K m/s        ', 'K            ', 'K            ',                &
    222              'm2/s2        ', 'm2/s2        ', 'kg m/s       ',                &
    223              'm            ', 'kg/kg        ', 'kg m/(kg s)  ',                &
    224              'kg/kg        ', 'W/m2         ', 'W/m2         ',                &
    225              'W/m2         ', 'W/m2         ', 's/m          ',                &
    226              's/m          ',                                                  &
    227              'W/m2         ', 'W/m2         ', 'W/m2         ',                &
    228              'W/m2         ', 'W/m2         ', '             ',                &
    229              '             ', '             ', '             ',                &
     225    CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_unit =                                         &
     226          (/ 'm2/s2        ', 'm2/s2        ', 's            ',                                    &
     227             'm/s          ', 'K            ', 'm/s          ',                                    &
     228             'm/s          ', 'm/s          ', 's-1          ',                                    &
     229             's-1          ', 'm            ', 'm            ',                                    &
     230             'm/s          ', 'K m/s        ', 'K m/s        ',                                    &
     231             'K m/s        ', 'K            ', 'K            ',                                    &
     232             'm2/s2        ', 'm2/s2        ', 'kg m/s       ',                                    &
     233             'm            ', 'kg/kg        ', 'kg m/(kg s)  ',                                    &
     234             'kg/kg        ', 'W/m2         ', 'W/m2         ',                                    &
     235             'W/m2         ', 'W/m2         ', 's/m          ',                                    &
     236             's/m          ',                                                                      &
     237             'W/m2         ', 'W/m2         ', 'W/m2         ',                                    &
     238             'W/m2         ', 'W/m2         ', '             ',                                    &
     239             '             ', '             ', '             ',                                    &
    230240             ( 'unknown      ', i9 = 1, dots_max-40 ) /)
    231241
    232     CHARACTER (LEN=16) :: heatflux_output_unit     !< unit for heatflux output
    233     CHARACTER (LEN=16) :: waterflux_output_unit    !< unit for waterflux output
    234     CHARACTER (LEN=16) :: momentumflux_output_unit !< unit for momentumflux output
    235 
    236     CHARACTER (LEN=9), DIMENSION(300) ::  dopr_unit = 'unknown'
     242    CHARACTER (LEN=20), DIMENSION(11) ::  netcdf_precision = ' '
    237243
    238244    CHARACTER (LEN=7), DIMENSION(0:1,500) ::  do2d_unit, do3d_unit
     
    260266!             'not_used        ' /)
    261267
    262     CHARACTER(LEN=20), DIMENSION(11) ::  netcdf_precision = ' '
    263     CHARACTER(LEN=40) ::  netcdf_data_format_string
    264 
    265     INTEGER(iwp) ::  id_dim_agtnum, id_dim_time_agt,                           &
    266                      id_dim_time_fl, id_dim_time_pr,                           &
    267                      id_dim_time_pts, id_dim_time_sp, id_dim_time_ts,          &
    268                      id_dim_x_sp, id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp,     &
    269                      id_set_agt, id_set_fl, id_set_pr, id_set_prt, id_set_pts, &
    270                      id_set_sp, id_set_ts, id_var_agtnum, id_var_time_agt,     &
    271                      id_var_time_fl, id_var_rnoa_agt, id_var_time_pr,          &
    272                      id_var_time_pts, id_var_time_sp, id_var_time_ts,          &
    273                      id_var_x_sp, id_var_y_sp, id_var_zu_sp, id_var_zw_sp,     &
     268    INTEGER(iwp) ::  dofl_time_count
     269
     270    INTEGER(iwp) ::  id_dim_agtnum, id_dim_time_agt, id_dim_time_fl, id_dim_time_pr,               &
     271                     id_dim_time_pts, id_dim_time_sp, id_dim_time_ts, id_dim_x_sp, id_dim_y_sp,    &
     272                     id_dim_zu_sp, id_dim_zw_sp,                                                   &
     273                     id_set_agt, id_set_fl, id_set_pr, id_set_prt, id_set_pts, id_set_sp,          &
     274                     id_set_ts,                                                                    &
     275                     id_var_agtnum, id_var_time_agt, id_var_time_fl, id_var_rnoa_agt,              &
     276                     id_var_time_pr, id_var_time_pts, id_var_time_sp, id_var_time_ts, id_var_x_sp, &
     277                     id_var_y_sp, id_var_zu_sp, id_var_zw_sp,                                      &
    274278                     nc_stat
    275279
    276 
    277     INTEGER(iwp), DIMENSION(0:1) ::  id_dim_time_xy, id_dim_time_xz, &
    278                     id_dim_time_yz, id_dim_time_3d, id_dim_x_xy, id_dim_xu_xy, &
    279                     id_dim_x_xz, id_dim_xu_xz, id_dim_x_yz, id_dim_xu_yz, &
    280                     id_dim_x_3d, id_dim_xu_3d, id_dim_y_xy, id_dim_yv_xy, &
    281                     id_dim_y_xz, id_dim_yv_xz, id_dim_y_yz, id_dim_yv_yz, &
    282                     id_dim_y_3d, id_dim_yv_3d, id_dim_zs_xy, id_dim_zs_xz, &
    283                     id_dim_zs_yz, id_dim_zs_3d, id_dim_zpc_3d, &
    284                     id_dim_zu_xy, id_dim_zu1_xy, &
    285                     id_dim_zu_xz, id_dim_zu_yz, id_dim_zu_3d, id_dim_zw_xy, &
    286                     id_dim_zw_xz, id_dim_zw_yz, id_dim_zw_3d, id_set_xy, &
    287                     id_set_xz, id_set_yz, id_set_3d, id_var_ind_x_yz, &
    288                     id_var_ind_y_xz, id_var_ind_z_xy, id_var_time_xy, &
    289                     id_var_time_xz, id_var_time_yz, id_var_time_3d, id_var_x_xy, &
    290                     id_var_xu_xy, id_var_x_xz, id_var_xu_xz, id_var_x_yz, &
    291                     id_var_xu_yz, id_var_x_3d, id_var_xu_3d, id_var_y_xy, &
    292                     id_var_yv_xy, id_var_y_xz, id_var_yv_xz, id_var_y_yz, &
    293                     id_var_yv_yz, id_var_y_3d, id_var_yv_3d, id_var_zs_xy, &
    294                     id_var_zs_xz, id_var_zs_yz, id_var_zs_3d, id_var_zpc_3d, &
    295                     id_var_zusi_xy, id_var_zusi_3d, id_var_zu_xy, id_var_zu1_xy, id_var_zu_xz, &
    296                     id_var_zu_yz, id_var_zu_3d, id_var_zwwi_xy, id_var_zwwi_3d, &
    297                     id_var_zw_xy, id_var_zw_xz, id_var_zw_yz, id_var_zw_3d
    298 
    299     INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_eutm_3d, id_var_nutm_3d, &
    300                                          id_var_eutm_xy, id_var_nutm_xy, &
    301                                          id_var_eutm_xz, id_var_nutm_xz, &
    302                                          id_var_eutm_yz, id_var_nutm_yz
    303 
    304     INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_lat_3d, id_var_lon_3d, &
    305                                          id_var_lat_xy, id_var_lon_xy, &
    306                                          id_var_lat_xz, id_var_lon_xz, &
    307                                          id_var_lat_yz, id_var_lon_yz
    308 
    309     INTEGER ::  netcdf_data_format = 2  !< NetCDF3 64bit offset format
    310     INTEGER ::  netcdf_deflate = 0      !< NetCDF compression, default: no
    311                                         !< compression
    312 
    313     INTEGER(iwp)                 ::  dofl_time_count
    314     INTEGER(iwp), DIMENSION(10)  ::  id_var_dospx, id_var_dospy
    315     INTEGER(iwp), DIMENSION(20)  ::  id_var_agt
    316 !    INTEGER(iwp), DIMENSION(20)  ::  id_var_prt
    317     INTEGER(iwp), DIMENSION(11)  ::  nc_precision
     280    INTEGER      ::  netcdf_data_format = 2  !< NetCDF3 64bit offset format
     281    INTEGER      ::  netcdf_deflate = 0      !< NetCDF compression, default: no
     282                                             !< compression
     283
     284    INTEGER(iwp), DIMENSION(20)            ::  id_var_agt
     285    INTEGER(iwp), DIMENSION(10)            ::  id_var_dospx, id_var_dospy
    318286    INTEGER(iwp), DIMENSION(dopr_norm_num) ::  id_var_norm_dopr
    319 
    320     INTEGER(iwp), DIMENSION(fl_max) ::  id_dim_x_fl, id_dim_y_fl, id_dim_z_fl
    321     INTEGER(iwp), DIMENSION(fl_max) ::  id_var_x_fl, id_var_y_fl, id_var_z_fl
    322 
    323     CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_label
    324     CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_unit
    325     CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_x
    326     CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_y
    327     CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_z
    328 
     287!    INTEGER(iwp), DIMENSION(20)            ::  id_var_prt
     288    INTEGER(iwp), DIMENSION(11)            ::  nc_precision
     289
     290    INTEGER(iwp), DIMENSION(fl_max)            ::  id_dim_x_fl, id_dim_y_fl, id_dim_z_fl
    329291    INTEGER(iwp), DIMENSION(fl_max*var_fl_max) :: id_var_dofl
     292    INTEGER(iwp), DIMENSION(fl_max)            ::  id_var_x_fl, id_var_y_fl, id_var_z_fl
     293
     294    INTEGER(iwp), DIMENSION(0:1) ::  id_dim_time_xy, id_dim_time_xz, id_dim_time_yz,               &
     295                                     id_dim_time_3d, id_dim_x_xy, id_dim_xu_xy, id_dim_x_xz,       &
     296                                     id_dim_xu_xz, id_dim_x_yz, id_dim_xu_yz, id_dim_x_3d,         &
     297                                     id_dim_xu_3d, id_dim_y_xy, id_dim_yv_xy, id_dim_y_xz,         &
     298                                     id_dim_yv_xz, id_dim_y_yz, id_dim_yv_yz, id_dim_y_3d,         &
     299                                     id_dim_yv_3d, id_dim_zs_xy, id_dim_zs_xz, id_dim_zs_yz,       &
     300                                     id_dim_zs_3d, id_dim_zpc_3d, id_dim_zu_xy, id_dim_zu1_xy,     &
     301                                     id_dim_zu_xz, id_dim_zu_yz, id_dim_zu_3d, id_dim_zw_xy,       &
     302                                     id_dim_zw_xz, id_dim_zw_yz, id_dim_zw_3d,                     &
     303                                     id_set_xy, id_set_xz, id_set_yz, id_set_3d,                   &
     304                                     id_var_ind_x_yz, id_var_ind_y_xz, id_var_ind_z_xy,            &
     305                                     id_var_time_xy, id_var_time_xz, id_var_time_yz,               &
     306                                     id_var_time_3d, id_var_x_xy, id_var_xu_xy, id_var_x_xz,       &
     307                                     id_var_xu_xz, id_var_x_yz, id_var_xu_yz, id_var_x_3d,         &
     308                                     id_var_xu_3d, id_var_y_xy, id_var_yv_xy, id_var_y_xz,         &
     309                                     id_var_yv_xz, id_var_y_yz, id_var_yv_yz, id_var_y_3d,         &
     310                                     id_var_yv_3d, id_var_zs_xy, id_var_zs_xz, id_var_zs_yz,       &
     311                                     id_var_zs_3d, id_var_zpc_3d, id_var_zusi_xy, id_var_zusi_3d,  &
     312                                     id_var_zu_xy, id_var_zu1_xy, id_var_zu_xz, id_var_zu_yz,      &
     313                                     id_var_zu_3d, id_var_zwwi_xy, id_var_zwwi_3d, id_var_zw_xy,   &
     314                                     id_var_zw_xz, id_var_zw_yz, id_var_zw_3d
     315
     316    INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_eutm_3d, id_var_eutm_xy, id_var_eutm_xz,           &
     317                                         id_var_eutm_yz,                                           &
     318                                         id_var_nutm_3d, id_var_nutm_xy, id_var_nutm_xz,           &
     319                                         id_var_nutm_yz
     320
     321    INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_lat_3d, id_var_lat_xy, id_var_lat_xz,              &
     322                                         id_var_lat_yz,                                            &
     323                                         id_var_lon_3d, id_var_lon_xy, id_var_lon_xz, id_var_lon_yz
     324
    330325
    331326    INTEGER(iwp), DIMENSION(dopts_num,0:10) ::  id_var_dopts
    332327    INTEGER(iwp), DIMENSION(0:1,500)        ::  id_var_do2d, id_var_do3d
    333     INTEGER(iwp), DIMENSION(100,0:99)       ::  id_dim_z_pr, id_var_dopr, &
    334                                                 id_var_z_pr
     328    INTEGER(iwp), DIMENSION(100,0:99)       ::  id_dim_z_pr, id_var_dopr, id_var_z_pr
    335329    INTEGER(iwp), DIMENSION(dots_max,0:99)  ::  id_var_dots
    336330
     
    339333    CHARACTER (LEN=7), DIMENSION(max_masks,0:1,100) ::  domask_unit
    340334
     335    INTEGER(iwp), DIMENSION(1:max_masks,0:1) ::  id_dim_time_mask, id_dim_x_mask, id_dim_xu_mask,  &
     336                                                 id_dim_y_mask, id_dim_yv_mask, id_dim_zs_mask,    &
     337                                                 id_dim_zu_mask, id_dim_zw_mask,                   &
     338                                                 id_set_mask,                                      &
     339                                                 id_var_time_mask, id_var_x_mask, id_var_xu_mask,  &
     340                                                 id_var_y_mask, id_var_yv_mask, id_var_zs_mask,    &
     341                                                 id_var_zu_mask, id_var_zw_mask,                   &
     342                                                 id_var_zusi_mask, id_var_zwwi_mask
     343
     344
     345    INTEGER(iwp), DIMENSION(1:max_masks,0:1,100) ::  id_var_domask
     346    INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_eutm_mask, id_var_nutm_mask
     347    INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_lat_mask, id_var_lon_mask
     348
     349
    341350    LOGICAL ::  output_for_t0 = .FALSE.
    342351
    343     INTEGER(iwp), DIMENSION(1:max_masks,0:1) ::  id_dim_time_mask, id_dim_x_mask, &
    344                    id_dim_xu_mask, id_dim_y_mask, id_dim_yv_mask, id_dim_zs_mask, &
    345                    id_dim_zu_mask, id_dim_zw_mask, &
    346                    id_set_mask, &
    347                    id_var_time_mask, id_var_x_mask, id_var_xu_mask, &
    348                    id_var_y_mask, id_var_yv_mask, id_var_zs_mask, &
    349                    id_var_zu_mask, id_var_zw_mask, &
    350                    id_var_zusi_mask, id_var_zwwi_mask
    351 
    352     INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_eutm_mask, &
    353                                                      id_var_nutm_mask
    354 
    355     INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_lat_mask, &
    356                                                      id_var_lon_mask
    357 
    358     INTEGER(iwp), DIMENSION(1:max_masks,0:1,100) ::  id_var_domask
    359 
    360352    REAL(wp) ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
    361353
    362354
    363     PUBLIC  dofl_dim_label_x, dofl_dim_label_y, dofl_dim_label_z, dofl_label,  &
    364             dofl_time_count, dofl_unit, domask_unit, dopr_unit, dopts_num,     &
    365             dots_label, dots_max, dots_num, dots_rad, dots_soil, dots_unit,    &
    366             do2d_unit, do3d_unit, fill_value, id_set_agt, id_set_fl,           &
    367             id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp,         &
    368             id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d, id_var_agt, &
    369             id_var_domask, id_var_dofl, id_var_dopr, id_var_dopts,             &
    370             id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d, id_var_do3d, &
    371             id_var_norm_dopr, id_var_time_agt, id_var_time_fl,                 &
    372             id_var_time_mask, id_var_time_pr, id_var_rnoa_agt, id_var_time_pts,&
    373             id_var_time_sp, id_var_time_ts,                                    &
    374             id_var_time_xy, id_var_time_xz, id_var_time_yz, id_var_time_3d,    &
    375             id_var_x_fl, id_var_y_fl, id_var_z_fl,  nc_stat,                   &
    376             netcdf_data_format, netcdf_data_format_string, netcdf_deflate,     &
    377             netcdf_precision, output_for_t0, heatflux_output_unit,             &
    378             waterflux_output_unit, momentumflux_output_unit
     355    PUBLIC  dofl_dim_label_x, dofl_dim_label_y, dofl_dim_label_z, dofl_label, dofl_time_count,     &
     356            dofl_unit, domask_unit, dopr_unit, dopts_num, dots_label, dots_max, dots_num, dots_rad,&
     357            dots_soil, dots_unit, do2d_unit, do3d_unit, fill_value, id_set_agt, id_set_fl,         &
     358            id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_set_xy,       &
     359            id_set_xz, id_set_yz, id_set_3d, id_var_agt, id_var_domask, id_var_dofl, id_var_dopr,  &
     360            id_var_dopts, id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d, id_var_do3d,       &
     361            id_var_norm_dopr, id_var_time_agt, id_var_time_fl, id_var_time_mask, id_var_time_pr,   &
     362            id_var_rnoa_agt, id_var_time_pts, id_var_time_sp, id_var_time_ts, id_var_time_xy,      &
     363            id_var_time_xz, id_var_time_yz, id_var_time_3d, id_var_x_fl, id_var_y_fl, id_var_z_fl, &
     364            nc_stat, netcdf_data_format, netcdf_data_format_string, netcdf_deflate,                &
     365            netcdf_precision, output_for_t0, heatflux_output_unit, waterflux_output_unit,          &
     366            momentumflux_output_unit
    379367
    380368    SAVE
     
    412400    END INTERFACE netcdf_open_write_file
    413401
    414     PUBLIC netcdf_create_att, netcdf_create_dim, netcdf_create_file,           &
    415            netcdf_create_global_atts, netcdf_create_var, netcdf_define_header, &
    416            netcdf_handle_error, netcdf_open_write_file
     402    PUBLIC netcdf_create_att, netcdf_create_dim, netcdf_create_file, netcdf_create_global_atts,    &
     403           netcdf_create_var, netcdf_define_header, netcdf_handle_error, netcdf_open_write_file
    417404
    418405 CONTAINS
     
    422409#if defined( __netcdf )
    423410
    424     USE arrays_3d,                                                             &
     411    USE arrays_3d,                                                                                 &
    425412        ONLY:  zu, zw
    426413
    427     USE biometeorology_mod,                                                    &
     414    USE biometeorology_mod,                                                                        &
    428415        ONLY:  bio_define_netcdf_grid
    429416
    430     USE chemistry_model_mod,                                                   &
     417    USE chemistry_model_mod,                                                                       &
    431418        ONLY:  chem_define_netcdf_grid
    432419
    433     USE basic_constants_and_equations_mod,                                     &
    434         ONLY:  convert_utm_to_geographic,                                      &
     420    USE basic_constants_and_equations_mod,                                                         &
     421        ONLY:  convert_utm_to_geographic,                                                          &
    435422               pi
    436423
    437     USE control_parameters,                                                    &
    438         ONLY:  agent_time_unlimited, air_chemistry, averaging_interval,        &
    439                averaging_interval_pr, data_output_pr, domask, dopr_n,          &
    440                dopr_time_count, dopts_time_count, dots_time_count,             &
    441                do2d, do2d_at_begin, do2d_xz_time_count, do3d, do3d_at_begin,   &
    442                do2d_yz_time_count, dt_data_output_av, dt_do2d_xy, dt_do2d_xz,  &
    443                dt_do2d_yz, dt_do3d, dt_write_agent_data, mask_size,            &
    444                do2d_xy_time_count, do3d_time_count, domask_time_count,         &
    445                end_time, indoor_model, land_surface,                           &
    446                mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global,      &
    447                mask_k_global, mask_surface,                                    &
    448                message_string, ntdim_2d_xy, ntdim_2d_xz,                       &
    449                ntdim_2d_yz, ntdim_3d, nz_do3d, ocean_mode, plant_canopy,       &
    450                run_description_header, salsa, section, simulated_time,         &
    451                simulated_time_at_begin, skip_time_data_output_av,              &
    452                skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
    453                skip_time_do3d, topography, num_leg, num_var_fl,                &
    454                urban_surface
    455 
    456     USE diagnostic_output_quantities_mod,                                      &
     424    USE control_parameters,                                                                        &
     425        ONLY:  agent_time_unlimited, air_chemistry, averaging_interval, averaging_interval_pr,     &
     426               data_output_pr, domask, dopr_n, dopr_time_count, dopts_time_count, dots_time_count, &
     427               do2d, do2d_at_begin, do2d_xz_time_count, do3d, do3d_at_begin, do2d_yz_time_count,   &
     428               dt_data_output_av, dt_do2d_xy, dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_write_agent_data,&
     429               mask_size, do2d_xy_time_count, do3d_time_count, domask_time_count, end_time,        &
     430               indoor_model, land_surface, mask_size_l, mask_i, mask_i_global, mask_j,             &
     431               mask_j_global, mask_k_global, mask_surface, message_string, ntdim_2d_xy,            &
     432               ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, ocean_mode, plant_canopy,              &
     433               run_description_header, salsa, section, simulated_time, simulated_time_at_begin,    &
     434               skip_time_data_output_av, skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,  &
     435               skip_time_do3d, topography, num_leg, num_var_fl, urban_surface
     436
     437    USE diagnostic_output_quantities_mod,                                                          &
    457438        ONLY:  doq_define_netcdf_grid
    458439
    459     USE grid_variables,                                                        &
     440    USE grid_variables,                                                                            &
    460441        ONLY:  dx, dy, zu_s_inner, zw_w_inner
    461442
    462     USE gust_mod,                                                              &
     443    USE gust_mod,                                                                                  &
    463444        ONLY: gust_define_netcdf_grid, gust_module_enabled
    464445
    465     USE indices,                                                               &
     446    USE indices,                                                                                   &
    466447        ONLY:  nx, nxl, nxr, ny, nys, nyn, nz ,nzb, nzt
    467448
    468449    USE kinds
    469450
    470     USE indoor_model_mod,                                                      &
     451    USE indoor_model_mod,                                                                          &
    471452        ONLY: im_define_netcdf_grid
    472453
    473     USE land_surface_model_mod,                                                &
     454    USE land_surface_model_mod,                                                                    &
    474455        ONLY: lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
    475456
    476     USE ocean_mod,                                                             &
     457    USE ocean_mod,                                                                                 &
    477458        ONLY:  ocean_define_netcdf_grid
    478459
    479460    USE pegrid
    480461
    481     USE particle_attributes,                                                   &
     462    USE particle_attributes,                                                                       &
    482463        ONLY:  number_of_particle_groups
    483464
    484     USE plant_canopy_model_mod,                                                &
     465    USE plant_canopy_model_mod,                                                                    &
    485466        ONLY:  pch_index, pcm_define_netcdf_grid
    486467
    487     USE profil_parameter,                                                      &
     468    USE profil_parameter,                                                                          &
    488469        ONLY:  crmax, cross_profiles, dopr_index, profile_columns, profile_rows
    489470
    490     USE radiation_model_mod,                                                   &
     471    USE radiation_model_mod,                                                                       &
    491472        ONLY: radiation, radiation_define_netcdf_grid
    492473
    493     USE salsa_mod,                                                             &
     474    USE salsa_mod,                                                                                 &
    494475        ONLY:  salsa_define_netcdf_grid
    495476
    496     USE spectra_mod,                                                           &
    497         ONLY:  averaging_interval_sp, comp_spectra_level, data_output_sp, dosp_time_count, spectra_direction
    498 
    499     USE statistics,                                                            &
     477    USE spectra_mod,                                                                               &
     478        ONLY:  averaging_interval_sp, comp_spectra_level, data_output_sp, dosp_time_count,         &
     479               spectra_direction
     480
     481    USE statistics,                                                                                &
    500482        ONLY:  hom, statistic_regions
    501483
    502     USE turbulence_closure_mod,                                                &
     484    USE turbulence_closure_mod,                                                                    &
    503485        ONLY:  tcm_define_netcdf_grid
    504486
    505     USE urban_surface_mod,                                                     &
     487    USE urban_surface_mod,                                                                         &
    506488        ONLY:  usm_define_netcdf_grid
    507489
    508     USE user,                                                                  &
     490    USE user,                                                                                      &
    509491        ONLY:  user_module_enabled, user_define_netcdf_grid
    510492
     
    513495    IMPLICIT NONE
    514496
    515     CHARACTER (LEN=3)              ::  suffix                !<
    516497    CHARACTER (LEN=2), INTENT (IN) ::  callmode              !<
     498    CHARACTER (LEN=4000)           ::  char_cross_profiles   !<
    517499    CHARACTER (LEN=4)              ::  grid_x                !<
    518500    CHARACTER (LEN=4)              ::  grid_y                !<
    519501    CHARACTER (LEN=4)              ::  grid_z                !<
    520502    CHARACTER (LEN=6)              ::  mode                  !<
     503    CHARACTER (LEN=20)             ::  netcdf_var_name       !<
    521504    CHARACTER (LEN=10)             ::  precision             !<
     505    CHARACTER (LEN=3)              ::  suffix                !<
     506    CHARACTER (LEN=80)             ::  time_average_text     !<
     507    CHARACTER (LEN=varnamelength)  ::  trimvar               !< TRIM of output-variable string
    522508    CHARACTER (LEN=10)             ::  var                   !<
    523     CHARACTER (LEN=20)             ::  netcdf_var_name       !<
    524     CHARACTER (LEN=varnamelength)  ::  trimvar               !< TRIM of output-variable string
    525     CHARACTER (LEN=80)             ::  time_average_text     !<
    526     CHARACTER (LEN=4000)           ::  char_cross_profiles   !<
    527509    CHARACTER (LEN=4000)           ::  var_list              !<
    528510    CHARACTER (LEN=4000)           ::  var_list_old          !<
     
    545527    INTEGER(iwp) ::  k                                       !<
    546528    INTEGER(iwp) ::  kk                                      !<
     529    INTEGER(iwp) ::  l                                       !<
    547530    INTEGER(iwp) ::  mid                                     !< masked output running index
    548531    INTEGER(iwp) ::  ns                                      !<
     
    551534    INTEGER(iwp) ::  ntime_count                             !< number of time levels found in file
    552535    INTEGER(iwp) ::  nz_old                                  !<
    553     INTEGER(iwp) ::  l                                       !<
    554536
    555537    INTEGER(iwp), SAVE ::  oldmode                           !<
     
    566548    INTEGER(iwp), DIMENSION(1:crmax) ::  cross_profiles_numb !<
    567549
    568     LOGICAL ::  found                                        !<
    569 
    570550    LOGICAL, INTENT (INOUT) ::  extend                       !<
     551    LOGICAL                 ::  found                        !<
    571552
    572553    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !<
     
    591572    IF ( .NOT. init_netcdf )  THEN
    592573!
    593 !--    Check and set accuracy for netCDF output. First set default value
     574!--    Check and set accuracy for netCDF output. First set default value.
    594575       nc_precision = NF90_REAL4
    595576
     
    598579          j = INDEX( netcdf_precision(i), '_' )
    599580          IF ( j == 0 )  THEN
    600              WRITE ( message_string, * ) 'netcdf_precision must contain a ', &
    601                                          '"_"netcdf_precision(', i, ')="',   &
     581             WRITE ( message_string, * ) 'netcdf_precision must contain a ',                       &
     582                                         '"_"netcdf_precision(', i, ')="',                         &
    602583                                         TRIM( netcdf_precision(i) ),'"'
    603584             CALL message( 'netcdf_define_header', 'PA0241', 2, 2, 0, 6, 0 )
     
    612593             j = NF90_REAL8
    613594          ELSE
    614              WRITE ( message_string, * ) 'illegal netcdf precision: ',  &
    615                                          'netcdf_precision(', i, ')="', &
     595             WRITE ( message_string, * ) 'illegal netcdf precision: ',                             &
     596                                         'netcdf_precision(', i, ')="',                            &
    616597                                         TRIM( netcdf_precision(i) ),'"'
    617598             CALL message( 'netcdf_define_header', 'PA0242', 1, 2, 0, 6, 0 )
     
    645626
    646627             CASE DEFAULT
    647                 WRITE ( message_string, * ) 'unknown variable in ' //          &
    648                                   'initialization_parameters ',                &
    649                                   'assignment: netcdf_precision(', i, ')="',   &
     628                WRITE ( message_string, * ) 'unknown variable in ' // 'initialization_parameters ',&
     629                                            'assignment: netcdf_precision(', i, ')="',             &
    650630                                            TRIM( netcdf_precision(i) ),'"'
    651631                CALL message( 'netcdf_define_header', 'PA0243', 1, 2, 0, 6, 0 )
     
    660640!--    Check for allowed parameter range
    661641       IF ( netcdf_deflate < 0  .OR.  netcdf_deflate > 9 )  THEN
    662           WRITE ( message_string, '(A,I3,A)' ) 'netcdf_deflate out of ' //     &
    663                                       'range & given value: ', netcdf_deflate, &
    664                                       ', allowed range: 0-9'
     642          WRITE ( message_string, '(A,I3,A)' ) 'netcdf_deflate out of ' // 'range & given value: ',&
     643                                               netcdf_deflate, ', allowed range: 0-9'
    665644          CALL message( 'netcdf_define_header', 'PA0355', 2, 2, 0, 6, 0 )
    666645       ENDIF
     
    687666
    688667!
    689 !-- Select the mode to be processed. Possibilities are 3d, ma (mask), xy, xz,
    690 !-- yz, pr (profiles), ps (particle timeseries), fl (flight data), ts
    691 !-- (timeseries) or sp (spectra)
     668!-- Select the mode to be processed. Possibilities are 3d, ma (mask), xy, xz, yz, pr (profiles), ps
     669!-- (particle timeseries), fl (flight data), ts (timeseries) or sp (spectra).
    692670    SELECT CASE ( mode )
    693671
     
    695673
    696674!
    697 !--       decompose actual parameter file_id (=formal parameter av) into
    698 !--       mid and av
     675!--       Decompose actual parameter file_id (=formal parameter av) into mid and av
    699676          file_id = av
    700677          IF ( file_id <= 200+max_masks )  THEN
     
    709686!--       Define some global attributes of the dataset
    710687          IF ( av == 0 )  THEN
    711              CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked', TRIM( run_description_header ), 464 )
     688             CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked',                    &
     689                                             TRIM( run_description_header ), 464 )
    712690             time_average_text = ' '
    713691          ELSE
    714              CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked', TRIM( run_description_header ), 464 )
     692             CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked',                    &
     693                                             TRIM( run_description_header ), 464 )
    715694             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    716              nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'time_avg',   &
     695             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'time_avg',                 &
    717696                                     TRIM( time_average_text ) )
    718697             CALL netcdf_handle_error( 'netcdf_define_header', 466 )
     
    721700!
    722701!--       Define time coordinate for volume data (unlimited dimension)
    723           CALL netcdf_create_dim( id_set_mask(mid,av), 'time', NF90_UNLIMITED, &
     702          CALL netcdf_create_dim( id_set_mask(mid,av), 'time', NF90_UNLIMITED,                     &
    724703                                  id_dim_time_mask(mid,av), 467 )
    725           CALL netcdf_create_var( id_set_mask(mid,av),                         &
    726                                   (/ id_dim_time_mask(mid,av) /), 'time',      &
    727                                   NF90_DOUBLE, id_var_time_mask(mid,av),       &
     704          CALL netcdf_create_var( id_set_mask(mid,av),                                             &
     705                                  (/ id_dim_time_mask(mid,av) /), 'time',                          &
     706                                  NF90_DOUBLE, id_var_time_mask(mid,av),                           &
    728707                                 'seconds', 'time', 468, 469, 000 )
    729           CALL netcdf_create_att( id_set_mask(mid,av), id_var_time_mask(mid,av), 'standard_name', 'time', 000)
     708          CALL netcdf_create_att( id_set_mask(mid,av), id_var_time_mask(mid,av),                   &
     709                                  'standard_name', 'time', 000)
    730710          CALL netcdf_create_att( id_set_mask(mid,av), id_var_time_mask(mid,av), 'axis', 'T', 000)
    731711
     
    734714          IF ( mask_surface(mid) )  THEN
    735715!
    736 !--          In case of terrain-following output, the vertical dimensions are
    737 !--          indices, not meters
    738              CALL netcdf_create_dim( id_set_mask(mid,av), 'ku_above_surf',     &
    739                                      mask_size(mid,3), id_dim_zu_mask(mid,av), &
     716!--          In case of terrain-following output, the vertical dimensions are indices, not meters.
     717             CALL netcdf_create_dim( id_set_mask(mid,av), 'ku_above_surf',                         &
     718                                     mask_size(mid,3), id_dim_zu_mask(mid,av),                     &
    740719                                     470 )
    741              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    742                                      (/ id_dim_zu_mask(mid,av) /),             &
    743                                      'ku_above_surf',                          &
    744                                      NF90_DOUBLE, id_var_zu_mask(mid,av),      &
    745                                      '1', 'grid point above terrain',          &
     720             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     721                                     (/ id_dim_zu_mask(mid,av) /),                                 &
     722                                     'ku_above_surf',                                              &
     723                                     NF90_DOUBLE, id_var_zu_mask(mid,av),                          &
     724                                     '1', 'grid point above terrain',                              &
    746725                                     471, 472, 000 )
    747              CALL netcdf_create_att( id_set_mask(mid,av),                      &
    748                                      id_var_zu_mask(mid,av), 'axis', 'Z', 000)
    749                                      
    750              CALL netcdf_create_dim( id_set_mask(mid,av), 'kw_above_surf',     &
    751                                      mask_size(mid,3), id_dim_zw_mask(mid,av), &
     726             CALL netcdf_create_att( id_set_mask(mid,av), id_var_zu_mask(mid,av), 'axis', 'Z', 000)
     727
     728             CALL netcdf_create_dim( id_set_mask(mid,av), 'kw_above_surf',                         &
     729                                     mask_size(mid,3), id_dim_zw_mask(mid,av),                     &
    752730                                     473 )
    753              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    754                                      (/ id_dim_zw_mask(mid,av) /),             &
    755                                      'kw_above_surf',                          &
    756                                      NF90_DOUBLE, id_var_zw_mask(mid,av),      &
    757                                     '1', 'grid point above terrain',           &
     731             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     732                                     (/ id_dim_zw_mask(mid,av) /),                                 &
     733                                     'kw_above_surf',                                              &
     734                                     NF90_DOUBLE, id_var_zw_mask(mid,av),                          &
     735                                    '1', 'grid point above terrain',                               &
    758736                                    474, 475, 000 )
    759              CALL netcdf_create_att( id_set_mask(mid,av),                      &
    760                                      id_var_zw_mask(mid,av), 'axis', 'Z', 000)
     737             CALL netcdf_create_att( id_set_mask(mid,av),id_var_zw_mask(mid,av), 'axis', 'Z', 000)
    761738          ELSE
    762739!
    763740!--          Define vertical coordinate grid (zu grid)
    764              CALL netcdf_create_dim( id_set_mask(mid,av), 'zu_3d',             &
    765                                      mask_size(mid,3), id_dim_zu_mask(mid,av), &
     741             CALL netcdf_create_dim( id_set_mask(mid,av), 'zu_3d',                                 &
     742                                     mask_size(mid,3), id_dim_zu_mask(mid,av),                     &
    766743                                     470 )
    767              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    768                                      (/ id_dim_zu_mask(mid,av) /), 'zu_3d',    &
    769                                      NF90_DOUBLE, id_var_zu_mask(mid,av),      &
     744             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     745                                     (/ id_dim_zu_mask(mid,av) /), 'zu_3d',                        &
     746                                     NF90_DOUBLE, id_var_zu_mask(mid,av),                          &
    770747                                     'meters', '', 471, 472, 000 )
    771              CALL netcdf_create_att( id_set_mask(mid,av),                      &
    772                                      id_var_zu_mask(mid,av), 'axis', 'Z', 000)
     748             CALL netcdf_create_att( id_set_mask(mid,av), id_var_zu_mask(mid,av), 'axis', 'Z', 000)
    773749!
    774750!--          Define vertical coordinate grid (zw grid)
    775              CALL netcdf_create_dim( id_set_mask(mid,av), 'zw_3d',             &
    776                                      mask_size(mid,3), id_dim_zw_mask(mid,av), &
     751             CALL netcdf_create_dim( id_set_mask(mid,av), 'zw_3d',                                 &
     752                                     mask_size(mid,3), id_dim_zw_mask(mid,av),                     &
    777753                                     473 )
    778              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    779                                      (/ id_dim_zw_mask(mid,av) /), 'zw_3d',    &
    780                                      NF90_DOUBLE, id_var_zw_mask(mid,av),      &
     754             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     755                                     (/ id_dim_zw_mask(mid,av) /), 'zw_3d',                        &
     756                                     NF90_DOUBLE, id_var_zw_mask(mid,av),                          &
    781757                                    'meters', '', 474, 475, 000 )
    782              CALL netcdf_create_att( id_set_mask(mid,av),                      &
    783                                      id_var_zw_mask(mid,av), 'axis', 'Z', 000)
     758             CALL netcdf_create_att( id_set_mask(mid,av), id_var_zw_mask(mid,av), 'axis', 'Z', 000)
    784759          ENDIF
    785760!
    786761!--       Define x-axis (for scalar position)
    787           CALL netcdf_create_dim( id_set_mask(mid,av), 'x', mask_size(mid,1),  &
     762          CALL netcdf_create_dim( id_set_mask(mid,av), 'x', mask_size(mid,1),                      &
    788763                                  id_dim_x_mask(mid,av), 476 )
    789           CALL netcdf_create_var( id_set_mask(mid,av),                         &
    790                                   (/ id_dim_x_mask(mid,av) /), 'x',            &
    791                                   NF90_DOUBLE, id_var_x_mask(mid,av),          &
     764          CALL netcdf_create_var( id_set_mask(mid,av),                                             &
     765                                  (/ id_dim_x_mask(mid,av) /), 'x',                                &
     766                                  NF90_DOUBLE, id_var_x_mask(mid,av),                              &
    792767                                  'meters', '', 477, 478, 000 )
    793           CALL netcdf_create_att( id_set_mask(mid,av), id_var_x_mask(mid,av),  &
    794                                   'axis', 'X', 000)
     768          CALL netcdf_create_att( id_set_mask(mid,av), id_var_x_mask(mid,av), 'axis', 'X', 000)
    795769!
    796770!--       Define x-axis (for u position)
    797           CALL netcdf_create_dim( id_set_mask(mid,av), 'xu', mask_size(mid,1), &
     771          CALL netcdf_create_dim( id_set_mask(mid,av), 'xu', mask_size(mid,1),                     &
    798772                                  id_dim_xu_mask(mid,av), 479 )
    799           CALL netcdf_create_var( id_set_mask(mid,av),                         &
    800                                   (/ id_dim_xu_mask(mid,av) /), 'xu',          &
    801                                   NF90_DOUBLE, id_var_xu_mask(mid,av),         &
     773          CALL netcdf_create_var( id_set_mask(mid,av),                                             &
     774                                  (/ id_dim_xu_mask(mid,av) /), 'xu',                              &
     775                                  NF90_DOUBLE, id_var_xu_mask(mid,av),                             &
    802776                                  'meters', '', 480, 481, 000 )
    803           CALL netcdf_create_att( id_set_mask(mid,av), id_var_xu_mask(mid,av), &
    804                                   'axis', 'X', 000)
     777          CALL netcdf_create_att( id_set_mask(mid,av), id_var_xu_mask(mid,av), 'axis', 'X', 000)
    805778!
    806779!--       Define y-axis (for scalar position)
    807           CALL netcdf_create_dim( id_set_mask(mid,av), 'y', mask_size(mid,2),  &
     780          CALL netcdf_create_dim( id_set_mask(mid,av), 'y', mask_size(mid,2),                      &
    808781                                  id_dim_y_mask(mid,av), 482 )
    809           CALL netcdf_create_var( id_set_mask(mid,av),                         &
    810                                   (/ id_dim_y_mask(mid,av) /), 'y',            &
    811                                   NF90_DOUBLE, id_var_y_mask(mid,av),          &
     782          CALL netcdf_create_var( id_set_mask(mid,av),                                             &
     783                                  (/ id_dim_y_mask(mid,av) /), 'y',                                &
     784                                  NF90_DOUBLE, id_var_y_mask(mid,av),                              &
    812785                                  'meters', '', 483, 484, 000 )
    813           CALL netcdf_create_att( id_set_mask(mid,av), id_var_y_mask(mid,av),  &
    814                                   'axis', 'Y', 000)
     786          CALL netcdf_create_att( id_set_mask(mid,av), id_var_y_mask(mid,av), 'axis', 'Y', 000)
    815787!
    816788!--       Define y-axis (for v position)
    817           CALL netcdf_create_dim( id_set_mask(mid,av), 'yv', mask_size(mid,2), &
     789          CALL netcdf_create_dim( id_set_mask(mid,av), 'yv', mask_size(mid,2),                     &
    818790                                  id_dim_yv_mask(mid,av), 485 )
    819           CALL netcdf_create_var( id_set_mask(mid,av),                         &
    820                                   (/ id_dim_yv_mask(mid,av) /),                &
    821                                   'yv', NF90_DOUBLE, id_var_yv_mask(mid,av),   &
     791          CALL netcdf_create_var( id_set_mask(mid,av),                                             &
     792                                  (/ id_dim_yv_mask(mid,av) /),                                    &
     793                                  'yv', NF90_DOUBLE, id_var_yv_mask(mid,av),                       &
    822794                                  'meters', '', 486, 487, 000 )
    823           CALL netcdf_create_att( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
    824                                   'axis', 'Y', 000)
     795          CALL netcdf_create_att( id_set_mask(mid,av), id_var_yv_mask(mid,av), 'axis', 'Y', 000)
    825796!
    826797!--       Define UTM and geographic coordinates
    827           CALL define_geo_coordinates( id_set_mask(mid,av),               &
    828                   (/ id_dim_x_mask(mid,av), id_dim_xu_mask(mid,av) /),    &
    829                   (/ id_dim_y_mask(mid,av), id_dim_yv_mask(mid,av) /),    &
    830                   id_var_eutm_mask(:,mid,av), id_var_nutm_mask(:,mid,av), &
    831                   id_var_lat_mask(:,mid,av), id_var_lon_mask(:,mid,av)    )
     798          CALL define_geo_coordinates( id_set_mask(mid,av),                                        &
     799                                       (/ id_dim_x_mask(mid,av), id_dim_xu_mask(mid,av) /),        &
     800                                       (/ id_dim_y_mask(mid,av), id_dim_yv_mask(mid,av) /),        &
     801                                       id_var_eutm_mask(:,mid,av), id_var_nutm_mask(:,mid,av),    &
     802                                       id_var_lat_mask(:,mid,av), id_var_lon_mask(:,mid,av)    )
    832803!
    833804!--       Define coordinate-reference system
    834805          CALL netcdf_create_crs( id_set_mask(mid,av), 000 )
    835806!
    836 !--       In case of non-flat topography define 2d-arrays containing the height
    837 !--       information. Only for parallel netcdf output.
    838           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    839                netcdf_data_format > 4 )  THEN
     807!--       In case of non-flat topography define 2d-arrays containing the height information. Only
     808!--       for parallel netcdf output.
     809          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4 )  THEN
    840810!
    841811!--          Define zusi = zu(nzb_s_inner)
    842              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    843                                      (/ id_dim_x_mask(mid,av),                 &
    844                                         id_dim_y_mask(mid,av) /), 'zusi',      &
    845                                      NF90_DOUBLE, id_var_zusi_mask(mid,av),    &
    846                                      'meters', 'zu(nzb_s_inner)', 488, 489,    &
    847                                      490 )
     812             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     813                                     (/ id_dim_x_mask(mid,av), id_dim_y_mask(mid,av) /), 'zusi',   &
     814                                     NF90_DOUBLE, id_var_zusi_mask(mid,av),                        &
     815                                     'meters', 'zu(nzb_s_inner)', 488, 489, 490 )
    848816!
    849817!--          Define zwwi = zw(nzb_w_inner)
    850              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    851                                      (/ id_dim_x_mask(mid,av),                 &
    852                                         id_dim_y_mask(mid,av) /), 'zwwi',      &
    853                                      NF90_DOUBLE, id_var_zwwi_mask(mid,av),    &
    854                                      'meters', 'zw(nzb_w_inner)', 491, 492,    &
    855                                      493 )
     818             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     819                                     (/ id_dim_x_mask(mid,av), id_dim_y_mask(mid,av) /), 'zwwi',   &
     820                                     NF90_DOUBLE, id_var_zwwi_mask(mid,av),                        &
     821                                     'meters', 'zw(nzb_w_inner)', 491, 492, 493 )
    856822          ENDIF
    857823
     
    859825!
    860826!--          Define vertical coordinate grid (zw grid)
    861              CALL netcdf_create_dim( id_set_mask(mid,av), 'zs_3d',             &
    862                                      mask_size(mid,3), id_dim_zs_mask(mid,av), &
     827             CALL netcdf_create_dim( id_set_mask(mid,av), 'zs_3d',                                 &
     828                                     mask_size(mid,3), id_dim_zs_mask(mid,av),                     &
    863829                                     536 )
    864              CALL netcdf_create_var( id_set_mask(mid,av),                      &
    865                                      (/ id_dim_zs_mask(mid,av) /), 'zs_3d',    &
    866                                      NF90_DOUBLE, id_var_zs_mask(mid,av),      &
     830             CALL netcdf_create_var( id_set_mask(mid,av),                                          &
     831                                     (/ id_dim_zs_mask(mid,av) /), 'zs_3d',                        &
     832                                     NF90_DOUBLE, id_var_zs_mask(mid,av),                          &
    867833                                     'meters', '', 537, 555, 000 )
    868              CALL netcdf_create_att( id_set_mask(mid,av),                      &
    869                                      id_var_zs_mask(mid,av), 'axis', 'Z', 000)
     834             CALL netcdf_create_att( id_set_mask(mid,av), id_var_zs_mask(mid,av), 'axis', 'Z', 000)
    870835          ENDIF
    871836
     
    875840          i = 1
    876841
    877           DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
     842          DO  WHILE ( domask(mid,av,i)(1:1) /= ' ' )
    878843
    879844             trimvar = TRIM( domask(mid,av,i) )
     
    884849!
    885850!--             Most variables are defined on the scalar grid
    886                 CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',                &
    887                        'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
     851                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',                                    &
     852                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',                       &
    888853                       's', 'theta', 'thetal', 'thetav', 'qi', 'ni', 'qg', 'ng', 'qs', 'ns' )
    889854
     
    923888                   ENDIF
    924889
    925                    IF ( .NOT. found )                                          &
     890                   IF ( .NOT. found )                                                              &
    926891                      CALL doq_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
    927892
     
    991956!
    992957!--          Define the grid
    993              CALL netcdf_create_var( id_set_mask(mid,av), (/ id_x, id_y, id_z, &
    994                                      id_dim_time_mask(mid,av) /),              &
    995                                      domask(mid,av,i), nc_precision(11),       &
    996                                      id_var_domask(mid,av,i),                  &
    997                                      TRIM( domask_unit(mid,av,i) ),            &
     958             CALL netcdf_create_var( id_set_mask(mid,av),                                         &
     959                                     (/ id_x, id_y, id_z, id_dim_time_mask(mid,av) /),             &
     960                                     domask(mid,av,i), nc_precision(11),                           &
     961                                     id_var_domask(mid,av,i),                                      &
     962                                     TRIM( domask_unit(mid,av,i) ),                                &
    998963                                     domask(mid,av,i), 494, 495, 496, .TRUE. )
    999964
     
    1009974
    1010975!
    1011 !--       Write the list of variables as global attribute (this is used by
    1012 !--       restart runs and by combine_plot_fields)
    1013           nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
    1014                                   'VAR_LIST', var_list )
     976!--       Write the list of variables as global attribute (this is used by restart runs and by
     977!--       combine_plot_fields).
     978          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST', var_list )
    1015979          CALL netcdf_handle_error( 'netcdf_define_header', 497 )
    1016980
     
    1026990          netcdf_data = ( mask_i_global(mid,:mask_size(mid,1)) + 0.5_wp ) * dx
    1027991
    1028           nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_x_mask(mid,av), &
    1029                                   netcdf_data, start = (/ 1 /),               &
     992          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_x_mask(mid,av),                      &
     993                                  netcdf_data, start = (/ 1 /),                                    &
    1030994                                  count = (/ mask_size(mid,1) /) )
    1031995          CALL netcdf_handle_error( 'netcdf_define_header', 499 )
     
    1033997          netcdf_data = mask_i_global(mid,:mask_size(mid,1)) * dx
    1034998
    1035           nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_xu_mask(mid,av),&
    1036                                   netcdf_data, start = (/ 1 /),               &
     999          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_xu_mask(mid,av),                     &
     1000                                  netcdf_data, start = (/ 1 /),                                    &
    10371001                                  count = (/ mask_size(mid,1) /) )
    10381002          CALL netcdf_handle_error( 'netcdf_define_header', 500 )
     
    10461010          netcdf_data = ( mask_j_global(mid,:mask_size(mid,2)) + 0.5_wp ) * dy
    10471011
    1048           nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_y_mask(mid,av), &
    1049                                   netcdf_data, start = (/ 1 /),               &
     1012          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_y_mask(mid,av),                      &
     1013                                  netcdf_data, start = (/ 1 /),                                    &
    10501014                                  count = (/ mask_size(mid,2) /))
    10511015          CALL netcdf_handle_error( 'netcdf_define_header', 501 )
     
    10531017          netcdf_data = mask_j_global(mid,:mask_size(mid,2)) * dy
    10541018
    1055           nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
    1056                                   netcdf_data, start = (/ 1 /),    &
     1019          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_yv_mask(mid,av),                     &
     1020                                  netcdf_data, start = (/ 1 /),                                    &
    10571021                                  count = (/ mask_size(mid,2) /))
    10581022          CALL netcdf_handle_error( 'netcdf_define_header', 502 )
     
    10841048                ENDIF
    10851049
    1086                 netcdf_data = init_model%origin_x + cos_rot_angle              &
    1087                        * ( mask_i_global(mid,:mask_size(mid,1)) + shift_x ) * dx
    1088 
    1089                 nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
    1090                                         id_var_eutm_mask(k,mid,av), &
    1091                                         netcdf_data, start = (/ 1 /), &
     1050                netcdf_data = init_model%origin_x + cos_rot_angle                                  &
     1051                                 * ( mask_i_global(mid,:mask_size(mid,1)) + shift_x ) * dx
     1052
     1053                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                       &
     1054                                        id_var_eutm_mask(k,mid,av),                                &
     1055                                        netcdf_data, start = (/ 1 /),                              &
    10921056                                        count = (/ mask_size(mid,1) /) )
    10931057                CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    11131077                ENDIF
    11141078
    1115                 netcdf_data = init_model%origin_y + cos_rot_angle              &
    1116                        * ( mask_j_global(mid,:mask_size(mid,2)) + shift_y ) * dy
    1117 
    1118                 nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
    1119                                         id_var_nutm_mask(k,mid,av), &
    1120                                         netcdf_data, start = (/ 1 /), &
     1079                netcdf_data = init_model%origin_y + cos_rot_angle                                  &
     1080                                 * ( mask_j_global(mid,:mask_size(mid,2)) + shift_y ) * dy
     1081
     1082                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                       &
     1083                                        id_var_nutm_mask(k,mid,av),                                &
     1084                                        netcdf_data, start = (/ 1 /),                              &
    11211085                                        count = (/ mask_size(mid,2) /) )
    11221086                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    11491113               DO  j = 1, mask_size(mid,2)
    11501114                  DO  i = 1, mask_size(mid,1)
    1151                      netcdf_data_2d(i,j) = init_model%origin_x                        &
    1152                            + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx &
    1153                            + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
     1115                     netcdf_data_2d(i,j) = init_model%origin_x                                     &
     1116                                         + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx &
     1117                                         + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
    11541118                  ENDDO
    11551119               ENDDO
    11561120
    1157                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
    1158                                        id_var_eutm_mask(k,mid,av), &
    1159                                        netcdf_data_2d, start = (/ 1, 1 /), &
    1160                                        count = (/ mask_size(mid,1), &
    1161                                                   mask_size(mid,2) /) )
     1121               nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                        &
     1122                                       id_var_eutm_mask(k,mid,av),                                 &
     1123                                       netcdf_data_2d, start = (/ 1, 1 /),                         &
     1124                                       count = (/ mask_size(mid,1), mask_size(mid,2) /) )
    11621125               CALL netcdf_handle_error( 'netcdf_define_header', 555 )
    11631126
    11641127               DO  j = 1, mask_size(mid,2)
    11651128                  DO  i = 1, mask_size(mid,1)
    1166                      netcdf_data_2d(i,j) = init_model%origin_y                        &
    1167                            - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx &
    1168                            + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
     1129                     netcdf_data_2d(i,j) = init_model%origin_y                                     &
     1130                                         - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx &
     1131                                         + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
    11691132                  ENDDO
    11701133               ENDDO
    11711134
    1172                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
    1173                                        id_var_nutm_mask(k,mid,av), &
    1174                                        netcdf_data_2d, start = (/ 1, 1 /), &
    1175                                        count = (/ mask_size(mid,1), &
    1176                                                   mask_size(mid,2) /) )
     1135               nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                        &
     1136                                       id_var_nutm_mask(k,mid,av),                                 &
     1137                                       netcdf_data_2d, start = (/ 1, 1 /),                         &
     1138                                       count = (/ mask_size(mid,1), mask_size(mid,2) /) )
    11771139               CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    11781140
     
    12041166             DO  j = 1, mask_size(mid,2)
    12051167                DO  i = 1, mask_size(mid,1)
    1206                    eutm = init_model%origin_x                                      &
    1207                         + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx  &
    1208                         + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
    1209                    nutm = init_model%origin_y                                      &
    1210                         - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx  &
    1211                         + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
    1212 
    1213                    CALL  convert_utm_to_geographic( crs_list,          &
    1214                                                     eutm, nutm,        &
    1215                                                     lon(i,j), lat(i,j) )
     1168                   eutm = init_model%origin_x                                                      &
     1169                          + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx                &
     1170                          + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
     1171                   nutm = init_model%origin_y                                                      &
     1172                          - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx                &
     1173                          + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy
     1174
     1175                   CALL  convert_utm_to_geographic( crs_list, eutm, nutm, lon(i,j), lat(i,j) )
    12161176                ENDDO
    12171177             ENDDO
    12181178
    1219              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),           &
    1220                                      id_var_lon_mask(k,mid,av),     &
    1221                                      lon, start = (/ 1, 1 /),       &
    1222                                      count = (/ mask_size(mid,1),   &
    1223                                                 mask_size(mid,2) /) )
     1179             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                          &
     1180                                     id_var_lon_mask(k,mid,av),                                    &
     1181                                     lon, start = (/ 1, 1 /),                                      &
     1182                                     count = (/ mask_size(mid,1), mask_size(mid,2) /) )
    12241183             CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    12251184
    1226              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),           &
    1227                                      id_var_lat_mask(k,mid,av),     &
    1228                                      lat, start = (/ 1, 1 /),       &
    1229                                      count = (/ mask_size(mid,1),   &
    1230                                                 mask_size(mid,2) /) )
     1185             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                          &
     1186                                     id_var_lat_mask(k,mid,av),                                    &
     1187                                     lat, start = (/ 1, 1 /),                                      &
     1188                                     count = (/ mask_size(mid,1), mask_size(mid,2) /) )
    12311189             CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    12321190          ENDDO
     
    12421200             netcdf_data = mask_k_global(mid,:mask_size(mid,3))
    12431201
    1244              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
    1245                                      netcdf_data, start = (/ 1 /), &
     1202             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av),                  &
     1203                                     netcdf_data, start = (/ 1 /),                                 &
    12461204                                     count = (/ mask_size(mid,3) /) )
    12471205             CALL netcdf_handle_error( 'netcdf_define_header', 503 )
     
    12491207             netcdf_data = mask_k_global(mid,:mask_size(mid,3))
    12501208
    1251              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
    1252                                      netcdf_data, start = (/ 1 /), &
     1209             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av),                  &
     1210                                     netcdf_data, start = (/ 1 /),                                 &
    12531211                                     count = (/ mask_size(mid,3) /) )
    12541212             CALL netcdf_handle_error( 'netcdf_define_header', 504 )
     
    12581216             netcdf_data = zu( mask_k_global(mid,:mask_size(mid,3)) )
    12591217
    1260              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
    1261                                      netcdf_data, start = (/ 1 /), &
     1218             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av),                  &
     1219                                     netcdf_data, start = (/ 1 /),                                 &
    12621220                                     count = (/ mask_size(mid,3) /) )
    12631221             CALL netcdf_handle_error( 'netcdf_define_header', 503 )
     
    12651223             netcdf_data = zw( mask_k_global(mid,:mask_size(mid,3)) )
    12661224
    1267              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
    1268                                      netcdf_data, start = (/ 1 /), &
     1225             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av),                  &
     1226                                     netcdf_data, start = (/ 1 /),                                 &
    12691227                                     count = (/ mask_size(mid,3) /) )
    12701228             CALL netcdf_handle_error( 'netcdf_define_header', 504 )
     
    12761234!
    12771235!--       In case of non-flat topography write height information
    1278           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    1279                netcdf_data_format > 4 )  THEN
     1236          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4 )  THEN
    12801237
    12811238             ALLOCATE( netcdf_data_2d(mask_size_l(mid,1),mask_size_l(mid,2)) )
    1282              netcdf_data_2d = zu_s_inner( mask_i(mid,:mask_size_l(mid,1)),     &
     1239             netcdf_data_2d = zu_s_inner( mask_i(mid,:mask_size_l(mid,1)),                         &
    12831240                                          mask_j(mid,:mask_size_l(mid,2)) )
    12841241
    1285              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
    1286                                      id_var_zusi_mask(mid,av),                 &
    1287                                      netcdf_data_2d,                           &
    1288                                      start = (/ 1, 1 /),                       &
    1289                                      count = (/ mask_size_l(mid,1),            &
    1290                                                 mask_size_l(mid,2) /) )
     1242             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                          &
     1243                                     id_var_zusi_mask(mid,av),                                     &
     1244                                     netcdf_data_2d,                                               &
     1245                                     start = (/ 1, 1 /),                                           &
     1246                                     count = (/ mask_size_l(mid,1), mask_size_l(mid,2) /) )
    12911247             CALL netcdf_handle_error( 'netcdf_define_header', 505 )
    12921248
    1293              netcdf_data_2d = zw_w_inner( mask_i(mid,:mask_size_l(mid,1)),     &
     1249             netcdf_data_2d = zw_w_inner( mask_i(mid,:mask_size_l(mid,1)),                         &
    12941250                                          mask_j(mid,:mask_size_l(mid,2)) )
    12951251
    1296              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
    1297                                      id_var_zwwi_mask(mid,av),                 &
    1298                                      netcdf_data_2d,                           &
    1299                                      start = (/ 1, 1 /),                       &
    1300                                      count = (/ mask_size_l(mid,1),            &
    1301                                                 mask_size_l(mid,2) /) )
     1252             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                                          &
     1253                                     id_var_zwwi_mask(mid,av),                                     &
     1254                                     netcdf_data_2d,                                               &
     1255                                     start = (/ 1, 1 /),                                           &
     1256                                     count = (/ mask_size_l(mid,1), mask_size_l(mid,2) /) )
    13021257             CALL netcdf_handle_error( 'netcdf_define_header', 506 )
    13031258
     
    13061261          ENDIF
    13071262!
    1308 !--       soil is not in masked output for now - disable temporary this block
     1263!--       Soil is not in masked output for now - disable temporary this block
    13091264!          IF ( land_surface )  THEN
    13101265!
     
    13251280
    13261281!
    1327 !--       restore original parameter file_id (=formal parameter av) into av
     1282!--       Restore original parameter file_id (=formal parameter av) into av
    13281283          av = file_id
    13291284
     
    13321287
    13331288!
    1334 !--       decompose actual parameter file_id (=formal parameter av) into
    1335 !--       mid and av
     1289!--       Decompose actual parameter file_id (=formal parameter av) into mid and av
    13361290          file_id = av
    13371291          IF ( file_id <= 200+max_masks )  THEN
     
    13451299!
    13461300!--       Get the list of variables and compare with the actual run.
    1347 !--       First var_list_old has to be reset, since GET_ATT does not assign
    1348 !--       trailing blanks.
     1301!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    13491302          var_list_old = ' '
    1350           nc_stat = NF90_GET_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST',&
    1351                                   var_list_old )
     1303          nc_stat = NF90_GET_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST', var_list_old )
    13521304          CALL netcdf_handle_error( 'netcdf_define_header', 507 )
    13531305
     
    13661318
    13671319          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    1368              WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),       &
    1369                   ' data for mask', mid, ' from previous run found,',           &
    1370                   '&but this file cannot be extended due to variable ',         &
    1371                   'mismatch.&New file is created instead.'
     1320             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),                          &
     1321                                         ' data for mask', mid, ' from previous run found,',       &
     1322                                         '&but this file cannot be extended due to variable ',     &
     1323                                         'mismatch.&New file is created instead.'
    13721324             CALL message( 'define_netcdf_header', 'PA0335', 0, 1, 0, 6, 0 )
    13731325             extend = .FALSE.
     
    13771329!
    13781330!--       Get and compare the number of vertical gridpoints
    1379           nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'zu_3d', &
    1380                                     id_var_zu_mask(mid,av) )
     1331          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'zu_3d', id_var_zu_mask(mid,av) )
    13811332          CALL netcdf_handle_error( 'netcdf_define_header', 508 )
    13821333
    1383           nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),     &
    1384                                            id_var_zu_mask(mid,av),  &
     1334          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),                                    &
     1335                                           id_var_zu_mask(mid,av),                                 &
    13851336                                           dimids = id_dim_zu_mask_old )
    13861337          CALL netcdf_handle_error( 'netcdf_define_header', 509 )
    13871338          id_dim_zu_mask(mid,av) = id_dim_zu_mask_old(1)
    13881339
    1389           nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),               &
    1390                                             id_dim_zu_mask(mid,av),            &
    1391                                             len = nz_old )
     1340          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),                                   &
     1341                                            id_dim_zu_mask(mid,av),                                &
     1342                                            LEN = nz_old )
    13921343          CALL netcdf_handle_error( 'netcdf_define_header', 510 )
    13931344
    13941345          IF ( mask_size(mid,3) /= nz_old )  THEN
    1395              WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),      &
    1396                   '&data for mask', mid, ' from previous run found,',          &
    1397                   ' but this file cannot be extended due to mismatch in ',     &
    1398                   ' number of vertical grid points.',                          &
    1399                   '&New file is created instead.'
     1346             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),                          &
     1347                                         '&data for mask', mid, ' from previous run found,',       &
     1348                                         ' but this file cannot be extended due to mismatch in ',  &
     1349                                         ' number of vertical grid points.',                       &
     1350                                         '&New file is created instead.'
    14001351             CALL message( 'define_netcdf_header', 'PA0336', 0, 1, 0, 6, 0 )
    14011352             extend = .FALSE.
     
    14041355
    14051356!
    1406 !--       Get the id of the time coordinate (unlimited coordinate) and its
    1407 !--       last index on the file. The next time level is plmask..count+1.
    1408 !--       The current time must be larger than the last output time
    1409 !--       on the file.
    1410           nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'time',               &
    1411                                     id_var_time_mask(mid,av) )
     1357!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     1358!--       The next time level is plmask..count+1.
     1359!--       The current time must be larger than the last output time on the file.
     1360          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'time', id_var_time_mask(mid,av) )
    14121361          CALL netcdf_handle_error( 'netcdf_define_header', 511 )
    14131362
    1414           nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),                &
    1415                                            id_var_time_mask(mid,av),           &
     1363          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),                                    &
     1364                                           id_var_time_mask(mid,av),                               &
    14161365                                           dimids = id_dim_time_old )
    14171366          CALL netcdf_handle_error( 'netcdf_define_header', 512 )
    14181367          id_dim_time_mask(mid,av) = id_dim_time_old(1)
    14191368
    1420           nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),               &
    1421                                             id_dim_time_mask(mid,av),          &
    1422                                             len = domask_time_count(mid,av) )
     1369          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),                                   &
     1370                                            id_dim_time_mask(mid,av),                              &
     1371                                            LEN = domask_time_count(mid,av) )
    14231372          CALL netcdf_handle_error( 'netcdf_define_header', 513 )
    14241373
    1425           nc_stat = NF90_GET_VAR( id_set_mask(mid,av),                         &
    1426                                   id_var_time_mask(mid,av),                    &
    1427                                   last_time_coordinate,                        &
    1428                                   start = (/ domask_time_count(mid,av) /),     &
     1374          nc_stat = NF90_GET_VAR( id_set_mask(mid,av),                                             &
     1375                                  id_var_time_mask(mid,av),                                        &
     1376                                  last_time_coordinate,                                            &
     1377                                  start = (/ domask_time_count(mid,av) /),                         &
    14291378                                  count = (/ 1 /) )
    14301379          CALL netcdf_handle_error( 'netcdf_define_header', 514 )
    14311380
    14321381          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    1433              WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),      &
    1434                   ' data for mask', mid, ' from previous run found,',          &
    1435                   '&but this file cannot be extended because the current ',    &
    1436                   'output time is less or equal than the last output time ',   &
    1437                   'on this file.&New file is created instead.'
     1382             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),                          &
     1383                                         ' data for mask', mid, ' from previous run found,',       &
     1384                                         '&but this file cannot be extended because the current ', &
     1385                                         'output time is less or equal than the last output time ',&
     1386                                         'on this file.&New file is created instead.'
    14381387             CALL message( 'define_netcdf_header', 'PA0337', 0, 1, 0, 6, 0 )
    14391388             domask_time_count(mid,av) = 0
     
    14471396          i = 1
    14481397          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
    1449              nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), &
    1450                                        TRIM( domask(mid,av,i) ), &
     1398             nc_stat = NF90_INQ_VARID( id_set_mask(mid,av),                                        &
     1399                                       TRIM( domask(mid,av,i) ),                                   &
    14511400                                       id_var_domask(mid,av,i) )
    14521401             CALL netcdf_handle_error( 'netcdf_define_header', 515 )
     
    14551404
    14561405!
    1457 !--       Update the title attribute on file
    1458 !--       In order to avoid 'data mode' errors if updated attributes are larger
    1459 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    1460 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    1461 !--       performance loss due to data copying; an alternative strategy would be
    1462 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     1406!--       Update the title attribute on file.
     1407!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     1408!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     1409!--       calls. This implies a possible performance loss due to data copying; an alternative
     1410!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    14631411          IF ( av == 0 )  THEN
    14641412             time_average_text = ' '
    14651413          ELSE
    1466              WRITE (time_average_text, '('', '',F7.1,'' s average'')')         &
    1467                                                             averaging_interval
     1414             WRITE (time_average_text, '('', '',F7.1,'' s average'')')  averaging_interval
    14681415          ENDIF
    14691416          nc_stat = NF90_REDEF( id_set_mask(mid,av) )
    14701417          CALL netcdf_handle_error( 'netcdf_define_header', 516 )
    1471           nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title',   &
    1472                                   TRIM( run_description_header ) //            &
    1473                                   TRIM( time_average_text ) )
     1418          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title',                       &
     1419                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    14741420          CALL netcdf_handle_error( 'netcdf_define_header', 517 )
    14751421          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
    14761422          CALL netcdf_handle_error( 'netcdf_define_header', 518 )
    1477           WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),         &
    1478                ' data for mask', mid, ' from previous run found.',             &
    1479                ' &This file will be extended.'
     1423          WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ), ' data for mask', mid,      &
     1424                                     ' from previous run found.', ' &This file will be extended.'
    14801425          CALL message( 'define_netcdf_header', 'PA0338', 0, 0, 0, 6, 0 )
    14811426!
    1482 !--       restore original parameter file_id (=formal parameter av) into av
     1427!--       Restore original parameter file_id (=formal parameter av) into av
    14831428          av = file_id
    14841429
     
    14891434!--       Define some global attributes of the dataset
    14901435          IF ( av == 0 )  THEN
    1491              CALL netcdf_create_global_atts( id_set_3d(av), '3d', TRIM( run_description_header ), 62 )
     1436             CALL netcdf_create_global_atts( id_set_3d(av), '3d',                                  &
     1437                                             TRIM( run_description_header ), 62 )
    14921438             time_average_text = ' '
    14931439          ELSE
    1494              CALL netcdf_create_global_atts( id_set_3d(av), '3d_av', TRIM( run_description_header ), 62 )
     1440             CALL netcdf_create_global_atts( id_set_3d(av), '3d_av',                               &
     1441                                             TRIM( run_description_header ), 62 )
    14951442             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    1496              nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'time_avg',   &
     1443             nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'time_avg',                       &
    14971444                                     TRIM( time_average_text ) )
    14981445             CALL netcdf_handle_error( 'netcdf_define_header', 63 )
     
    15011448!
    15021449!--       Define time coordinate for volume data.
    1503 !--       For parallel output the time dimensions has to be limited, otherwise
    1504 !--       the performance drops significantly.
     1450!--       For parallel output the time dimensions has to be limited, otherwise the performance drops
     1451!--       significantly.
    15051452          IF ( netcdf_data_format < 5 )  THEN
    1506              CALL netcdf_create_dim( id_set_3d(av), 'time', NF90_UNLIMITED,    &
    1507                                      id_dim_time_3d(av), 64 )
     1453             CALL netcdf_create_dim( id_set_3d(av), 'time', NF90_UNLIMITED, id_dim_time_3d(av), 64 )
    15081454          ELSE
    1509              CALL netcdf_create_dim( id_set_3d(av), 'time', ntdim_3d(av),      &
    1510                                      id_dim_time_3d(av), 523 )
    1511           ENDIF
    1512 
    1513           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_time_3d(av) /),     &
    1514                                   'time', NF90_DOUBLE, id_var_time_3d(av),     &
    1515                                   'seconds', 'time', 65, 66, 00 )
     1455             CALL netcdf_create_dim( id_set_3d(av), 'time', ntdim_3d(av), id_dim_time_3d(av), 523 )
     1456          ENDIF
     1457
     1458          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_time_3d(av) /), 'time', NF90_DOUBLE,    &
     1459                                  id_var_time_3d(av), 'seconds', 'time', 65, 66, 00 )
    15161460          CALL netcdf_create_att( id_set_3d(av), id_var_time_3d(av), 'standard_name', 'time', 000)
    15171461          CALL netcdf_create_att( id_set_3d(av), id_var_time_3d(av), 'axis', 'T', 000)
     
    15191463!--       Define spatial dimensions and coordinates:
    15201464!--       Define vertical coordinate grid (zu grid)
    1521           CALL netcdf_create_dim( id_set_3d(av), 'zu_3d', nz_do3d-nzb+1,       &
    1522                                   id_dim_zu_3d(av), 67 )
    1523           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zu_3d(av) /),       &
    1524                                   'zu_3d', NF90_DOUBLE, id_var_zu_3d(av),      &
    1525                                   'meters', '', 68, 69, 00 )
    1526           CALL netcdf_create_att( id_set_3d(av), id_var_zu_3d(av), 'axis',     &
    1527                                   'Z', 000)
     1465          CALL netcdf_create_dim( id_set_3d(av), 'zu_3d', nz_do3d-nzb+1, id_dim_zu_3d(av), 67 )
     1466          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zu_3d(av) /), 'zu_3d', NF90_DOUBLE,     &
     1467                                  id_var_zu_3d(av), 'meters', '', 68, 69, 00 )
     1468          CALL netcdf_create_att( id_set_3d(av), id_var_zu_3d(av), 'axis', 'Z', 000)
    15281469!
    15291470!--       Define vertical coordinate grid (zw grid)
    1530           CALL netcdf_create_dim( id_set_3d(av), 'zw_3d', nz_do3d-nzb+1,       &
    1531                                   id_dim_zw_3d(av), 70 )
    1532           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zw_3d(av) /),       &
    1533                                   'zw_3d', NF90_DOUBLE, id_var_zw_3d(av),      &
    1534                                   'meters', '', 71, 72, 00 )
    1535           CALL netcdf_create_att( id_set_3d(av), id_var_zw_3d(av), 'axis',     &
    1536                                   'Z', 000)
     1471          CALL netcdf_create_dim( id_set_3d(av), 'zw_3d', nz_do3d-nzb+1, id_dim_zw_3d(av), 70 )
     1472          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zw_3d(av) /), 'zw_3d', NF90_DOUBLE,     &
     1473                                  id_var_zw_3d(av), 'meters', '', 71, 72, 00 )
     1474          CALL netcdf_create_att( id_set_3d(av), id_var_zw_3d(av), 'axis', 'Z', 000)
    15371475!
    15381476!--       Define x-axis (for scalar position)
    1539           CALL netcdf_create_dim( id_set_3d(av), 'x', nx+1, id_dim_x_3d(av),   &
    1540                                   73 )
    1541           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av) /), 'x',   &
    1542                                   NF90_DOUBLE, id_var_x_3d(av), 'meters', '',  &
    1543                                   74, 75, 00 )
    1544           CALL netcdf_create_att( id_set_3d(av), id_var_x_3d(av), 'axis',     &
    1545                                   'X', 000)
     1477          CALL netcdf_create_dim( id_set_3d(av), 'x', nx+1, id_dim_x_3d(av), 73 )
     1478          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av) /), 'x', NF90_DOUBLE,          &
     1479                                  id_var_x_3d(av), 'meters', '', 74, 75, 00 )
     1480          CALL netcdf_create_att( id_set_3d(av), id_var_x_3d(av), 'axis', 'X', 000)
    15461481!
    15471482!--       Define x-axis (for u position)
    1548           CALL netcdf_create_dim( id_set_3d(av), 'xu', nx+1, id_dim_xu_3d(av), &
    1549                                   358 )
    1550           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_xu_3d(av) /), 'xu', &
    1551                                   NF90_DOUBLE, id_var_xu_3d(av), 'meters', '', &
    1552                                   359, 360, 000 )
    1553           CALL netcdf_create_att( id_set_3d(av), id_var_xu_3d(av), 'axis',     &
    1554                                   'X', 000)
     1483          CALL netcdf_create_dim( id_set_3d(av), 'xu', nx+1, id_dim_xu_3d(av), 358 )
     1484          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_xu_3d(av) /), 'xu', NF90_DOUBLE,        &
     1485                                  id_var_xu_3d(av), 'meters', '', 359, 360, 000 )
     1486          CALL netcdf_create_att( id_set_3d(av), id_var_xu_3d(av), 'axis', 'X', 000)
    15551487!
    15561488!--       Define y-axis (for scalar position)
    1557           CALL netcdf_create_dim( id_set_3d(av), 'y', ny+1, id_dim_y_3d(av),   &
    1558                                   76 )
    1559           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_y_3d(av) /), 'y',   &
    1560                                   NF90_DOUBLE, id_var_y_3d(av), 'meters', '',  &
    1561                                   77, 78, 00 )
    1562           CALL netcdf_create_att( id_set_3d(av), id_var_y_3d(av), 'axis',     &
    1563                                   'Y', 000)
     1489          CALL netcdf_create_dim( id_set_3d(av), 'y', ny+1, id_dim_y_3d(av), 76 )
     1490          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_y_3d(av) /), 'y', NF90_DOUBLE,          &
     1491                                  id_var_y_3d(av), 'meters', '', 77, 78, 00 )
     1492          CALL netcdf_create_att( id_set_3d(av), id_var_y_3d(av), 'axis', 'Y', 000)
    15641493!
    15651494!--       Define y-axis (for v position)
    1566           CALL netcdf_create_dim( id_set_3d(av), 'yv', ny+1, id_dim_yv_3d(av), &
    1567                                   361 )
    1568           CALL netcdf_create_var( id_set_3d(av), (/ id_dim_yv_3d(av) /), 'yv', &
    1569                                   NF90_DOUBLE, id_var_yv_3d(av), 'meters', '', &
    1570                                   362, 363, 000 )
    1571           CALL netcdf_create_att( id_set_3d(av), id_var_yv_3d(av), 'axis',     &
    1572                                   'Y', 000)
     1495          CALL netcdf_create_dim( id_set_3d(av), 'yv', ny+1, id_dim_yv_3d(av), 361 )
     1496          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_yv_3d(av) /), 'yv', NF90_DOUBLE,        &
     1497                                  id_var_yv_3d(av), 'meters', '', 362, 363, 000 )
     1498          CALL netcdf_create_att( id_set_3d(av), id_var_yv_3d(av), 'axis', 'Y', 000)
    15731499!
    15741500!--       Define UTM and geographic coordinates
    1575           CALL define_geo_coordinates( id_set_3d(av),         &
    1576                   (/ id_dim_x_3d(av), id_dim_xu_3d(av) /),    &
    1577                   (/ id_dim_y_3d(av), id_dim_yv_3d(av) /),    &
    1578                   id_var_eutm_3d(:,av), id_var_nutm_3d(:,av), &
    1579                   id_var_lat_3d(:,av), id_var_lon_3d(:,av)    )
     1501          CALL define_geo_coordinates( id_set_3d(av),                                              &
     1502                                       (/ id_dim_x_3d(av), id_dim_xu_3d(av) /),                    &
     1503                                       (/ id_dim_y_3d(av), id_dim_yv_3d(av) /),                    &
     1504                                       id_var_eutm_3d(:,av), id_var_nutm_3d(:,av),                &
     1505                                       id_var_lat_3d(:,av), id_var_lon_3d(:,av)    )
    15801506!
    15811507!--       Define coordinate-reference system
    15821508          CALL netcdf_create_crs( id_set_3d(av), 000 )
    15831509!
    1584 !--       In case of non-flat topography define 2d-arrays containing the height
    1585 !--       information. Only output 2d topography information in case of parallel
    1586 !--       output.
    1587           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    1588                netcdf_data_format > 4 )  THEN
     1510!--       In case of non-flat topography define 2d-arrays containing the height information. Only
     1511!--       output 2d topography information in case of parallel output.
     1512          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4 )  THEN
    15891513!
    15901514!--          Define zusi = zu(nzb_s_inner)
    1591              CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av),        &
    1592                                      id_dim_y_3d(av) /), 'zusi', NF90_DOUBLE,  &
    1593                                      id_var_zusi_3d(av), 'meters',             &
    1594                                      'zu(nzb_s_inner)', 413, 414, 415 )
     1515             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av), id_dim_y_3d(av) /), 'zusi',&
     1516                                     NF90_DOUBLE, id_var_zusi_3d(av), 'meters', 'zu(nzb_s_inner)', &
     1517                                     413, 414, 415 )
    15951518!
    15961519!--          Define zwwi = zw(nzb_w_inner)
    1597              CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av),        &
    1598                                      id_dim_y_3d(av) /), 'zwwi', NF90_DOUBLE,  &
    1599                                      id_var_zwwi_3d(av), 'meters',             &
    1600                                      'zw(nzb_w_inner)', 416, 417, 418 )
     1520             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av), id_dim_y_3d(av) /), 'zwwi',&
     1521                                     NF90_DOUBLE, id_var_zwwi_3d(av), 'meters', 'zw(nzb_w_inner)', &
     1522                                     416, 417, 418 )
    16011523
    16021524          ENDIF
     
    16051527!
    16061528!--          Define vertical coordinate grid (zs grid)
    1607              CALL netcdf_create_dim( id_set_3d(av), 'zs_3d',                   &
     1529             CALL netcdf_create_dim( id_set_3d(av), 'zs_3d',                                       &
    16081530                                     nzt_soil-nzb_soil+1, id_dim_zs_3d(av), 70 )
    1609              CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zs_3d(av) /),    &
    1610                                      'zs_3d', NF90_DOUBLE, id_var_zs_3d(av),   &
    1611                                      'meters', '', 71, 72, 00 )
    1612              CALL netcdf_create_att( id_set_3d(av), id_var_zs_3d(av), 'axis',  &
    1613                                      'Z', 000)
     1531             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zs_3d(av) /), 'zs_3d', NF90_DOUBLE,  &
     1532                                     id_var_zs_3d(av), 'meters', '', 71, 72, 00 )
     1533             CALL netcdf_create_att( id_set_3d(av), id_var_zs_3d(av), 'axis', 'Z', 000)
    16141534
    16151535          ENDIF
     
    16181538!
    16191539!--          Define vertical coordinate grid (zpc grid)
    1620              CALL netcdf_create_dim( id_set_3d(av), 'zpc_3d',                  &
    1621                                      pch_index+1, id_dim_zpc_3d(av), 70 )
     1540             CALL netcdf_create_dim( id_set_3d(av), 'zpc_3d', pch_index+1, id_dim_zpc_3d(av), 70 )
    16221541             !netcdf_create_dim(ncid, dim_name, ncdim_type, ncdim_id, error_no)
    1623              CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zpc_3d(av) /),   &
    1624                                      'zpc_3d', NF90_DOUBLE, id_var_zpc_3d(av), &
    1625                                      'meters', '', 71, 72, 00 )
    1626              CALL netcdf_create_att( id_set_3d(av), id_var_zpc_3d(av), 'axis', &
    1627                                      'Z', 000)
     1542             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zpc_3d(av) /), 'zpc_3d', NF90_DOUBLE,&
     1543                                     id_var_zpc_3d(av), 'meters', '', 71, 72, 00 )
     1544             CALL netcdf_create_att( id_set_3d(av), id_var_zpc_3d(av), 'axis', 'Z', 000)
    16281545
    16291546          ENDIF
     
    16361553          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
    16371554!
    1638 !--          Temporary solution to account for data output within the new urban
    1639 !--          surface model (urban_surface_mod.f90), see also SELECT CASE ( trimvar )
     1555!--          Temporary solution to account for data output within the new urban surface model
     1556!--          (urban_surface_mod.f90), see also SELECT CASE ( trimvar )
    16401557             trimvar = TRIM( do3d(av,i) )
    16411558             IF ( urban_surface  .AND.  trimvar(1:4) == 'usm_' )  THEN
     
    16801597!--             Block of urban surface model outputs
    16811598                CASE ( 'usm_output' )
    1682                    CALL usm_define_netcdf_grid( do3d(av,i), found, &
    1683                                                    grid_x, grid_y, grid_z )
     1599                   CALL usm_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    16841600
    16851601                CASE DEFAULT
    16861602
    1687                    CALL tcm_define_netcdf_grid( do3d(av,i), found, &
    1688                                                    grid_x, grid_y, grid_z )
     1603                   CALL tcm_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    16891604
    16901605!
    16911606!--                Check for land surface quantities
    1692                    IF ( .NOT. found .AND. land_surface )  THEN
    1693                       CALL lsm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
    1694                                                    grid_y, grid_z )
     1607                   IF ( .NOT. found  .AND.  land_surface )  THEN
     1608                      CALL lsm_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    16951609                   ENDIF
    16961610!
    16971611!--                Check for ocean quantities
    16981612                   IF ( .NOT. found  .AND.  ocean_mode )  THEN
    1699                       CALL ocean_define_netcdf_grid( do3d(av,i), found,  &
    1700                                                      grid_x, grid_y, grid_z )
     1613                      CALL ocean_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17011614                   ENDIF
    17021615
     
    17041617!--                Check for plant canopy quantities
    17051618                   IF ( .NOT. found  .AND.  plant_canopy )  THEN
    1706                       CALL pcm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
    1707                                                    grid_y, grid_z )
     1619                      CALL pcm_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17081620                   ENDIF
    17091621
     
    17111623!--                Check for radiation quantities
    17121624                   IF ( .NOT. found  .AND.  radiation )  THEN
    1713                       CALL radiation_define_netcdf_grid( do3d(av,i), found,    &
    1714                                                          grid_x, grid_y,       &
    1715                                                          grid_z )
     1625                      CALL radiation_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17161626                   ENDIF
    17171627
    17181628!--                Check for gust module quantities
    17191629                   IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    1720                       CALL gust_define_netcdf_grid( do3d(av,i), found, grid_x, &
    1721                                                     grid_y, grid_z )
     1630                      CALL gust_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17221631                   ENDIF
    17231632!
    17241633!--                Check for indoor model quantities
    1725                    IF ( .NOT. found .AND. indoor_model ) THEN
    1726                       CALL im_define_netcdf_grid( do3d(av,i), found,           &
    1727                                                   grid_x, grid_y, grid_z )
     1634                   IF ( .NOT. found  .AND.  indoor_model ) THEN
     1635                      CALL im_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17281636                   ENDIF
    17291637
     
    17311639!--                Check for biometeorology quantities
    17321640                   IF ( .NOT. found  .AND.  biometeorology )  THEN
    1733                       CALL bio_define_netcdf_grid( do3d(av,i), found,          &
    1734                                                    grid_x, grid_y, grid_z )
     1641                      CALL bio_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17351642                   ENDIF
    17361643
     
    17381645!--                Check for chemistry quantities
    17391646                   IF ( .NOT. found  .AND.  air_chemistry )  THEN
    1740                       CALL chem_define_netcdf_grid( do3d(av,i), found,         &
    1741                                                     grid_x, grid_y, grid_z )
     1647                      CALL chem_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17421648                   ENDIF
    17431649
     
    17451651!--                Check for SALSA quantities
    17461652                   IF ( .NOT. found  .AND.  salsa )  THEN
    1747                       CALL salsa_define_netcdf_grid( do3d(av,i), found, grid_x,&
    1748                                                      grid_y, grid_z )
     1653                      CALL salsa_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17491654                   ENDIF
    17501655!
    17511656!--                Check for user-defined quantities
    17521657                   IF ( .NOT. found  .AND.  user_module_enabled )  THEN
    1753                       CALL user_define_netcdf_grid( do3d(av,i), found, grid_x, &
    1754                                                     grid_y, grid_z )
     1658                      CALL user_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17551659                   ENDIF
    17561660
    1757                    IF ( .NOT. found )                                          &
    1758                       CALL doq_define_netcdf_grid( do3d(av,i), found, grid_x,  &
    1759                                                    grid_y, grid_z        )
     1661                   IF ( .NOT. found )                                                              &
     1662                      CALL doq_define_netcdf_grid( do3d(av,i), found, grid_x, grid_y, grid_z )
    17601663
    17611664                   IF ( .NOT. found )  THEN
    1762                       WRITE ( message_string, * ) 'no grid defined for varia', &
    1763                                                   'ble ', TRIM( do3d(av,i) )
    1764                       CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, &
    1765                                     6, 0 )
     1665                      WRITE ( message_string, * ) 'no grid defined for variable ',                 &
     1666                                                  TRIM( do3d(av,i) )
     1667                      CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
    17661668                   ENDIF
    17671669
     
    17941696!
    17951697!--          Define the grid
    1796              CALL netcdf_create_var( id_set_3d(av),(/ id_x, id_y, id_z,        &
    1797                                      id_dim_time_3d(av) /), do3d(av,i),        &
    1798                                      nc_precision(4), id_var_do3d(av,i),       &
    1799                                      TRIM( do3d_unit(av,i) ), do3d(av,i), 79,  &
    1800                                      80, 357, .TRUE. )
     1698             CALL netcdf_create_var( id_set_3d(av),(/ id_x, id_y, id_z, id_dim_time_3d(av) /),     &
     1699                                     do3d(av,i), nc_precision(4), id_var_do3d(av,i),               &
     1700                                     TRIM( do3d_unit(av,i) ), do3d(av,i), 79, 80, 357, .TRUE. )
    18011701#if defined( __netcdf4_parallel )
    18021702             IF ( netcdf_data_format > 4 )  THEN
    18031703!
    18041704!--             Set no fill for every variable to increase performance.
    1805                 nc_stat = NF90_DEF_VAR_FILL( id_set_3d(av),     &
    1806                                              id_var_do3d(av,i), &
    1807                                              NF90_NOFILL, 0 )
     1705                nc_stat = NF90_DEF_VAR_FILL( id_set_3d(av), id_var_do3d(av,i), NF90_NOFILL, 0 )
    18081706                CALL netcdf_handle_error( 'netcdf_define_header', 532 )
    18091707!
    18101708!--             Set collective io operations for parallel io
    1811                 nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
    1812                                                id_var_do3d(av,i), &
    1813                                                NF90_COLLECTIVE )
     1709                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av), id_var_do3d(av,i), NF90_COLLECTIVE )
    18141710                CALL netcdf_handle_error( 'netcdf_define_header', 445 )
    18151711             ENDIF
     
    18261722
    18271723!
    1828 !--       Write the list of variables as global attribute (this is used by
    1829 !--       restart runs and by combine_plot_fields)
    1830           nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
    1831                                   var_list )
     1724!--       Write the list of variables as global attribute (this is used by restart runs and by
     1725!--       combine_plot_fields).
     1726          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', var_list )
    18321727          CALL netcdf_handle_error( 'netcdf_define_header', 81 )
    18331728
    18341729!
    1835 !--       Set general no fill, otherwise the performance drops significantly for
    1836 !--       parallel output.
     1730!--       Set general no fill, otherwise the performance drops significantly for parallel output.
    18371731          nc_stat = NF90_SET_FILL( id_set_3d(av), NF90_NOFILL, oldmode )
    18381732          CALL netcdf_handle_error( 'netcdf_define_header', 528 )
     
    18441738
    18451739!
    1846 !--       These data are only written by PE0 for parallel output to increase
    1847 !--       the performance.
     1740!--       These data are only written by PE0 for parallel output to increase the performance.
    18481741          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
    18491742!
     
    18551748             ENDDO
    18561749
    1857              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av),  &
    1858                                      netcdf_data, start = (/ 1 /),    &
     1750             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av),                               &
     1751                                     netcdf_data, start = (/ 1 /),                                 &
    18591752                                     count = (/ nx+1 /) )
    18601753             CALL netcdf_handle_error( 'netcdf_define_header', 83 )
     
    18641757             ENDDO
    18651758
    1866              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_xu_3d(av), &
    1867                                      netcdf_data, start = (/ 1 /),    &
     1759             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_xu_3d(av),                              &
     1760                                     netcdf_data, start = (/ 1 /),                                 &
    18681761                                     count = (/ nx+1 /) )
    18691762             CALL netcdf_handle_error( 'netcdf_define_header', 385 )
     
    18791772             ENDDO
    18801773
    1881              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av),  &
    1882                                      netcdf_data, start = (/ 1 /),    &
     1774             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av),                               &
     1775                                     netcdf_data, start = (/ 1 /),                                 &
    18831776                                     count = (/ ny+1 /) )
    18841777             CALL netcdf_handle_error( 'netcdf_define_header', 84 )
     
    18881781             ENDDO
    18891782
    1890              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_yv_3d(av), &
    1891                                      netcdf_data, start = (/ 1 /),    &
     1783             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_yv_3d(av),                              &
     1784                                     netcdf_data, start = (/ 1 /),                                 &
    18921785                                     count = (/ ny+1 /))
    18931786             CALL netcdf_handle_error( 'netcdf_define_header', 387 )
     
    19201813
    19211814                   DO  i = 0, nx
    1922                      netcdf_data(i) = init_model%origin_x                      &
    1923                                     + cos_rot_angle * ( i + shift_x ) * dx
     1815                     netcdf_data(i) = init_model%origin_x + cos_rot_angle * ( i + shift_x ) * dx
    19241816                   ENDDO
    19251817
    1926                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),&
    1927                                            netcdf_data, start = (/ 1 /),       &
     1818                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),                    &
     1819                                           netcdf_data, start = (/ 1 /),                           &
    19281820                                           count = (/ nx+1 /) )
    19291821                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    19501842
    19511843                   DO  j = 0, ny
    1952                       netcdf_data(j) = init_model%origin_y                     &
    1953                                      + cos_rot_angle * ( j + shift_y ) * dy
     1844                      netcdf_data(j) = init_model%origin_y + cos_rot_angle * ( j + shift_y ) * dy
    19541845                   ENDDO
    19551846
    1956                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),&
    1957                                            netcdf_data, start = (/ 1 /),       &
     1847                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),                    &
     1848                                           netcdf_data, start = (/ 1 /),                           &
    19581849                                           count = (/ ny+1 /) )
    19591850                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    19861877                  DO  j = 0, ny
    19871878                     DO  i = 0, nx
    1988                         netcdf_data_2d(i,j) = init_model%origin_x                   &
    1989                                             + cos_rot_angle * ( i + shift_x ) * dx  &
    1990                                             + sin_rot_angle * ( j + shift_y ) * dy
     1879                        netcdf_data_2d(i,j) = init_model%origin_x                                  &
     1880                                              + cos_rot_angle * ( i + shift_x ) * dx               &
     1881                                              + sin_rot_angle * ( j + shift_y ) * dy
    19911882                     ENDDO
    19921883                  ENDDO
    19931884
    1994                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),  &
    1995                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     1885                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),                     &
     1886                                          netcdf_data_2d, start = (/ 1, 1 /),                      &
    19961887                                          count = (/ nx+1, ny+1 /) )
    19971888                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    19991890                  DO  j = 0, ny
    20001891                     DO  i = 0, nx
    2001                         netcdf_data_2d(i,j) = init_model%origin_y                   &
    2002                                             - sin_rot_angle * ( i + shift_x ) * dx  &
    2003                                             + cos_rot_angle * ( j + shift_y ) * dy
     1892                        netcdf_data_2d(i,j) = init_model%origin_y                                  &
     1893                                              - sin_rot_angle * ( i + shift_x ) * dx  &
     1894                                              + cos_rot_angle * ( j + shift_y ) * dy
    20041895                     ENDDO
    20051896                  ENDDO
    20061897
    2007                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),  &
    2008                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     1898                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),                     &
     1899                                          netcdf_data_2d, start = (/ 1, 1 /),                      &
    20091900                                          count = (/ nx+1, ny+1 /) )
    20101901                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    20151906!
    20161907!--          Write zu and zw data (vertical axes)
    2017              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zu_3d(av),  &
    2018                                      zu(nzb:nz_do3d), start = (/ 1 /), &
     1908             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zu_3d(av),                              &
     1909                                     zu(nzb:nz_do3d), start = (/ 1 /),                             &
    20191910                                     count = (/ nz_do3d-nzb+1 /) )
    20201911             CALL netcdf_handle_error( 'netcdf_define_header', 85 )
    20211912
    20221913
    2023              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zw_3d(av),  &
    2024                                      zw(nzb:nz_do3d), start = (/ 1 /), &
     1914             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zw_3d(av),                              &
     1915                                     zw(nzb:nz_do3d), start = (/ 1 /),                             &
    20251916                                     count = (/ nz_do3d-nzb+1 /) )
    20261917             CALL netcdf_handle_error( 'netcdf_define_header', 86 )
     
    20291920!
    20301921!--             Write zs grid
    2031                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zs_3d(av),  &
    2032                                         - zs(nzb_soil:nzt_soil), start = (/ 1 /), &
     1922                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zs_3d(av),                           &
     1923                                        - zs(nzb_soil:nzt_soil), start = (/ 1 /),                  &
    20331924                                        count = (/ nzt_soil-nzb_soil+1 /) )
    20341925                CALL netcdf_handle_error( 'netcdf_define_header', 86 )
     
    20381929!
    20391930!--             Write zpc grid
    2040                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zpc_3d(av),  &
    2041                                         zu(nzb:nzb+pch_index), start = (/ 1 /), &
     1931                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zpc_3d(av),                          &
     1932                                        zu(nzb:nzb+pch_index), start = (/ 1 /),                    &
    20421933                                        count = (/ pch_index+1 /) )
    20431934                CALL netcdf_handle_error( 'netcdf_define_header', 86 )
     
    20711962                DO  j = nys, nyn
    20721963                   DO  i = nxl, nxr
    2073                       eutm = init_model%origin_x                   &
    2074                            + cos_rot_angle * ( i + shift_x ) * dx  &
    2075                            + sin_rot_angle * ( j + shift_y ) * dy
    2076                       nutm = init_model%origin_y                   &
    2077                            - sin_rot_angle * ( i + shift_x ) * dx  &
    2078                            + cos_rot_angle * ( j + shift_y ) * dy
    2079 
    2080                       CALL  convert_utm_to_geographic( crs_list,          &
    2081                                                        eutm, nutm,        &
    2082                                                        lon(i,j), lat(i,j) )
     1964                      eutm = init_model%origin_x                                                   &
     1965                             + cos_rot_angle * ( i + shift_x ) * dx                                &
     1966                             + sin_rot_angle * ( j + shift_y ) * dy
     1967                      nutm = init_model%origin_y                                                   &
     1968                             - sin_rot_angle * ( i + shift_x ) * dx                                &
     1969                             + cos_rot_angle * ( j + shift_y ) * dy
     1970
     1971                      CALL  convert_utm_to_geographic( crs_list, eutm, nutm, lon(i,j), lat(i,j) )
    20831972                   ENDDO
    20841973                ENDDO
    20851974
    2086                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lon_3d(k,av), &
    2087                                      lon, start = (/ nxl+1, nys+1 /),       &
    2088                                      count = (/ nxr-nxl+1, nyn-nys+1 /) )
     1975                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lon_3d(k,av),                        &
     1976                                        lon, start = (/ nxl+1, nys+1 /),                           &
     1977                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    20891978                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    20901979
    2091                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lat_3d(k,av), &
    2092                                      lat, start = (/ nxl+1, nys+1 /),       &
    2093                                      count = (/ nxr-nxl+1, nyn-nys+1 /) )
     1980                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lat_3d(k,av),                        &
     1981                                        lat, start = (/ nxl+1, nys+1 /),                           &
     1982                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    20941983                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    20951984             ENDDO
     
    21001989          ENDIF
    21011990!
    2102 !--       In case of non-flat topography write height information. Only for
    2103 !--       parallel netcdf output.
    2104           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    2105                netcdf_data_format > 4 )  THEN
     1991!--       In case of non-flat topography write height information. Only for parallel netcdf output.
     1992          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4 )  THEN
    21061993
    21071994!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    2108 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    2109 !                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
    2110 !                                        start = (/ nxl+1, nys+1 /),            &
     1995!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),                         &
     1996!                                        zu_s_inner(nxl:nxr+1,nys:nyn),                             &
     1997!                                        start = (/ nxl+1, nys+1 /),                                &
    21111998!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
    21121999!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    2113 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    2114 !                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
    2115 !                                        start = (/ nxl+1, nys+1 /),            &
     2000!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),                         &
     2001!                                        zu_s_inner(nxl:nxr,nys:nyn+1),                             &
     2002!                                        start = (/ nxl+1, nys+1 /),                                &
    21162003!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
    21172004!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    2118 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    2119 !                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
    2120 !                                        start = (/ nxl+1, nys+1 /),            &
     2005!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),                         &
     2006!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),                           &
     2007!                                        start = (/ nxl+1, nys+1 /),                                &
    21212008!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
    21222009!             ELSE
    2123                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
    2124                                         zu_s_inner(nxl:nxr,nys:nyn),           &
    2125                                         start = (/ nxl+1, nys+1 /),            &
     2010                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),                         &
     2011                                        zu_s_inner(nxl:nxr,nys:nyn),                               &
     2012                                        start = (/ nxl+1, nys+1 /),                                &
    21262013                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    21272014!             ENDIF
     
    21292016
    21302017!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    2131 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    2132 !                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
    2133 !                                        start = (/ nxl+1, nys+1 /),            &
     2018!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),                         &
     2019!                                        zw_w_inner(nxl:nxr+1,nys:nyn),                             &
     2020!                                        start = (/ nxl+1, nys+1 /),                                &
    21342021!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
    21352022!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    2136 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    2137 !                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
    2138 !                                        start = (/ nxl+1, nys+1 /),            &
     2023!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),                         &
     2024!                                        zw_w_inner(nxl:nxr,nys:nyn+1),                             &
     2025!                                        start = (/ nxl+1, nys+1 /),                                &
    21392026!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
    21402027!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    2141 !                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    2142 !                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
    2143 !                                        start = (/ nxl+1, nys+1 /),            &
     2028!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),                         &
     2029!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),                           &
     2030!                                        start = (/ nxl+1, nys+1 /),                                &
    21442031!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
    21452032!             ELSE
    2146                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
    2147                                         zw_w_inner(nxl:nxr,nys:nyn),           &
    2148                                         start = (/ nxl+1, nys+1 /),            &
     2033                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),                         &
     2034                                        zw_w_inner(nxl:nxr,nys:nyn),                               &
     2035                                        start = (/ nxl+1, nys+1 /),                                &
    21492036                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    21502037!             ENDIF
     
    21572044!
    21582045!--       Get the list of variables and compare with the actual run.
    2159 !--       First var_list_old has to be reset, since GET_ATT does not assign
    2160 !--       trailing blanks.
     2046!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    21612047          var_list_old = ' '
    2162           nc_stat = NF90_GET_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
    2163                                   var_list_old )
     2048          nc_stat = NF90_GET_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', var_list_old )
    21642049          CALL netcdf_handle_error( 'netcdf_define_header', 87 )
    21652050
    21662051          var_list = ';'
    21672052          i = 1
    2168           DO WHILE ( do3d(av,i)(1:1) /= ' ' )
    2169              var_list = TRIM(var_list) // TRIM( do3d(av,i) ) // ';'
     2053          DO  WHILE ( do3d(av,i)(1:1) /= ' ' )
     2054             var_list = TRIM( var_list ) // TRIM( do3d(av,i) ) // ';'
    21702055             i = i + 1
    21712056          ENDDO
     
    21782063
    21792064          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    2180              message_string = 'netCDF file for volume data ' //             &
    2181                               TRIM( var ) // ' from previous run found,' // &
    2182                               '&but this file cannot be extended due to' // &
    2183                               ' variable mismatch.' //                      &
    2184                               '&New file is created instead.'
     2065             message_string = 'netCDF file for volume data ' // TRIM( var ) //                     &
     2066                              ' from previous run found,' //                                       &
     2067                              '&but this file cannot be extended due to' //                        &
     2068                              ' variable mismatch.' // '&New file is created instead.'
    21852069             CALL message( 'define_netcdf_header', 'PA0245', 0, 1, 0, 6, 0 )
    21862070             extend = .FALSE.
     
    21932077          CALL netcdf_handle_error( 'netcdf_define_header', 88 )
    21942078
    2195           nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_zu_3d(av), &
     2079          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_zu_3d(av),                        &
    21962080                                           dimids = id_dim_zu_3d_old )
    21972081          CALL netcdf_handle_error( 'netcdf_define_header', 89 )
    21982082          id_dim_zu_3d(av) = id_dim_zu_3d_old(1)
    21992083
    2200           nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_zu_3d(av), &
    2201                                             len = nz_old )
     2084          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_zu_3d(av), LEN = nz_old )
    22022085          CALL netcdf_handle_error( 'netcdf_define_header', 90 )
    22032086
    22042087          IF ( nz_do3d-nzb+1 /= nz_old )  THEN
    2205               message_string = 'netCDF file for volume data ' //             &
    2206                                TRIM( var ) // ' from previous run found,' // &
    2207                                '&but this file cannot be extended due to' // &
    2208                                ' mismatch in number of' //                   &
    2209                                ' vertical grid points (nz_do3d).' //         &
     2088              message_string = 'netCDF file for volume data ' // TRIM( var ) //                    &
     2089                               ' from previous run found,' //                                      &
     2090                               '&but this file cannot be extended due to' //                       &
     2091                               ' mismatch in number of' // ' vertical grid points (nz_do3d).' //   &
    22102092                               '&New file is created instead.'
    22112093             CALL message( 'define_netcdf_header', 'PA0246', 0, 1, 0, 6, 0 )
     
    22152097
    22162098!
    2217 !--       Get the id of the time coordinate (unlimited coordinate) and its
    2218 !--       last index on the file. The next time level is pl3d..count+1.
    2219 !--       The current time must be larger than the last output time
    2220 !--       on the file.
     2099!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     2100!--       The next time level is pl3d..count+1.
     2101!--       The current time must be larger than the last output time on the file.
    22212102          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'time', id_var_time_3d(av) )
    22222103          CALL netcdf_handle_error( 'netcdf_define_header', 91 )
    22232104
    2224           nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_time_3d(av), &
     2105          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_time_3d(av),                      &
    22252106                                           dimids = id_dim_time_old )
    22262107          CALL netcdf_handle_error( 'netcdf_define_header', 92 )
     
    22282109          id_dim_time_3d(av) = id_dim_time_old(1)
    22292110
    2230           nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_time_3d(av), &
    2231                                             len = ntime_count )
     2111          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_time_3d(av), LEN = ntime_count )
    22322112          CALL netcdf_handle_error( 'netcdf_define_header', 93 )
    22332113
    22342114!
    2235 !--       For non-parallel output use the last output time level of the netcdf
    2236 !--       file because the time dimension is unlimited. In case of parallel
    2237 !--       output the variable ntime_count could get the value of 9*10E36 because
    2238 !--       the time dimension is limited.
     2115!--       For non-parallel output use the last output time level of the netcdf file because the time
     2116!--       dimension is unlimited. In case of parallel output the variable ntime_count could get the
     2117!--       value of 9*10E36 because the time dimension is limited.
    22392118          IF ( netcdf_data_format < 5 ) do3d_time_count(av) = ntime_count
    22402119
    2241           nc_stat = NF90_GET_VAR( id_set_3d(av), id_var_time_3d(av), &
    2242                                   last_time_coordinate,              &
    2243                                   start = (/ do3d_time_count(av) /), &
     2120          nc_stat = NF90_GET_VAR( id_set_3d(av), id_var_time_3d(av),                               &
     2121                                  last_time_coordinate,                                            &
     2122                                  start = (/ do3d_time_count(av) /),                               &
    22442123                                  count = (/ 1 /) )
    22452124          CALL netcdf_handle_error( 'netcdf_define_header', 94 )
    22462125
    22472126          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    2248              message_string = 'netCDF file for volume data ' //             &
    2249                               TRIM( var ) // ' from previous run found,' // &
    2250                               '&but this file cannot be extended becaus' // &
    2251                               'e the current output time' //                &
    2252                               '&is less or equal than the last output t' // &
    2253                               'ime on this file.' //                        &
     2127             message_string = 'netCDF file for volume data ' // TRIM( var ) //                     &
     2128                              ' from previous run found,' //                                       &
     2129                              '&but this file cannot be extended because' //                       &
     2130                              ' the current output time' //                                        &
     2131                              '&is less or equal than the last output time' // ' on this file.' // &
    22542132                              '&New file is created instead.'
    22552133             CALL message( 'define_netcdf_header', 'PA0247', 0, 1, 0, 6, 0 )
     
    22612139          IF ( netcdf_data_format > 4 )  THEN
    22622140!
    2263 !--          Check if the needed number of output time levels is increased
    2264 !--          compared to the number of time levels in the existing file.
     2141!--          Check if the needed number of output time levels is increased compared to the number of
     2142!--          time levels in the existing file.
    22652143             IF ( ntdim_3d(av) > ntime_count )  THEN
    2266                 message_string = 'netCDF file for volume data ' // &
    2267                                  TRIM( var ) // ' from previous run found,' // &
    2268                                  '&but this file cannot be extended becaus' // &
    2269                                  'e the number of output time levels has b' // &
    2270                                  'een increased compared to the previous s' // &
    2271                                  'imulation.' //                               &
     2144                message_string = 'netCDF file for volume data ' // TRIM( var ) //                  &
     2145                                 ' from previous run found,' //                                    &
     2146                                 '&but this file cannot be extended becaus' //                     &
     2147                                 'e the number of output time levels has b' //                     &
     2148                                 'een increased compared to the previous s' // 'imulation.' //     &
    22722149                                 '&New file is created instead.'
    22732150                CALL message( 'define_netcdf_header', 'PA0388', 0, 1, 0, 6, 0 )
     
    22772154!--             Recalculate the needed time levels for the new file.
    22782155                IF ( av == 0 )  THEN
    2279                    ntdim_3d(0) = CEILING(                               &
    2280                            ( end_time - MAX( skip_time_do3d,            &
    2281                                              simulated_time_at_begin )  &
    2282                            ) / dt_do3d )
     2156                   ntdim_3d(0) = CEILING( ( end_time - MAX( skip_time_do3d,                        &
     2157                                                            simulated_time_at_begin )              &
     2158                                          ) / dt_do3d )
    22832159                   IF ( do3d_at_begin )  ntdim_3d(0) = ntdim_3d(0) + 1
    22842160                ELSE
    2285                    ntdim_3d(1) = CEILING(                               &
    2286                            ( end_time - MAX( skip_time_data_output_av,  &
    2287                                              simulated_time_at_begin )  &
    2288                            ) / dt_data_output_av )
     2161                   ntdim_3d(1) = CEILING( ( end_time - MAX( skip_time_data_output_av,              &
     2162                                                            simulated_time_at_begin )              &
     2163                                          ) / dt_data_output_av )
    22892164                ENDIF
    22902165                RETURN
     
    22962171!--       Now get the variable ids.
    22972172          i = 1
    2298           DO WHILE ( do3d(av,i)(1:1) /= ' ' )
    2299              nc_stat = NF90_INQ_VARID( id_set_3d(av), TRIM( do3d(av,i) ), &
    2300                                        id_var_do3d(av,i) )
     2173          DO  WHILE ( do3d(av,i)(1:1) /= ' ' )
     2174             nc_stat = NF90_INQ_VARID( id_set_3d(av), TRIM( do3d(av,i) ), id_var_do3d(av,i) )
    23012175             CALL netcdf_handle_error( 'netcdf_define_header', 95 )
    23022176#if defined( __netcdf4_parallel )
     
    23042178!--          Set collective io operations for parallel io
    23052179             IF ( netcdf_data_format > 4 )  THEN
    2306                 nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
    2307                                                id_var_do3d(av,i), &
    2308                                                NF90_COLLECTIVE )
     2180                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av), id_var_do3d(av,i), NF90_COLLECTIVE )
    23092181                CALL netcdf_handle_error( 'netcdf_define_header', 453 )
    23102182             ENDIF
     
    23142186
    23152187!
    2316 !--       Update the title attribute on file
    2317 !--       In order to avoid 'data mode' errors if updated attributes are larger
    2318 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    2319 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    2320 !--       performance loss due to data copying; an alternative strategy would be
    2321 !--       to ensure equal attribute size. Maybe revise later.
     2188!--       Update the title attribute on file.
     2189!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     2190!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     2191!--       calls. This implies a possible performance loss due to data copying; an alternative
     2192!--       strategy would be to ensure equal attribute size. Maybe revise later.
    23222193          IF ( av == 0 )  THEN
    23232194             time_average_text = ' '
    23242195          ELSE
    2325              WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
    2326                                                             averaging_interval
     2196             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' ) averaging_interval
    23272197          ENDIF
    23282198          nc_stat = NF90_REDEF( id_set_3d(av) )
    23292199          CALL netcdf_handle_error( 'netcdf_define_header', 429 )
    2330           nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title', &
    2331                                   TRIM( run_description_header ) //    &
    2332                                   TRIM( time_average_text ) )
     2200          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title',                             &
     2201                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    23332202          CALL netcdf_handle_error( 'netcdf_define_header', 96 )
    23342203          nc_stat = NF90_ENDDEF( id_set_3d(av) )
    23352204          CALL netcdf_handle_error( 'netcdf_define_header', 430 )
    2336           message_string = 'netCDF file for volume data ' //             &
    2337                            TRIM( var ) // ' from previous run found.' // &
    2338                            '&This file will be extended.'
     2205          message_string = 'netCDF file for volume data ' // TRIM( var ) //                        &
     2206                           ' from previous run found.' // '&This file will be extended.'
    23392207          CALL message( 'define_netcdf_header', 'PA0248', 0, 0, 0, 6, 0 )
    23402208
     
    23442212!
    23452213!--       Define some global attributes of the dataset
    2346           nc_stat = NF90_PUT_ATT( id_set_agt, NF90_GLOBAL, 'title', &
    2347                                   TRIM( run_description_header ) )
     2214          nc_stat = NF90_PUT_ATT( id_set_agt, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    23482215          CALL netcdf_handle_error( 'netcdf_define_header', 330 )
    23492216!
    23502217!--       Switch for unlimited time dimension
    23512218          IF ( agent_time_unlimited ) THEN
    2352              CALL netcdf_create_dim( id_set_agt, 'time', NF90_UNLIMITED,       &
     2219             CALL netcdf_create_dim( id_set_agt, 'time', NF90_UNLIMITED, id_dim_time_agt, 331 )
     2220          ELSE
     2221             CALL netcdf_create_dim( id_set_agt, 'time',                                           &
     2222                                     INT( ( MIN( multi_agent_system_end, end_time ) -              &
     2223                                            multi_agent_system_start ) /                           &
     2224                                            dt_write_agent_data * 1.1 ),                           &
    23532225                                     id_dim_time_agt, 331 )
    2354           ELSE
    2355              CALL netcdf_create_dim( id_set_agt, 'time',                       &
    2356                                      INT( ( MIN( multi_agent_system_end,       &
    2357                                                  end_time ) -                  &
    2358                                             multi_agent_system_start ) /       &
    2359                                             dt_write_agent_data * 1.1 ),       &
    2360                                      id_dim_time_agt, 331 )
    2361           ENDIF
    2362 
    2363           CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /), 'time',   &
    2364                                   NF90_REAL4, id_var_time_agt, 'seconds', 'time',  &
    2365                                   332, 333, 000 )
     2226          ENDIF
     2227
     2228          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /), 'time', NF90_REAL4,           &
     2229                                  id_var_time_agt, 'seconds', 'time', 332, 333, 000 )
    23662230          CALL netcdf_create_att( id_set_agt, id_var_time_agt, 'standard_name', 'time', 000)
    23672231          CALL netcdf_create_att( id_set_agt, id_var_time_agt, 'axis', 'T', 000)
    23682232
    2369           CALL netcdf_create_dim( id_set_agt, 'agent_number',                  &
    2370                                   dim_size_agtnum, id_dim_agtnum, 334 )
    2371 
    2372           CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum /),             &
    2373                                   'agent_number', NF90_REAL4,                  &
    2374                                   id_var_agtnum, 'agent number', '', 335,      &
    2375                                   336, 000 )
     2233          CALL netcdf_create_dim( id_set_agt, 'agent_number', dim_size_agtnum, id_dim_agtnum, 334 )
     2234
     2235          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum /), 'agent_number', NF90_REAL4,     &
     2236                                  id_var_agtnum, 'agent number', '', 335, 336, 000 )
    23762237!
    23772238!--       Define variable which contains the real number of agents in use
    2378           CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /),           &
    2379                                   'real_num_of_agt', NF90_REAL4,               &
    2380                                   id_var_rnoa_agt, 'agent number', '', 337,    &
    2381                                   338, 000 )
     2239          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /), 'real_num_of_agt', NF90_REAL4,&
     2240                                  id_var_rnoa_agt, 'agent number', '', 337, 338, 000 )
    23822241          i = 1
    2383           CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,                &
    2384                                   id_dim_time_agt /), agt_var_names(i),        &
    2385                                   NF90_DOUBLE, id_var_agt(i),                  &
    2386                                   TRIM( agt_var_units(i) ),                    &
    2387                                   TRIM( agt_var_names(i) ), 339, 340, 341 )
     2242          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum, id_dim_time_agt /),                &
     2243                                  agt_var_names(i), NF90_DOUBLE, id_var_agt(i),                    &
     2244                                  TRIM( agt_var_units(i) ), TRIM( agt_var_names(i) ),              &
     2245                                  339, 340, 341 )
    23882246!
    23892247!--       Define the variables
    23902248          DO  i = 2, 6
    2391              CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,             &
    2392                                      id_dim_time_agt /), agt_var_names(i),     &
    2393                                      NF90_REAL4, id_var_agt(i),                &
    2394                                      TRIM( agt_var_units(i) ),                 &
    2395                                      TRIM( agt_var_names(i) ), 339, 340, 341 )
     2249             CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum, id_dim_time_agt /),             &
     2250                                     agt_var_names(i), NF90_REAL4, id_var_agt(i),                  &
     2251                                     TRIM( agt_var_units(i) ), TRIM( agt_var_names(i) ),           &
     2252                                     339, 340, 341 )
    23962253
    23972254          ENDDO
     
    23992256!--       Define vars for biometeorology
    24002257          IF ( biometeorology )  THEN
    2401              CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,             &
    2402                                      id_dim_time_agt /), agt_var_names(7),     &
    2403                                      nc_precision(8), id_var_agt(7),           &
    2404                                      TRIM( agt_var_units(7) ),                 &
    2405                                      TRIM( agt_var_names(7) ), 339, 340, 341 )                     
     2258             CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum, id_dim_time_agt /),             &
     2259                                     agt_var_names(7), nc_precision(8), id_var_agt(7),             &
     2260                                     TRIM( agt_var_units(7) ), TRIM( agt_var_names(7) ),           &
     2261                                     339, 340, 341 )
    24062262          ENDIF
    24072263!
     
    24152271!
    24162272! !
    2417 ! !--       Get the id of the time coordinate (unlimited coordinate) and its
    2418 ! !--       last index on the file. The next time level is prt..count+1.
    2419 ! !--       The current time must be larger than the last output time
    2420 ! !--       on the file.
     2273! !--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     2274! !--       The next time level is prt..count+1.
     2275! !--       The current time must be larger than the last output time on the file.
    24212276!           nc_stat = NF90_INQ_VARID( id_set_agt, 'time', id_var_time_agt )
    24222277!           CALL netcdf_handle_error( 'netcdf_define_header', 343 )
    24232278!
    2424 !           nc_stat = NF90_INQUIRE_VARIABLE( id_set_agt, id_var_time_agt, &
    2425 !                                            dimids = id_dim_time_old )
     2279!           nc_stat = NF90_INQUIRE_VARIABLE( id_set_agt, id_var_time_agt, dimids = id_dim_time_old )
    24262280!           CALL netcdf_handle_error( 'netcdf_define_header', 344 )
    24272281!           id_dim_time_agt = id_dim_time_old(1)
    24282282!
    2429 !           nc_stat = NF90_INQUIRE_DIMENSION( id_set_agt, id_dim_time_agt, &
    2430 !                                             len = agt_time_count )
     2283!           nc_stat = NF90_INQUIRE_DIMENSION( id_set_agt, id_dim_time_agt, LEN = agt_time_count )
    24312284!           CALL netcdf_handle_error( 'netcdf_define_header', 345 )
    24322285!
    2433 !           nc_stat = NF90_GET_VAR( id_set_agt, id_var_time_agt,  &
    2434 !                                   last_time_coordinate,         &
    2435 !                                   start = (/ agt_time_count /), &
     2286!           nc_stat = NF90_GET_VAR( id_set_agt, id_var_time_agt,                                   &
     2287!                                   last_time_coordinate,                                          &
     2288!                                   start = (/ agt_time_count /),                                  &
    24362289!                                   count = (/ 1 /) )
    24372290!           CALL netcdf_handle_error( 'netcdf_define_header', 346 )
    24382291!
    24392292!           IF ( last_time_coordinate(1) >= simulated_time )  THEN
    2440 !              message_string = 'netCDF file for agents ' //                  &
    2441 !                               'from previous run found,' //                 &
    2442 !                               '&but this file cannot be extended becaus' // &
    2443 !                               'e the current output time' //                &
    2444 !                               '&is less or equal than the last output t' // &
    2445 !                               'ime on this file.' //                        &
     2293!              message_string = 'netCDF file for agents ' //'from previous run found,' //           &
     2294!                               '&but this file cannot be extended because' //                      &
     2295!                               ' the current output time' //                &
     2296!                               '&is less or equal than the last output time' // ' on this file.' //&
    24462297!                               '&New file is created instead.'
    24472298!              CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
     
    24542305! !--       Dataset seems to be extendable.
    24552306! !--       Now get the variable ids.
    2456 !           nc_stat = NF90_INQ_VARID( id_set_agt, 'real_num_of_agt', &
    2457 !                                     id_var_rnoa_agt )
     2307!           nc_stat = NF90_INQ_VARID( id_set_agt, 'real_num_of_agt', id_var_rnoa_agt )
    24582308!           CALL netcdf_handle_error( 'netcdf_define_header', 347 )
    24592309!
    24602310!           DO  i = 1, 17
    24612311!
    2462 !              nc_stat = NF90_INQ_VARID( id_set_agt, agt_var_names(i), &
    2463 !                                        id_var_prt(i) )
     2312!              nc_stat = NF90_INQ_VARID( id_set_agt, agt_var_names(i), id_var_prt(i) )
    24642313!              CALL netcdf_handle_error( 'netcdf_define_header', 348 )
    24652314!
    24662315!           ENDDO
    24672316!
    2468 !           message_string = 'netCDF file for particles ' // &
    2469 !                            'from previous run found.' //   &
     2317!           message_string = 'netCDF file for particles ' //'from previous run found.' //           &
    24702318!                            '&This file will be extended.'
    24712319!           CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
     
    24772325!--       Define some global attributes of the dataset
    24782326          IF ( av == 0 )  THEN
    2479              CALL netcdf_create_global_atts( id_set_xy(av), 'xy', TRIM( run_description_header ), 97 )
     2327             CALL netcdf_create_global_atts( id_set_xy(av), 'xy', TRIM( run_description_header ),  &
     2328                                             97 )
    24802329             time_average_text = ' '
    24812330          ELSE
    2482              CALL netcdf_create_global_atts( id_set_xy(av), 'xy_av', TRIM( run_description_header ), 97 )
     2331             CALL netcdf_create_global_atts( id_set_xy(av), 'xy_av',                               &
     2332                                             TRIM( run_description_header ), 97 )
    24832333             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    2484              nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'time_avg',   &
     2334             nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'time_avg',                       &
    24852335                                     TRIM( time_average_text ) )
    24862336             CALL netcdf_handle_error( 'netcdf_define_header', 98 )
     
    24892339!
    24902340!--       Define time coordinate for xy sections.
    2491 !--       For parallel output the time dimensions has to be limited, otherwise
    2492 !--       the performance drops significantly.
     2341!--       For parallel output the time dimensions has to be limited, otherwise the performance drops
     2342!--       significantly.
    24932343          IF ( netcdf_data_format < 5 )  THEN
    2494              CALL netcdf_create_dim( id_set_xy(av), 'time', NF90_UNLIMITED,    &
    2495                                      id_dim_time_xy(av), 99 )
     2344             CALL netcdf_create_dim( id_set_xy(av), 'time', NF90_UNLIMITED, id_dim_time_xy(av), 99 )
    24962345          ELSE
    2497              CALL netcdf_create_dim( id_set_xy(av), 'time', ntdim_2d_xy(av),   &
    2498                                      id_dim_time_xy(av), 524 )
    2499           ENDIF
    2500 
    2501           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_time_xy(av) /),     &
    2502                                   'time', NF90_DOUBLE, id_var_time_xy(av),     &
    2503                                   'seconds', 'time', 100, 101, 000 )
     2346             CALL netcdf_create_dim( id_set_xy(av), 'time', ntdim_2d_xy(av), id_dim_time_xy(av),   &
     2347                                     524 )
     2348          ENDIF
     2349
     2350          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_time_xy(av) /), 'time', NF90_DOUBLE,    &
     2351                                  id_var_time_xy(av), 'seconds', 'time', 100, 101, 000 )
    25042352          CALL netcdf_create_att( id_set_xy(av), id_var_time_xy(av), 'standard_name', 'time', 000)
    25052353          CALL netcdf_create_att( id_set_xy(av), id_var_time_xy(av), 'axis', 'T', 000)
     
    25112359          ELSE
    25122360             ns = 1
    2513              DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
     2361             DO  WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
    25142362                ns = ns + 1
    25152363             ENDDO
     
    25192367!
    25202368!--       Define vertical coordinate grid (zu grid)
    2521           CALL netcdf_create_dim( id_set_xy(av), 'zu_xy', ns,                  &
    2522                                   id_dim_zu_xy(av), 102 )
    2523           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /),       &
    2524                                   'zu_xy', NF90_DOUBLE, id_var_zu_xy(av),      &
    2525                                   'meters', '', 103, 104, 000 )
    2526           CALL netcdf_create_att( id_set_xy(av), id_var_zu_xy(av), 'axis',     &
    2527                                   'Z', 000)
     2369          CALL netcdf_create_dim( id_set_xy(av), 'zu_xy', ns, id_dim_zu_xy(av), 102 )
     2370          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /), 'zu_xy', NF90_DOUBLE,     &
     2371                                  id_var_zu_xy(av), 'meters', '', 103, 104, 000 )
     2372          CALL netcdf_create_att( id_set_xy(av), id_var_zu_xy(av), 'axis', 'Z', 000)
    25282373!
    25292374!--       Define vertical coordinate grid (zw grid)
    2530           CALL netcdf_create_dim( id_set_xy(av), 'zw_xy', ns,                  &
    2531                                   id_dim_zw_xy(av), 105 )
    2532           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zw_xy(av) /),       &
    2533                                   'zw_xy', NF90_DOUBLE, id_var_zw_xy(av),      &
    2534                                   'meters', '', 106, 107, 000 )
    2535           CALL netcdf_create_att( id_set_xy(av), id_var_zw_xy(av), 'axis',     &
    2536                                   'Z', 000)
     2375          CALL netcdf_create_dim( id_set_xy(av), 'zw_xy', ns, id_dim_zw_xy(av), 105 )
     2376          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zw_xy(av) /), 'zw_xy', NF90_DOUBLE,     &
     2377                                  id_var_zw_xy(av), 'meters', '', 106, 107, 000 )
     2378          CALL netcdf_create_att( id_set_xy(av), id_var_zw_xy(av), 'axis', 'Z', 000)
    25372379
    25382380          IF ( land_surface )  THEN
    25392381
    25402382             ns_do = 1
    2541              DO WHILE ( section(ns_do,1) /= -9999  .AND.  ns_do < nzs )
     2383             DO  WHILE ( section(ns_do,1) /= -9999  .AND.  ns_do < nzs )
    25422384                ns_do = ns_do + 1
    25432385             ENDDO
    25442386!
    25452387!--          Define vertical coordinate grid (zs grid)
    2546              CALL netcdf_create_dim( id_set_xy(av), 'zs_xy', ns_do,            &
    2547                                      id_dim_zs_xy(av), 539 )
    2548              CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zs_xy(av) /),    &
    2549                                      'zs_xy', NF90_DOUBLE, id_var_zs_xy(av),   &
    2550                                      'meters', '', 540, 541, 000 )
    2551              CALL netcdf_create_att( id_set_xy(av), id_var_zs_xy(av), 'axis',  &
    2552                                      'Z', 000)
    2553 
    2554           ENDIF
    2555 
    2556 !
    2557 !--       Define a pseudo vertical coordinate grid for the surface variables
    2558 !--       u* and t* to store their height level
    2559           CALL netcdf_create_dim( id_set_xy(av), 'zu1_xy', 1,                  &
    2560                                   id_dim_zu1_xy(av), 108 )
    2561           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu1_xy(av) /),      &
    2562                                   'zu1_xy', NF90_DOUBLE, id_var_zu1_xy(av),    &
    2563                                   'meters', '', 109, 110, 000 )
    2564           CALL netcdf_create_att( id_set_xy(av), id_var_zu1_xy(av), 'axis',    &
    2565                                   'Z', 000)
    2566 !
    2567 !--       Define a variable to store the layer indices of the horizontal cross
    2568 !--       sections, too
    2569           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /),       &
    2570                                   'ind_z_xy', NF90_DOUBLE,                     &
    2571                                   id_var_ind_z_xy(av), 'gridpoints', '', 111,  &
    2572                                   112, 000 )
     2388             CALL netcdf_create_dim( id_set_xy(av), 'zs_xy', ns_do, id_dim_zs_xy(av), 539 )
     2389             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zs_xy(av) /), 'zs_xy', NF90_DOUBLE,  &
     2390                                     id_var_zs_xy(av), 'meters', '', 540, 541, 000 )
     2391             CALL netcdf_create_att( id_set_xy(av), id_var_zs_xy(av), 'axis', 'Z', 000)
     2392
     2393          ENDIF
     2394
     2395!
     2396!--       Define a pseudo vertical coordinate grid for the surface variables u* and t* to store
     2397!--       their height level.
     2398          CALL netcdf_create_dim( id_set_xy(av), 'zu1_xy', 1, id_dim_zu1_xy(av), 108 )
     2399          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu1_xy(av) /), 'zu1_xy', NF90_DOUBLE,   &
     2400                                  id_var_zu1_xy(av), 'meters', '', 109, 110, 000 )
     2401          CALL netcdf_create_att( id_set_xy(av), id_var_zu1_xy(av), 'axis', 'Z', 000)
     2402!
     2403!--       Define a variable to store the layer indices of the horizontal cross sections, too.
     2404          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /), 'ind_z_xy', NF90_DOUBLE,  &
     2405                                  id_var_ind_z_xy(av), 'gridpoints', '', 111, 112, 000 )
    25732406!
    25742407!--       Define x-axis (for scalar position)
    2575           CALL netcdf_create_dim( id_set_xy(av), 'x', nx+1, id_dim_x_xy(av),   &
    2576                                   113 )
    2577           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av) /), 'x',   &
    2578                                   NF90_DOUBLE, id_var_x_xy(av), 'meters', '',  &
    2579                                   114, 115, 000 )
    2580           CALL netcdf_create_att( id_set_xy(av), id_var_x_xy(av), 'axis',      &
    2581                                   'X', 000)
     2408          CALL netcdf_create_dim( id_set_xy(av), 'x', nx+1, id_dim_x_xy(av), 113 )
     2409          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av) /), 'x', NF90_DOUBLE,          &
     2410                                  id_var_x_xy(av), 'meters', '', 114, 115, 000 )
     2411          CALL netcdf_create_att( id_set_xy(av), id_var_x_xy(av), 'axis', 'X', 000)
    25822412!
    25832413!--       Define x-axis (for u position)
    2584           CALL netcdf_create_dim( id_set_xy(av), 'xu', nx+1,                   &
    2585                                   id_dim_xu_xy(av), 388 )
    2586           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_xu_xy(av) /), 'xu', &
    2587                                   NF90_DOUBLE, id_var_xu_xy(av), 'meters', '', &
    2588                                   389, 390, 000 )
    2589           CALL netcdf_create_att( id_set_xy(av), id_var_xu_xy(av), 'axis',     &
    2590                                   'X', 000)
     2414          CALL netcdf_create_dim( id_set_xy(av), 'xu', nx+1, id_dim_xu_xy(av), 388 )
     2415          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_xu_xy(av) /), 'xu', NF90_DOUBLE,        &
     2416                                  id_var_xu_xy(av), 'meters', '', 389, 390, 000 )
     2417          CALL netcdf_create_att( id_set_xy(av), id_var_xu_xy(av), 'axis', 'X', 000)
    25912418!
    25922419!--       Define y-axis (for scalar position)
    2593           CALL netcdf_create_dim( id_set_xy(av), 'y', ny+1, id_dim_y_xy(av),   &
    2594                                   116 )
    2595           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_y_xy(av) /), 'y',   &
    2596                                   NF90_DOUBLE, id_var_y_xy(av), 'meters', '',  &
    2597                                   117, 118, 000 )
    2598           CALL netcdf_create_att( id_set_xy(av), id_var_y_xy(av), 'axis',      &
    2599                                   'Y', 000)
     2420          CALL netcdf_create_dim( id_set_xy(av), 'y', ny+1, id_dim_y_xy(av), 116 )
     2421          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_y_xy(av) /), 'y', NF90_DOUBLE,          &
     2422                                  id_var_y_xy(av), 'meters', '', 117, 118, 000 )
     2423          CALL netcdf_create_att( id_set_xy(av), id_var_y_xy(av), 'axis', 'Y', 000)
    26002424!
    26012425!--       Define y-axis (for scalar position)
    2602           CALL netcdf_create_dim( id_set_xy(av), 'yv', ny+1,                   &
    2603                                   id_dim_yv_xy(av), 364 )
    2604           CALL netcdf_create_var( id_set_xy(av), (/ id_dim_yv_xy(av) /), 'yv', &
    2605                                   NF90_DOUBLE, id_var_yv_xy(av), 'meters', '', &
    2606                                   365, 366, 000 )
    2607           CALL netcdf_create_att( id_set_xy(av), id_var_yv_xy(av), 'axis',     &
    2608                                   'Y', 000)
     2426          CALL netcdf_create_dim( id_set_xy(av), 'yv', ny+1, id_dim_yv_xy(av), 364 )
     2427          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_yv_xy(av) /), 'yv', NF90_DOUBLE,        &
     2428                                  id_var_yv_xy(av), 'meters', '', 365, 366, 000 )
     2429          CALL netcdf_create_att( id_set_xy(av), id_var_yv_xy(av), 'axis', 'Y', 000)
    26092430!
    26102431!--       Define UTM and geographic coordinates
    2611           CALL define_geo_coordinates( id_set_xy(av),         &
    2612                   (/ id_dim_x_xy(av), id_dim_xu_xy(av) /),    &
    2613                   (/ id_dim_y_xy(av), id_dim_yv_xy(av) /),    &
    2614                   id_var_eutm_xy(:,av), id_var_nutm_xy(:,av), &
    2615                   id_var_lat_xy(:,av), id_var_lon_xy(:,av)    )
     2432          CALL define_geo_coordinates( id_set_xy(av),                                              &
     2433                                       (/ id_dim_x_xy(av), id_dim_xu_xy(av) /),                    &
     2434                                       (/ id_dim_y_xy(av), id_dim_yv_xy(av) /),                    &
     2435                                       id_var_eutm_xy(:,av), id_var_nutm_xy(:,av),                &
     2436                                       id_var_lat_xy(:,av), id_var_lon_xy(:,av)    )
    26162437!
    26172438!--       Define coordinate-reference system
    26182439          CALL netcdf_create_crs( id_set_xy(av), 000 )
    26192440!
    2620 !--       In case of non-flat topography define 2d-arrays containing the height
    2621 !--       information. Only for parallel netcdf output.
    2622           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    2623                netcdf_data_format > 4  )  THEN
     2441!--       In case of non-flat topography define 2d-arrays containing the height information. Only
     2442!--       for parallel netcdf output.
     2443          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4  )  THEN
    26242444!
    26252445!--          Define zusi = zu(nzb_s_inner)
    2626              CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),        &
    2627                                      id_dim_y_xy(av) /), 'zusi', NF90_DOUBLE,  &
    2628                                      id_var_zusi_xy(av), 'meters',             &
    2629                                      'zu(nzb_s_inner)', 421, 422, 423 )
     2446             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av), id_dim_y_xy(av) /), 'zusi',&
     2447                                     NF90_DOUBLE, id_var_zusi_xy(av), 'meters', 'zu(nzb_s_inner)', &
     2448                                     421, 422, 423 )
    26302449!
    26312450!--          Define zwwi = zw(nzb_w_inner)
    2632              CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),        &
    2633                                      id_dim_y_xy(av) /), 'zwwi', NF90_DOUBLE,  &
    2634                                      id_var_zwwi_xy(av), 'meters',             &
    2635                                      'zw(nzb_w_inner)', 424, 425, 426 )
     2451             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av), id_dim_y_xy(av) /), 'zwwi',&
     2452                                     NF90_DOUBLE, id_var_zwwi_xy(av), 'meters', 'zw(nzb_w_inner)', &
     2453                                     424, 425, 426 )
    26362454
    26372455          ENDIF
     
    26422460          i = 1
    26432461
    2644           DO WHILE ( do2d(av,i)(1:1) /= ' ' )
     2462          DO  WHILE ( do2d(av,i)(1:1) /= ' ' )
    26452463
    26462464             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
    26472465!
    2648 !--             If there is a star in the variable name (u* or t*), it is a
    2649 !--             surface variable. Define it with id_dim_zu1_xy.
     2466!--             If there is a star in the variable name (u* or t*), it is a surface variable. Define
     2467!--             it with id_dim_zu1_xy.
    26502468                IF ( INDEX( do2d(av,i), '*' ) /= 0 )  THEN
    26512469
    2652                    CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),  &
    2653                                            id_dim_y_xy(av), id_dim_zu1_xy(av), &
    2654                                            id_dim_time_xy(av) /), do2d(av,i),  &
    2655                                            nc_precision(1), id_var_do2d(av,i), &
    2656                                            TRIM( do2d_unit(av,i) ),            &
    2657                                            do2d(av,i), 119, 120, 354, .TRUE. )
     2470                   CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av), id_dim_y_xy(av),     &
     2471                                           id_dim_zu1_xy(av), id_dim_time_xy(av) /), do2d(av,i),   &
     2472                                           nc_precision(1), id_var_do2d(av,i),                     &
     2473                                           TRIM( do2d_unit(av,i) ), do2d(av,i), 119, 120, 354,     &
     2474                                           .TRUE. )
    26582475
    26592476                ELSE
     
    26662483!--                   Most variables are defined on the zu grid
    26672484                      CASE ( 'e_xy', 'nc_xy', 'ng_xy', 'ni_xy', 'nr_xy', 'ns_xy', 'p_xy',          &
    2668                              'pc_xy', 'pr_xy', 'prr_xy', 'q_xy',               &
     2485                             'pc_xy', 'pr_xy', 'prr_xy', 'q_xy',                                   &
    26692486                             'qc_xy', 'qg_xy', 'qi_xy', 'ql_xy', 'ql_c_xy', 'ql_v_xy',             &
    26702487                             'ql_vp_xy', 'qr_xy', 'qs_xy', 'qv_xy',                                &
    2671                              's_xy',                                           &
     2488                             's_xy',                                                               &
    26722489                             'theta_xy', 'thetal_xy', 'thetav_xy' )
    26732490
     
    27022519!--                      Check for land surface quantities
    27032520                         IF ( land_surface )  THEN
    2704                             CALL lsm_define_netcdf_grid( do2d(av,i), found,    &
    2705                                                    grid_x, grid_y, grid_z )
     2521                            CALL lsm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    27062522                         ENDIF
    27072523
    27082524                         IF ( .NOT. found )  THEN
    2709                             CALL tcm_define_netcdf_grid( do2d(av,i), found,    &
    2710                                                          grid_x, grid_y,       &
     2525                            CALL tcm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
     2526                         ENDIF
     2527
     2528!
     2529!--                      Check for ocean quantities
     2530                         IF ( .NOT. found  .AND.  ocean_mode )  THEN
     2531                            CALL ocean_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,      &
     2532                                                           grid_z )
     2533                         ENDIF
     2534!
     2535!--                      Check for radiation quantities
     2536                         IF ( .NOT. found  .AND.  radiation )  THEN
     2537                            CALL radiation_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,  &
     2538                                                               grid_z )
     2539                         ENDIF
     2540
     2541!
     2542!--                      Check for SALSA quantities
     2543                         IF ( .NOT. found  .AND.  salsa )  THEN
     2544                            CALL salsa_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,      &
     2545                                                           grid_z )
     2546                         ENDIF
     2547
     2548!
     2549!--                      Check for gust module quantities
     2550                         IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
     2551                            CALL gust_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,       &
     2552                                                          grid_z )
     2553                         ENDIF
     2554!
     2555!--                      Check for biometeorology quantities
     2556                         IF ( .NOT. found  .AND.  biometeorology )  THEN
     2557                            CALL bio_define_netcdf_grid( do2d( av, i), found, grid_x, grid_y,      &
    27112558                                                         grid_z )
    27122559                         ENDIF
    2713 
    2714 !
    2715 !--                      Check for ocean quantities
    2716                          IF ( .NOT. found  .AND.  ocean_mode )  THEN
    2717                             CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
    2718                                                            grid_x, grid_y,     &
    2719                                                            grid_z )
    2720                          ENDIF
    2721 !
    2722 !--                      Check for radiation quantities
    2723                          IF ( .NOT. found  .AND.  radiation )  THEN
    2724                             CALL radiation_define_netcdf_grid( do2d(av,i),     &
    2725                                                          found, grid_x, grid_y,&
    2726                                                          grid_z )
    2727                          ENDIF
    2728 
    2729 !
    2730 !--                      Check for SALSA quantities
    2731                          IF ( .NOT. found  .AND.  salsa )  THEN
    2732                             CALL salsa_define_netcdf_grid( do2d(av,i), found,  &
    2733                                                            grid_x, grid_y,     &
    2734                                                            grid_z )
    2735                          ENDIF
    2736 
    2737 !
    2738 !--                      Check for gust module quantities
    2739                          IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    2740                             CALL gust_define_netcdf_grid( do2d(av,i), found,   &
    2741                                                           grid_x, grid_y,      &
     2560!
     2561!--                      Check for chemistry quantities
     2562                         IF ( .NOT. found  .AND.  air_chemistry )  THEN
     2563                            CALL chem_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,       &
    27422564                                                          grid_z )
    27432565                         ENDIF
    2744 !
    2745 !--                      Check for biometeorology quantities
    2746                          IF ( .NOT. found  .AND.  biometeorology )  THEN
    2747                             CALL bio_define_netcdf_grid( do2d( av, i), found,  &
    2748                                                          grid_x, grid_y,       &
    2749                                                          grid_z )
    2750                          ENDIF
    2751 !
    2752 !--                      Check for chemistry quantities
    2753                          IF ( .NOT. found  .AND.  air_chemistry )  THEN
    2754                             CALL chem_define_netcdf_grid( do2d(av,i), found,   &
    2755                                                           grid_x, grid_y,      &
     2566
     2567                         IF ( .NOT. found )                                                        &
     2568                            CALL doq_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
     2569!
     2570!--                      Check for user-defined quantities
     2571                         IF ( .NOT. found  .AND.  user_module_enabled )  THEN
     2572                            CALL user_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,       &
    27562573                                                          grid_z )
    27572574                         ENDIF
    27582575
    2759                          IF ( .NOT. found )                                    &
    2760                             CALL doq_define_netcdf_grid(                       &
    2761                                                     do2d(av,i), found, grid_x, &
    2762                                                     grid_y, grid_z              )
    2763 !
    2764 !--                      Check for user-defined quantities
    2765                          IF ( .NOT. found  .AND.  user_module_enabled )  THEN
    2766                             CALL user_define_netcdf_grid( do2d(av,i), found,   &
    2767                                                           grid_x, grid_y,      &
    2768                                                           grid_z )
    2769                          ENDIF
    2770 
    27712576                         IF ( .NOT. found )  THEN
    2772                             WRITE ( message_string, * ) 'no grid defined for', &
    2773                                                 ' variable ', TRIM( do2d(av,i) )
    2774                             CALL message( 'define_netcdf_header', 'PA0244',    &
    2775                                           0, 1, 0, 6, 0 )
     2577                            WRITE ( message_string, * ) 'no grid defined for', ' variable ',       &
     2578                                                        TRIM( do2d(av,i) )
     2579                            CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
    27762580                         ENDIF
    27772581
     
    28042608!
    28052609!--                Define the grid
    2806                    CALL netcdf_create_var( id_set_xy(av), (/ id_x, id_y, id_z, &
    2807                                            id_dim_time_xy(av) /), do2d(av,i),  &
    2808                                            nc_precision(1), id_var_do2d(av,i), &
    2809                                            TRIM( do2d_unit(av,i) ),            &
    2810                                            do2d(av,i), 119, 120, 354, .TRUE. )
     2610                   CALL netcdf_create_var( id_set_xy(av), (/ id_x, id_y, id_z,                     &
     2611                                           id_dim_time_xy(av) /), do2d(av,i), nc_precision(1),     &
     2612                                           id_var_do2d(av,i), TRIM( do2d_unit(av,i) ), do2d(av,i), &
     2613                                           119, 120, 354, .TRUE. )
    28112614
    28122615                ENDIF
     
    28162619!
    28172620!--                Set no fill for every variable to increase performance.
    2818                    nc_stat = NF90_DEF_VAR_FILL( id_set_xy(av),     &
    2819                                                 id_var_do2d(av,i), &
    2820                                                 NF90_NOFILL, 0 )
     2621                   nc_stat = NF90_DEF_VAR_FILL( id_set_xy(av), id_var_do2d(av,i), NF90_NOFILL, 0 )
    28212622                   CALL netcdf_handle_error( 'netcdf_define_header', 533 )
    28222623!
    28232624!--                Set collective io operations for parallel io
    2824                    nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
    2825                                                   id_var_do2d(av,i), &
     2625                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av), id_var_do2d(av,i),                &
    28262626                                                  NF90_COLLECTIVE )
    28272627                   CALL netcdf_handle_error( 'netcdf_define_header', 448 )
     
    28412641
    28422642!
    2843 !--       Write the list of variables as global attribute (this is used by
    2844 !--       restart runs and by combine_plot_fields)
    2845           nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
    2846                                   var_list )
     2643!--       Write the list of variables as global attribute (this is used by restart runs and by
     2644!--       combine_plot_fields).
     2645          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', var_list )
    28472646          CALL netcdf_handle_error( 'netcdf_define_header', 121 )
    28482647
    28492648!
    2850 !--       Set general no fill, otherwise the performance drops significantly for
    2851 !--       parallel output.
     2649!--       Set general no fill, otherwise the performance drops significantly for parallel output.
    28522650          nc_stat = NF90_SET_FILL( id_set_xy(av), NF90_NOFILL, oldmode )
    28532651          CALL netcdf_handle_error( 'netcdf_define_header', 529 )
     
    28592657
    28602658!
    2861 !--       These data are only written by PE0 for parallel output to increase
    2862 !--       the performance.
     2659!--       These data are only written by PE0 for parallel output to increase the performance.
    28632660          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
    28642661
     
    28762673                ENDIF
    28772674             ENDDO
    2878              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu_xy(av), &
    2879                                      netcdf_data, start = (/ 1 /),    &
     2675             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu_xy(av),                              &
     2676                                     netcdf_data, start = (/ 1 /),                                 &
    28802677                                     count = (/ ns /) )
    28812678             CALL netcdf_handle_error( 'netcdf_define_header', 123 )
     
    28902687                ENDIF
    28912688             ENDDO
    2892              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zw_xy(av), &
    2893                                      netcdf_data, start = (/ 1 /),    &
     2689             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zw_xy(av),                              &
     2690                                     netcdf_data, start = (/ 1 /),                                 &
    28942691                                     count = (/ ns /) )
    28952692             CALL netcdf_handle_error( 'netcdf_define_header', 124 )
     
    29092706                ENDDO
    29102707
    2911                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zs_xy(av), &
    2912                                         netcdf_data(1:ns_do), start = (/ 1 /),    &
     2708                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zs_xy(av),                           &
     2709                                        netcdf_data(1:ns_do), start = (/ 1 /),                     &
    29132710                                        count = (/ ns_do /) )
    29142711                CALL netcdf_handle_error( 'netcdf_define_header', 124 )
     
    29192716!--          Write gridpoint number data
    29202717             netcdf_data(1:ns) = section(1:ns,1)
    2921              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_ind_z_xy(av), &
    2922                                      netcdf_data, start = (/ 1 /),       &
     2718             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_ind_z_xy(av),                           &
     2719                                     netcdf_data, start = (/ 1 /),                                 &
    29232720                                     count = (/ ns /) )
    29242721             CALL netcdf_handle_error( 'netcdf_define_header', 125 )
     
    29282725!
    29292726!--          Write the cross section height u*, t*
    2930              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu1_xy(av), &
    2931                                      (/ zu(nzb+1) /), start = (/ 1 /), &
     2727             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu1_xy(av),                             &
     2728                                     (/ zu(nzb+1) /), start = (/ 1 /),                             &
    29322729                                     count = (/ 1 /) )
    29332730             CALL netcdf_handle_error( 'netcdf_define_header', 126 )
     
    29412738             ENDDO
    29422739
    2943              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av), &
    2944                                      netcdf_data, start = (/ 1 /),   &
     2740             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av),                               &
     2741                                     netcdf_data, start = (/ 1 /),                                 &
    29452742                                     count = (/ nx+1 /) )
    29462743             CALL netcdf_handle_error( 'netcdf_define_header', 127 )
     
    29502747             ENDDO
    29512748
    2952              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_xu_xy(av), &
    2953                                      netcdf_data, start = (/ 1 /),    &
     2749             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_xu_xy(av),                              &
     2750                                     netcdf_data, start = (/ 1 /),                                 &
    29542751                                     count = (/ nx+1 /) )
    29552752             CALL netcdf_handle_error( 'netcdf_define_header', 367 )
     
    29652762             ENDDO
    29662763
    2967              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av), &
    2968                                      netcdf_data, start = (/ 1 /),   &
     2764             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av),                               &
     2765                                     netcdf_data, start = (/ 1 /),                                 &
    29692766                                     count = (/ ny+1 /))
    29702767             CALL netcdf_handle_error( 'netcdf_define_header', 128 )
     
    29742771             ENDDO
    29752772
    2976              nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_yv_xy(av), &
    2977                                      netcdf_data, start = (/ 1 /),    &
     2773             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_yv_xy(av),                              &
     2774                                     netcdf_data, start = (/ 1 /),                                 &
    29782775                                     count = (/ ny+1 /))
    29792776             CALL netcdf_handle_error( 'netcdf_define_header', 368 )
     
    30052802
    30062803                   DO  i = 0, nx
    3007                      netcdf_data(i) = init_model%origin_x                      &
    3008                                     + cos_rot_angle * ( i + shift_x ) * dx
     2804                     netcdf_data(i) = init_model%origin_x + cos_rot_angle * ( i + shift_x ) * dx
    30092805                   ENDDO
    30102806
    3011                    nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),&
    3012                                            netcdf_data, start = (/ 1 /),       &
     2807                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),                    &
     2808                                           netcdf_data, start = (/ 1 /),                           &
    30132809                                           count = (/ nx+1 /) )
    30142810                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    30352831
    30362832                   DO  j = 0, ny
    3037                       netcdf_data(j) = init_model%origin_y                     &
    3038                                      + cos_rot_angle * ( j + shift_y ) * dy
     2833                      netcdf_data(j) = init_model%origin_y + cos_rot_angle * ( j + shift_y ) * dy
    30392834                   ENDDO
    30402835
    3041                    nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),&
    3042                                            netcdf_data, start = (/ 1 /),       &
     2836                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),                    &
     2837                                           netcdf_data, start = (/ 1 /),                           &
    30432838                                           count = (/ ny+1 /) )
    30442839                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    30712866                  DO  j = 0, ny
    30722867                     DO  i = 0, nx
    3073                         netcdf_data_2d(i,j) = init_model%origin_x                   &
    3074                                             + cos_rot_angle * ( i + shift_x ) * dx  &
    3075                                             + sin_rot_angle * ( j + shift_y ) * dy
     2868                        netcdf_data_2d(i,j) = init_model%origin_x                                  &
     2869                                              + cos_rot_angle * ( i + shift_x ) * dx               &
     2870                                              + sin_rot_angle * ( j + shift_y ) * dy
    30762871                     ENDDO
    30772872                  ENDDO
    30782873
    3079                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),  &
    3080                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     2874                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),                     &
     2875                                          netcdf_data_2d, start = (/ 1, 1 /),                      &
    30812876                                          count = (/ nx+1, ny+1 /) )
    30822877                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    30842879                  DO  j = 0, ny
    30852880                     DO  i = 0, nx
    3086                         netcdf_data_2d(i,j) = init_model%origin_y                   &
    3087                                             - sin_rot_angle * ( i + shift_x ) * dx  &
    3088                                             + cos_rot_angle * ( j + shift_y ) * dy
     2881                        netcdf_data_2d(i,j) = init_model%origin_y                                  &
     2882                                              - sin_rot_angle * ( i + shift_x ) * dx               &
     2883                                              + cos_rot_angle * ( j + shift_y ) * dy
    30892884                     ENDDO
    30902885                  ENDDO
    30912886
    3092                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),  &
    3093                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     2887                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),                     &
     2888                                          netcdf_data_2d, start = (/ 1, 1 /),                      &
    30942889                                          count = (/ nx+1, ny+1 /) )
    30952890                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    31262921                DO  j = nys, nyn
    31272922                   DO  i = nxl, nxr
    3128                       eutm = init_model%origin_x                   &
    3129                            + cos_rot_angle * ( i + shift_x ) * dx  &
    3130                            + sin_rot_angle * ( j + shift_y ) * dy
    3131                       nutm = init_model%origin_y                   &
    3132                            - sin_rot_angle * ( i + shift_x ) * dx  &
    3133                            + cos_rot_angle * ( j + shift_y ) * dy
    3134 
    3135                       CALL  convert_utm_to_geographic( crs_list,          &
    3136                                                        eutm, nutm,        &
    3137                                                        lon(i,j), lat(i,j) )
     2923                      eutm = init_model%origin_x                                                   &
     2924                             + cos_rot_angle * ( i + shift_x ) * dx                                &
     2925                             + sin_rot_angle * ( j + shift_y ) * dy
     2926                      nutm = init_model%origin_y                                                   &
     2927                             - sin_rot_angle * ( i + shift_x ) * dx                                &
     2928                             + cos_rot_angle * ( j + shift_y ) * dy
     2929
     2930                      CALL  convert_utm_to_geographic( crs_list, eutm, nutm, lon(i,j), lat(i,j) )
    31382931                   ENDDO
    31392932                ENDDO
    31402933
    3141                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lon_xy(k,av), &
    3142                                      lon, start = (/ nxl+1, nys+1 /),       &
    3143                                      count = (/ nxr-nxl+1, nyn-nys+1 /) )
     2934                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lon_xy(k,av),                        &
     2935                                        lon, start = (/ nxl+1, nys+1 /),                           &
     2936                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    31442937                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    31452938
    3146                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lat_xy(k,av), &
    3147                                      lat, start = (/ nxl+1, nys+1 /),       &
    3148                                      count = (/ nxr-nxl+1, nyn-nys+1 /) )
     2939                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lat_xy(k,av),                        &
     2940                                        lat, start = (/ nxl+1, nys+1 /),                           &
     2941                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    31492942                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    31502943             ENDDO
     
    31572950!--       In case of non-flat topography write height information. Only for
    31582951!--       parallel netcdf output.
    3159           IF ( TRIM( topography ) /= 'flat'  .AND.                             &
    3160                netcdf_data_format > 4  )  THEN
     2952          IF ( TRIM( topography ) /= 'flat'  .AND.  netcdf_data_format > 4  )  THEN
    31612953
    31622954!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    3163 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    3164 !                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
    3165 !                                        start = (/ nxl+1, nys+1 /),            &
     2955!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),                         &
     2956!                                        zu_s_inner(nxl:nxr+1,nys:nyn),                             &
     2957!                                        start = (/ nxl+1, nys+1 /),                                &
    31662958!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
    31672959!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    3168 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    3169 !                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
    3170 !                                        start = (/ nxl+1, nys+1 /),            &
     2960!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),                         &
     2961!                                        zu_s_inner(nxl:nxr,nys:nyn+1),                             &
     2962!                                        start = (/ nxl+1, nys+1 /),                                &
    31712963!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
    31722964!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    3173 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    3174 !                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
    3175 !                                        start = (/ nxl+1, nys+1 /),            &
     2965!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),                         &
     2966!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),                           &
     2967!                                        start = (/ nxl+1, nys+1 /),                                &
    31762968!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
    31772969!             ELSE
    3178                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
    3179                                         zu_s_inner(nxl:nxr,nys:nyn),           &
    3180                                         start = (/ nxl+1, nys+1 /),            &
     2970                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),                         &
     2971                                        zu_s_inner(nxl:nxr,nys:nyn),                               &
     2972                                        start = (/ nxl+1, nys+1 /),                                &
    31812973                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    31822974!             ENDIF
     
    31842976
    31852977!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    3186 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    3187 !                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
    3188 !                                        start = (/ nxl+1, nys+1 /),            &
     2978!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),                         &
     2979!                                        zw_w_inner(nxl:nxr+1,nys:nyn),                             &
     2980!                                        start = (/ nxl+1, nys+1 /),                                &
    31892981!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
    31902982!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    3191 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    3192 !                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
    3193 !                                        start = (/ nxl+1, nys+1 /),            &
     2983!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),                         &
     2984!                                        zw_w_inner(nxl:nxr,nys:nyn+1),                             &
     2985!                                        start = (/ nxl+1, nys+1 /),                                &
    31942986!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
    31952987!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    3196 !                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    3197 !                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
    3198 !                                        start = (/ nxl+1, nys+1 /),            &
     2988!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),                         &
     2989!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),                           &
     2990!                                        start = (/ nxl+1, nys+1 /),                                &
    31992991!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
    32002992!             ELSE
    3201                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
    3202                                         zw_w_inner(nxl:nxr,nys:nyn),           &
    3203                                         start = (/ nxl+1, nys+1 /),            &
     2993                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),                         &
     2994                                        zw_w_inner(nxl:nxr,nys:nyn),                               &
     2995                                        start = (/ nxl+1, nys+1 /),                                &
    32042996                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    32052997!             ENDIF
     
    32123004!
    32133005!--       Get the list of variables and compare with the actual run.
    3214 !--       First var_list_old has to be reset, since GET_ATT does not assign
    3215 !--       trailing blanks.
     3006!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    32163007          var_list_old = ' '
    3217           nc_stat = NF90_GET_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
    3218                                   var_list_old )
     3008          nc_stat = NF90_GET_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', var_list_old )
    32193009          CALL netcdf_handle_error( 'netcdf_define_header', 129 )
    32203010
    32213011          var_list = ';'
    32223012          i = 1
    3223           DO WHILE ( do2d(av,i)(1:1) /= ' ' )
     3013          DO  WHILE ( do2d(av,i)(1:1) /= ' ' )
    32243014             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
    32253015                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
     
    32353025
    32363026          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    3237              message_string = 'netCDF file for cross-sections ' //           &
    3238                               TRIM( var ) // ' from previous run found,' //  &
    3239                               '&but this file cannot be extended due to' //  &
    3240                               ' variable mismatch.' //                       &
    3241                               '&New file is created instead.'
     3027             message_string = 'netCDF file for cross-sections ' //                                 &
     3028                              TRIM( var ) // ' from previous run found,' //                        &
     3029                              '&but this file cannot be extended due to' //                        &
     3030                              ' variable mismatch.' // '&New file is created instead.'
    32423031             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
    32433032             extend = .FALSE.
     
    32483037!--       Calculate the number of current sections
    32493038          ns = 1
    3250           DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
     3039          DO  WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
    32513040             ns = ns + 1
    32523041          ENDDO
     
    32583047          CALL netcdf_handle_error( 'netcdf_define_header', 130 )
    32593048
    3260           nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_zu_xy(av), &
     3049          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_zu_xy(av),                        &
    32613050                                           dimids = id_dim_zu_xy_old )
    32623051          CALL netcdf_handle_error( 'netcdf_define_header', 131 )
    32633052          id_dim_zu_xy(av) = id_dim_zu_xy_old(1)
    32643053
    3265           nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_zu_xy(av), &
    3266                                             len = ns_old )
     3054          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_zu_xy(av), LEN = ns_old )
    32673055          CALL netcdf_handle_error( 'netcdf_define_header', 132 )
    32683056
    32693057          IF ( ns /= ns_old )  THEN
    3270              message_string = 'netCDF file for cross-sections ' //          &
    3271                               TRIM( var ) // ' from previous run found,' // &
    3272                               '&but this file cannot be extended due to' // &
    3273                               ' mismatch in number of' //                   &
    3274                               ' cross sections.' //                         &
     3058             message_string = 'netCDF file for cross-sections ' //                                 &
     3059                              TRIM( var ) // ' from previous run found,' //                        &
     3060                              '&but this file cannot be extended due to' //                        &
     3061                              ' mismatch in number of' // ' cross sections.' //                    &
    32753062                              '&New file is created instead.'
    32763063             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
     
    32893076             IF ( section(i,1) /= -1 )  THEN
    32903077                IF ( zu(section(i,1)) /= netcdf_data(i) )  THEN
    3291                    message_string = 'netCDF file for cross-sections ' //       &
    3292                                TRIM( var ) // ' from previous run found,' //   &
    3293                                ' but this file cannot be extended' //          &
    3294                                ' due to mismatch in cross' //                  &
    3295                                ' section levels.' //                           &
    3296                                ' New file is created instead.'
    3297                    CALL message( 'define_netcdf_header', 'PA0251',             &
    3298                                                                  0, 1, 0, 6, 0 )
     3078                   message_string = 'netCDF file for cross-sections ' //                           &
     3079                                     TRIM( var ) // ' from previous run found,' //                 &
     3080                                     ' but this file cannot be extended' //                        &
     3081                                     ' due to mismatch in cross' // ' section levels.' //          &
     3082                                     ' New file is created instead.'
     3083                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    32993084                   extend = .FALSE.
    33003085                   RETURN
     
    33023087             ELSE
    33033088                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    3304                    message_string = 'netCDF file for cross-sections ' //       &
    3305                                TRIM( var ) // ' from previous run found,' //   &
    3306                                ' but this file cannot be extended' //          &
    3307                                ' due to mismatch in cross' //                  &
    3308                                ' section levels.' //                           &
    3309                                ' New file is created instead.'
    3310                    CALL message( 'define_netcdf_header', 'PA0251',             &
    3311                                                                  0, 1, 0, 6, 0 )
     3089                   message_string = 'netCDF file for cross-sections ' //                           &
     3090                                     TRIM( var ) // ' from previous run found,' //                 &
     3091                                     ' but this file cannot be extended' //                        &
     3092                                     ' due to mismatch in cross' // ' section levels.' //          &
     3093                                     ' New file is created instead.'
     3094                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    33123095                   extend = .FALSE.
    33133096                   RETURN
     
    33193102
    33203103!
    3321 !--       Get the id of the time coordinate (unlimited coordinate) and its
    3322 !--       last index on the file. The next time level is do2d..count+1.
    3323 !--       The current time must be larger than the last output time
    3324 !--       on the file.
     3104!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     3105!--       The next time level is do2d..count+1.
     3106!--       The current time must be larger than the last output time on the file.
    33253107          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'time', id_var_time_xy(av) )
    33263108          CALL netcdf_handle_error( 'netcdf_define_header', 134 )
    33273109
    3328           nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_time_xy(av), &
     3110          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_time_xy(av),                      &
    33293111                                           dimids = id_dim_time_old )
    33303112          CALL netcdf_handle_error( 'netcdf_define_header', 135 )
    33313113          id_dim_time_xy(av) = id_dim_time_old(1)
    33323114
    3333           nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_time_xy(av), &
    3334                                             len = ntime_count )
     3115          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_time_xy(av), LEN = ntime_count )
    33353116          CALL netcdf_handle_error( 'netcdf_define_header', 136 )
    33363117
    33373118!
    3338 !--       For non-parallel output use the last output time level of the netcdf
    3339 !--       file because the time dimension is unlimited. In case of parallel
    3340 !--       output the variable ntime_count could get the value of 9*10E36 because
    3341 !--       the time dimension is limited.
     3119!--       For non-parallel output use the last output time level of the netcdf file because the time
     3120!--       dimension is unlimited. In case of parallel output the variable ntime_count could get the
     3121!--       value of 9*10E36 because the time dimension is limited.
    33423122          IF ( netcdf_data_format < 5 ) do2d_xy_time_count(av) = ntime_count
    33433123
    3344           nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_time_xy(av),           &
    3345                                   last_time_coordinate,                        &
    3346                                   start = (/ do2d_xy_time_count(av) /),        &
     3124          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_time_xy(av),                               &
     3125                                  last_time_coordinate,                                            &
     3126                                  start = (/ do2d_xy_time_count(av) /),                            &
    33473127                                  count = (/ 1 /) )
    33483128          CALL netcdf_handle_error( 'netcdf_define_header', 137 )
    33493129
    33503130          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    3351              message_string = 'netCDF file for cross sections ' //             &
    3352                               TRIM( var ) // ' from previous run found,' //    &
    3353                               '&but this file cannot be extended becaus' //    &
    3354                               'e the current output time' //                   &
    3355                               '&is less or equal than the last output t' //    &
    3356                               'ime on this file.' //                           &
     3131             message_string = 'netCDF file for cross sections ' //                                 &
     3132                              TRIM( var ) // ' from previous run found,' //                        &
     3133                              '&but this file cannot be extended because' //                       &
     3134                              ' the current output time' //                                        &
     3135                              '&is less or equal than the last output time' // ' on this file.' // &
    33573136                              '&New file is created instead.'
    33583137             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
     
    33643143          IF ( netcdf_data_format > 4 )  THEN
    33653144!
    3366 !--          Check if the needed number of output time levels is increased
    3367 !--          compared to the number of time levels in the existing file.
     3145!--          Check if the needed number of output time levels is increased compared to the number of
     3146!--          time levels in the existing file.
    33683147             IF ( ntdim_2d_xy(av) > ntime_count )  THEN
    3369                 message_string = 'netCDF file for cross sections ' //          &
    3370                                  TRIM( var ) // ' from previous run found,' // &
    3371                                  '&but this file cannot be extended becaus' // &
    3372                                  'e the number of output time levels has b' // &
    3373                                  'een increased compared to the previous s' // &
    3374                                  'imulation.' //                               &
    3375                                  '&New file is created instead.'
     3148                message_string = 'netCDF file for cross sections ' //                              &
     3149                                 TRIM( var ) // ' from previous run found,' //                     &
     3150                                 '&but this file cannot be extended becaus' //                     &
     3151                                 'e the number of output time levels has b' //                     &
     3152                                 'een increased compared to the previous s' //                     &
     3153                                 'imulation.' // '&New file is created instead.'
    33763154                CALL message( 'define_netcdf_header', 'PA0389', 0, 1, 0, 6, 0 )
    33773155                do2d_xy_time_count(av) = 0
     
    33803158!--             Recalculate the needed time levels for the new file.
    33813159                IF ( av == 0 )  THEN
    3382                    ntdim_2d_xy(0) = CEILING(                            &
    3383                            ( end_time - MAX( skip_time_do2d_xy,         &
    3384                                              simulated_time_at_begin )  &
    3385                            ) / dt_do2d_xy )
     3160                   ntdim_2d_xy(0) = CEILING( ( end_time - MAX( skip_time_do2d_xy,                  &
     3161                                                               simulated_time_at_begin )           &
     3162                                             ) / dt_do2d_xy )
    33863163                   IF ( do2d_at_begin )  ntdim_2d_xy(0) = ntdim_2d_xy(0) + 1
    33873164                ELSE
    3388                    ntdim_2d_xy(1) = CEILING(                            &
    3389                            ( end_time - MAX( skip_time_data_output_av,  &
    3390                                              simulated_time_at_begin )  &
    3391                            ) / dt_data_output_av )
     3165                   ntdim_2d_xy(1) = CEILING( ( end_time - MAX( skip_time_data_output_av,           &
     3166                                                               simulated_time_at_begin )           &
     3167                                             ) / dt_data_output_av )
    33923168                ENDIF
    33933169                RETURN
     
    33993175!--       Now get the variable ids.
    34003176          i = 1
    3401           DO WHILE ( do2d(av,i)(1:1) /= ' ' )
     3177          DO  WHILE ( do2d(av,i)(1:1) /= ' ' )
    34023178             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
    3403                 nc_stat = NF90_INQ_VARID( id_set_xy(av), do2d(av,i), &
    3404                                           id_var_do2d(av,i) )
     3179                nc_stat = NF90_INQ_VARID( id_set_xy(av), do2d(av,i), id_var_do2d(av,i) )
    34053180                CALL netcdf_handle_error( 'netcdf_define_header', 138 )
    34063181#if defined( __netcdf4_parallel )
     
    34083183!--             Set collective io operations for parallel io
    34093184                IF ( netcdf_data_format > 4 )  THEN
    3410                    nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
    3411                                                   id_var_do2d(av,i), &
     3185                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av), id_var_do2d(av,i),                &
    34123186                                                  NF90_COLLECTIVE )
    34133187                   CALL netcdf_handle_error( 'netcdf_define_header', 454 )
     
    34193193
    34203194!
    3421 !--       Update the title attribute on file
    3422 !--       In order to avoid 'data mode' errors if updated attributes are larger
    3423 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    3424 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    3425 !--       performance loss due to data copying; an alternative strategy would be
    3426 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     3195!--       Update the title attribute on file.
     3196!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     3197!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     3198!--       calls. This implies a possible performance loss due to data copying; an alternative
     3199!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    34273200          IF ( av == 0 )  THEN
    34283201             time_average_text = ' '
    34293202          ELSE
    3430              WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
    3431                                                             averaging_interval
     3203             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' ) averaging_interval
    34323204          ENDIF
    34333205          nc_stat = NF90_REDEF( id_set_xy(av) )
    34343206          CALL netcdf_handle_error( 'netcdf_define_header', 431 )
    3435           nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title',         &
    3436                                   TRIM( run_description_header ) //            &
    3437                                   TRIM( time_average_text ) )
     3207          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title',                             &
     3208                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    34383209          CALL netcdf_handle_error( 'netcdf_define_header', 139 )
    34393210          nc_stat = NF90_ENDDEF( id_set_xy(av) )
    34403211          CALL netcdf_handle_error( 'netcdf_define_header', 432 )
    3441           message_string = 'netCDF file for cross-sections ' //                &
    3442                             TRIM( var ) // ' from previous run found.' //      &
     3212          message_string = 'netCDF file for cross-sections ' //                                    &
     3213                            TRIM( var ) // ' from previous run found.' //                          &
    34433214                           '&This file will be extended.'
    34443215          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
     
    34503221!--       Define some global attributes of the dataset
    34513222          IF ( av == 0 )  THEN
    3452              CALL netcdf_create_global_atts( id_set_xz(av), 'xz', TRIM( run_description_header ), 140 )
     3223             CALL netcdf_create_global_atts( id_set_xz(av), 'xz', TRIM( run_description_header ),  &
     3224                                             140 )
    34533225             time_average_text = ' '
    34543226          ELSE
    3455              CALL netcdf_create_global_atts( id_set_xz(av), 'xz_av', TRIM( run_description_header ), 140 )
     3227             CALL netcdf_create_global_atts( id_set_xz(av), 'xz_av',                               &
     3228                                             TRIM( run_description_header ), 140 )
    34563229             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    3457              nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'time_avg',   &
     3230             nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'time_avg',                       &
    34583231                                     TRIM( time_average_text ) )
    34593232             CALL netcdf_handle_error( 'netcdf_define_header', 141 )
     
    34623235!
    34633236!--       Define time coordinate for xz sections.
    3464 !--       For parallel output the time dimensions has to be limited, otherwise
    3465 !--       the performance drops significantly.
     3237!--       For parallel output the time dimensions has to be limited, otherwise the performance drops
     3238!--       significantly.
    34663239          IF ( netcdf_data_format < 5 )  THEN
    3467              CALL netcdf_create_dim( id_set_xz(av), 'time', NF90_UNLIMITED,    &
    3468                                      id_dim_time_xz(av), 142 )
     3240             CALL netcdf_create_dim( id_set_xz(av), 'time', NF90_UNLIMITED, id_dim_time_xz(av),    &
     3241                                     142 )
    34693242          ELSE
    3470              CALL netcdf_create_dim( id_set_xz(av), 'time', ntdim_2d_xz(av),   &
    3471                                      id_dim_time_xz(av), 525 )
    3472           ENDIF
    3473 
    3474           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_time_xz(av) /),     &
    3475                                   'time', NF90_DOUBLE, id_var_time_xz(av),     &
    3476                                   'seconds', 'time', 143, 144, 000 )
     3243             CALL netcdf_create_dim( id_set_xz(av), 'time', ntdim_2d_xz(av), id_dim_time_xz(av),   &
     3244                                     525 )
     3245          ENDIF
     3246
     3247          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_time_xz(av) /), 'time', NF90_DOUBLE,    &
     3248                                  id_var_time_xz(av), 'seconds', 'time', 143, 144, 000 )
    34773249          CALL netcdf_create_att( id_set_xz(av), id_var_time_xz(av), 'standard_name', 'time', 000)
    34783250          CALL netcdf_create_att( id_set_xz(av), id_var_time_xz(av), 'axis', 'T', 000)
     
    34923264!
    34933265!--       Define y-axis (for scalar position)
    3494           CALL netcdf_create_dim( id_set_xz(av), 'y_xz', ns, id_dim_y_xz(av),  &
    3495                                   145 )
    3496           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /),        &
    3497                                   'y_xz', NF90_DOUBLE, id_var_y_xz(av),        &
    3498                                   'meters', '', 146, 147, 000 )
    3499           CALL netcdf_create_att( id_set_xz(av), id_var_y_xz(av), 'axis',      &
    3500                                   'Y', 000)
     3266          CALL netcdf_create_dim( id_set_xz(av), 'y_xz', ns, id_dim_y_xz(av), 145 )
     3267          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /), 'y_xz', NF90_DOUBLE,       &
     3268                                 id_var_y_xz(av), 'meters', '', 146, 147, 000 )
     3269          CALL netcdf_create_att( id_set_xz(av), id_var_y_xz(av), 'axis', 'Y', 000)
    35013270!
    35023271!--       Define y-axis (for v position)
    3503           CALL netcdf_create_dim( id_set_xz(av), 'yv_xz', ns,                  &
    3504                                   id_dim_yv_xz(av), 369 )
    3505           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_yv_xz(av) /),       &
    3506                                   'yv_xz', NF90_DOUBLE, id_var_yv_xz(av),      &
    3507                                   'meters', '', 370, 371, 000 )
    3508           CALL netcdf_create_att( id_set_xz(av), id_var_yv_xz(av), 'axis',     &
    3509                                   'Y', 000)
    3510 !
    3511 !--       Define a variable to store the layer indices of the vertical cross
    3512 !--       sections
    3513           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /),        &
    3514                                   'ind_y_xz', NF90_DOUBLE,                     &
    3515                                   id_var_ind_y_xz(av), 'gridpoints', '', 148,  &
    3516                                   149, 000 )
     3272          CALL netcdf_create_dim( id_set_xz(av), 'yv_xz', ns, id_dim_yv_xz(av), 369 )
     3273          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_yv_xz(av) /), 'yv_xz', NF90_DOUBLE,     &
     3274                                  id_var_yv_xz(av), 'meters', '', 370, 371, 000 )
     3275          CALL netcdf_create_att( id_set_xz(av), id_var_yv_xz(av), 'axis', 'Y', 000)
     3276!
     3277!--       Define a variable to store the layer indices of the vertical cross sections
     3278          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /), 'ind_y_xz', NF90_DOUBLE,   &
     3279                                  id_var_ind_y_xz(av), 'gridpoints', '', 148, 149, 000 )
    35173280!
    35183281!--       Define x-axis (for scalar position)
    3519           CALL netcdf_create_dim( id_set_xz(av), 'x', nx+1, id_dim_x_xz(av),   &
    3520                                   150 )
    3521           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_x_xz(av) /), 'x',   &
    3522                                   NF90_DOUBLE, id_var_x_xz(av), 'meters', '',  &
    3523                                   151, 152, 000 )
    3524           CALL netcdf_create_att( id_set_xz(av), id_var_x_xz(av), 'axis',      &
    3525                                   'X', 000)
     3282          CALL netcdf_create_dim( id_set_xz(av), 'x', nx+1, id_dim_x_xz(av), 150 )
     3283          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_x_xz(av) /), 'x', NF90_DOUBLE,          &
     3284                                  id_var_x_xz(av), 'meters', '', 151, 152, 000 )
     3285          CALL netcdf_create_att( id_set_xz(av), id_var_x_xz(av), 'axis', 'X', 000)
    35263286!
    35273287!--       Define x-axis (for u position)
    3528           CALL netcdf_create_dim( id_set_xz(av), 'xu', nx+1, id_dim_xu_xz(av), &
    3529                                   372 )
    3530           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_xu_xz(av) /), 'xu', &
    3531                                   NF90_DOUBLE, id_var_xu_xz(av), 'meters', '', &
    3532                                   373, 374, 000 )
    3533           CALL netcdf_create_att( id_set_xz(av), id_var_xu_xz(av), 'axis',     &
    3534                                   'X', 000)
    3535                                  
     3288          CALL netcdf_create_dim( id_set_xz(av), 'xu', nx+1, id_dim_xu_xz(av), 372 )
     3289          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_xu_xz(av) /), 'xu', NF90_DOUBLE,        &
     3290                                  id_var_xu_xz(av), 'meters', '', 373, 374, 000 )
     3291          CALL netcdf_create_att( id_set_xz(av), id_var_xu_xz(av), 'axis', 'X', 000)
     3292
    35363293!
    35373294!--       Define the three z-axes (zu, zw, and zs)
    3538           CALL netcdf_create_dim( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av), &
    3539                                   153 )
    3540           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zu_xz(av) /), 'zu', &
    3541                                   NF90_DOUBLE, id_var_zu_xz(av), 'meters', '', &
    3542                                   154, 155, 000 )
    3543           CALL netcdf_create_att( id_set_xz(av), id_var_zu_xz(av), 'axis',     &
    3544                                   'Z', 000)
    3545                                  
    3546           CALL netcdf_create_dim( id_set_xz(av), 'zw', nz+2, id_dim_zw_xz(av), &
    3547                                   156 )
    3548           CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zw_xz(av) /), 'zw', &
    3549                                   NF90_DOUBLE, id_var_zw_xz(av), 'meters', '', &
    3550                                   157, 158, 000 )
    3551           CALL netcdf_create_att( id_set_xz(av), id_var_zw_xz(av), 'axis',     &
    3552                                   'Z', 000)
     3295          CALL netcdf_create_dim( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av), 153 )
     3296          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zu_xz(av) /), 'zu', NF90_DOUBLE,        &
     3297                                  id_var_zu_xz(av), 'meters', '', 154, 155, 000 )
     3298          CALL netcdf_create_att( id_set_xz(av), id_var_zu_xz(av), 'axis', 'Z', 000)
     3299
     3300          CALL netcdf_create_dim( id_set_xz(av), 'zw', nz+2, id_dim_zw_xz(av), 156 )
     3301          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zw_xz(av) /), 'zw', NF90_DOUBLE,        &
     3302                                  id_var_zw_xz(av), 'meters', '', 157, 158, 000 )
     3303          CALL netcdf_create_att( id_set_xz(av), id_var_zw_xz(av), 'axis', 'Z', 000)
    35533304!
    35543305!--       Define UTM and geographic coordinates
    3555           CALL define_geo_coordinates( id_set_xz(av),         &
    3556                   (/ id_dim_x_xz(av), id_dim_xu_xz(av) /),    &
    3557                   (/ id_dim_y_xz(av), id_dim_yv_xz(av) /),    &
    3558                   id_var_eutm_xz(:,av), id_var_nutm_xz(:,av), &
    3559                   id_var_lat_xz(:,av), id_var_lon_xz(:,av)    )
     3306          CALL define_geo_coordinates( id_set_xz(av),                                              &
     3307                                       (/ id_dim_x_xz(av), id_dim_xu_xz(av) /),                    &
     3308                                       (/ id_dim_y_xz(av), id_dim_yv_xz(av) /),                    &
     3309                                       id_var_eutm_xz(:,av), id_var_nutm_xz(:,av),                &
     3310                                       id_var_lat_xz(:,av), id_var_lon_xz(:,av)    )
    35603311!
    35613312!--       Define coordinate-reference system
     
    35643315          IF ( land_surface )  THEN
    35653316
    3566              CALL netcdf_create_dim( id_set_xz(av), 'zs', nzs,                 &
    3567                                      id_dim_zs_xz(av), 542 )
    3568              CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zs_xz(av) /),    &
    3569                                      'zs', NF90_DOUBLE, id_var_zs_xz(av),      &
    3570                                      'meters', '', 543, 544, 000 )
    3571              CALL netcdf_create_att( id_set_xz(av), id_var_zs_xz(av), 'axis',  &
    3572                                      'Z', 000)
     3317             CALL netcdf_create_dim( id_set_xz(av), 'zs', nzs, id_dim_zs_xz(av), 542 )
     3318             CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zs_xz(av) /), 'zs', NF90_DOUBLE,     &
     3319                                     id_var_zs_xz(av), 'meters', '', 543, 544, 000 )
     3320             CALL netcdf_create_att( id_set_xz(av), id_var_zs_xz(av), 'axis', 'Z', 000)
    35733321
    35743322          ENDIF
     
    36253373!--                   Check for land surface quantities
    36263374                      IF ( land_surface )  THEN
    3627                          CALL lsm_define_netcdf_grid( do2d(av,i), found,       &
    3628                                                       grid_x, grid_y, grid_z )
     3375                         CALL lsm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36293376                      ENDIF
    36303377
    36313378                      IF ( .NOT. found )  THEN
    3632                          CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
    3633                                                       grid_x, grid_y, grid_z )
     3379                         CALL tcm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36343380                      ENDIF
    36353381
     
    36373383!--                   Check for ocean quantities
    36383384                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
    3639                          CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
    3640                                                         grid_x, grid_y, grid_z )
     3385                         CALL ocean_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36413386                      ENDIF
    36423387!
    36433388!--                   Check for radiation quantities
    36443389                      IF ( .NOT. found  .AND.  radiation )  THEN
    3645                          CALL radiation_define_netcdf_grid( do2d(av,i), found, &
    3646                                                             grid_x, grid_y,    &
     3390                         CALL radiation_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,     &
    36473391                                                            grid_z )
    36483392                      ENDIF
     
    36503394!--                   Check for SALSA quantities
    36513395                      IF ( .NOT. found  .AND.  salsa )  THEN
    3652                          CALL salsa_define_netcdf_grid( do2d(av,i), found,     &
    3653                                                         grid_x, grid_y, grid_z )
     3396                         CALL salsa_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36543397                      ENDIF
    36553398
     
    36573400!--                   Check for gust module quantities
    36583401                      IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    3659                          CALL gust_define_netcdf_grid( do2d(av,i), found,      &
    3660                                                        grid_x, grid_y, grid_z )
     3402                         CALL gust_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36613403                      ENDIF
    36623404
     
    36643406!--                   Check for chemistry quantities
    36653407                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
    3666                          CALL chem_define_netcdf_grid( do2d(av,i), found,      &
    3667                                                        grid_x, grid_y,         &
    3668                                                        grid_z )
     3408                         CALL chem_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36693409                      ENDIF
    36703410
    3671                       IF ( .NOT. found )                                       &
    3672                          CALL doq_define_netcdf_grid( do2d(av,i), found,       &
    3673                                                       grid_x, grid_y, grid_z )
     3411                      IF ( .NOT. found )                                                           &
     3412                         CALL doq_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36743413
    36753414!
    36763415!--                   Check for user-defined quantities
    36773416                      IF ( .NOT. found  .AND.  user_module_enabled )  THEN
    3678                          CALL user_define_netcdf_grid( do2d(av,i), found,      &
    3679                                                        grid_x, grid_y, grid_z )
     3417                         CALL user_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    36803418                      ENDIF
    36813419
    36823420                      IF ( .NOT. found )  THEN
    3683                          WRITE ( message_string, * ) 'no grid defined for',    &
    3684                                                 ' variable ', TRIM( do2d(av,i) )
    3685                          CALL message( 'define_netcdf_header', 'PA0244',       &
    3686                                        0, 1, 0, 6, 0 )
     3421                         WRITE ( message_string, * ) 'no grid defined for', ' variable ',          &
     3422                                                     TRIM( do2d(av,i) )
     3423                         CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
    36873424                      ENDIF
    36883425
     
    37133450!
    37143451!--             Define the grid
    3715                 CALL netcdf_create_var( id_set_xz(av), (/ id_x, id_y, id_z,    &
    3716                                         id_dim_time_xz(av) /), do2d(av,i),     &
    3717                                         nc_precision(2), id_var_do2d(av,i),    &
    3718                                         TRIM( do2d_unit(av,i) ), do2d(av,i),   &
    3719                                         159, 160, 355, .TRUE. )
     3452                CALL netcdf_create_var( id_set_xz(av), (/ id_x, id_y, id_z, id_dim_time_xz(av) /), &
     3453                                        do2d(av,i), nc_precision(2), id_var_do2d(av,i),            &
     3454                                        TRIM( do2d_unit(av,i) ), do2d(av,i), 159, 160, 355, .TRUE. )
    37203455
    37213456#if defined( __netcdf4_parallel )
     
    37293464                   CALL netcdf_handle_error( 'netcdf_define_header', 534 )
    37303465!
    3731 !--                Set independent io operations for parallel io. Collective io
    3732 !--                is only allowed in case of a 1d-decomposition along x,
    3733 !--                because otherwise, not all PEs have output data.
     3466!--                Set independent io operations for parallel io. Collective io is only allowed in
     3467!--                case of a 1d-decomposition along x, because otherwise, not all PEs have output
     3468!--                data.
    37343469                   IF ( npey == 1 )  THEN
    3735                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
    3736                                                      id_var_do2d(av,i), &
     3470                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3471                                                     id_var_do2d(av,i),                            &
    37373472                                                     NF90_COLLECTIVE )
    37383473                   ELSE
    37393474!
    3740 !--                   Test simulations showed that the output of cross sections
    3741 !--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
    3742 !--                   faster than the output by the first row of PEs in
    3743 !--                   x-direction using NF90_INDEPENDENT.
    3744                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),    &
    3745                                                     id_var_do2d(av,i), &
    3746                                                     NF90_COLLECTIVE )
    3747 !                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
    3748 !                                                     id_var_do2d(av,i), &
     3475!--                   Test simulations showed that the output of cross sections by all PEs in
     3476!--                   data_output_2d using NF90_COLLECTIVE is faster than the output by the first
     3477!--                   row of PEs in x-direction using NF90_INDEPENDENT.
     3478                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3479                                                     id_var_do2d(av,i),                            &
     3480                                                     NF90_COLLECTIVE )
     3481!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3482!                                                     id_var_do2d(av,i),                            &
    37493483!                                                     NF90_INDEPENDENT )
    37503484                   ENDIF
     
    37653499
    37663500!
    3767 !--       Write the list of variables as global attribute (this is used by
    3768 !--       restart runs and by combine_plot_fields)
    3769           nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
    3770                                   var_list )
     3501!--       Write the list of variables as global attribute (this is used by restart runs and by
     3502!--       combine_plot_fields)
     3503          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', var_list )
    37713504          CALL netcdf_handle_error( 'netcdf_define_header', 161 )
    37723505
    37733506!
    3774 !--       Set general no fill, otherwise the performance drops significantly for
    3775 !--       parallel output.
     3507!--       Set general no fill, otherwise the performance drops significantly for parallel output.
    37763508          nc_stat = NF90_SET_FILL( id_set_xz(av), NF90_NOFILL, oldmode )
    37773509          CALL netcdf_handle_error( 'netcdf_define_header', 530 )
     
    37833515
    37843516!
    3785 !--       These data are only written by PE0 for parallel output to increase
    3786 !--       the performance.
     3517!--       These data are only written by PE0 for parallel output to increase the performance.
    37873518          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
    37883519
     
    38003531                ENDIF
    38013532             ENDDO
    3802              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), &
    3803                                      netcdf_data, start = (/ 1 /),   &
     3533             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av),                               &
     3534                                     netcdf_data, start = (/ 1 /),                                 &
    38043535                                     count = (/ ns /) )
    38053536             CALL netcdf_handle_error( 'netcdf_define_header', 163 )
     
    38143545                ENDIF
    38153546             ENDDO
    3816              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_yv_xz(av), &
    3817                                      netcdf_data, start = (/ 1 /),    &
     3547             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_yv_xz(av),                              &
     3548                                     netcdf_data, start = (/ 1 /),                                 &
    38183549                                     count = (/ ns /) )
    38193550             CALL netcdf_handle_error( 'netcdf_define_header', 375 )
     
    38223553!--          Write gridpoint number data
    38233554             netcdf_data(1:ns) = section(1:ns,2)
    3824              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_ind_y_xz(av), &
    3825                                      netcdf_data, start = (/ 1 /),       &
     3555             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_ind_y_xz(av),                           &
     3556                                     netcdf_data, start = (/ 1 /),                                 &
    38263557                                     count = (/ ns /) )
    38273558             CALL netcdf_handle_error( 'netcdf_define_header', 164 )
     
    38383569             ENDDO
    38393570
    3840              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av), &
    3841                                      netcdf_data, start = (/ 1 /),   &
     3571             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av),                               &
     3572                                     netcdf_data, start = (/ 1 /),                                 &
    38423573                                     count = (/ nx+1 /) )
    38433574             CALL netcdf_handle_error( 'netcdf_define_header', 165 )
     
    38473578             ENDDO
    38483579
    3849              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_xu_xz(av), &
    3850                                      netcdf_data, start = (/ 1 /),    &
     3580             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_xu_xz(av),                              &
     3581                                     netcdf_data, start = (/ 1 /),                                 &
    38513582                                     count = (/ nx+1 /) )
    38523583             CALL netcdf_handle_error( 'netcdf_define_header', 377 )
     
    38593590
    38603591             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
    3861              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zu_xz(av), &
    3862                                      netcdf_data, start = (/ 1 /),    &
     3592             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zu_xz(av),                              &
     3593                                     netcdf_data, start = (/ 1 /),                                 &
    38633594                                     count = (/ nz+2 /) )
    38643595             CALL netcdf_handle_error( 'netcdf_define_header', 166 )
    38653596
    38663597             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
    3867              nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zw_xz(av), &
    3868                                      netcdf_data, start = (/ 1 /),    &
     3598             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zw_xz(av),                              &
     3599                                     netcdf_data, start = (/ 1 /),                                 &
    38693600                                     count = (/ nz+2 /) )
    38703601             CALL netcdf_handle_error( 'netcdf_define_header', 167 )
     
    38743605             IF ( land_surface )  THEN
    38753606                netcdf_data(0:nzs-1) = - zs(nzb_soil:nzt_soil)
    3876                 nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zs_xz(av), &
    3877                                         netcdf_data(0:nzs), start = (/ 1 /),    &
     3607                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zs_xz(av),                           &
     3608                                        netcdf_data(0:nzs), start = (/ 1 /),                       &
    38783609                                        count = (/ nzt_soil-nzb_soil+1 /) )
    38793610               CALL netcdf_handle_error( 'netcdf_define_header', 548 )
     
    39063637
    39073638                   DO  i = 0, nx
    3908                      netcdf_data(i) = init_model%origin_x                      &
    3909                                     + cos_rot_angle * ( i + shift_x ) * dx
     3639                     netcdf_data(i) = init_model%origin_x + cos_rot_angle * ( i + shift_x ) * dx
    39103640                   ENDDO
    39113641
    3912                    nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),&
    3913                                            netcdf_data, start = (/ 1 /),       &
     3642                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),                    &
     3643                                           netcdf_data, start = (/ 1 /),                           &
    39143644                                           count = (/ nx+1 /) )
    39153645                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    39393669                         netcdf_data(i) = -1.0_wp  ! section averaged along y
    39403670                      ELSE
    3941                          netcdf_data(i) = init_model%origin_y &
    3942                                      + cos_rot_angle * ( section(i,2) + shift_y ) * dy
     3671                         netcdf_data(i) = init_model%origin_y                                      &
     3672                                          + cos_rot_angle * ( section(i,2) + shift_y ) * dy
    39433673                      ENDIF
    39443674                   ENDDO
    39453675
    3946                    nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),&
    3947                                            netcdf_data, start = (/ 1 /),   &
     3676                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),                    &
     3677                                           netcdf_data, start = (/ 1 /),                           &
    39483678                                           count = (/ ns /) )
    39493679                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    39793709                      ELSE
    39803710                         DO  i = 0, nx
    3981                             netcdf_data_2d(i,j) = init_model%origin_x                 &
    3982                                     + cos_rot_angle * ( i + shift_x ) * dx            &
    3983                                     + sin_rot_angle * ( section(j,2) + shift_y ) * dy
     3711                            netcdf_data_2d(i,j) = init_model%origin_x                              &
     3712                                                  + cos_rot_angle * ( i + shift_x ) * dx           &
     3713                                                  + sin_rot_angle * ( section(j,2) + shift_y ) * dy
    39843714                         ENDDO
    39853715                      ENDIF
    39863716                   ENDDO
    39873717
    3988                    nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),  &
    3989                                            netcdf_data_2d, start = (/ 1, 1 /),   &
     3718                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),                    &
     3719                                           netcdf_data_2d, start = (/ 1, 1 /),                     &
    39903720                                           count = (/ nx+1, ns /) )
    39913721                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    39963726                      ELSE
    39973727                         DO  i = 0, nx
    3998                             netcdf_data_2d(i,j) = init_model%origin_y                 &
    3999                                     - sin_rot_angle * ( i + shift_x ) * dx            &
    4000                                     + cos_rot_angle * ( section(j,2) + shift_y ) * dy
     3728                            netcdf_data_2d(i,j) = init_model%origin_y                              &
     3729                                                  - sin_rot_angle * ( i + shift_x ) * dx           &
     3730                                                  + cos_rot_angle * ( section(j,2) + shift_y ) * dy
    40013731                         ENDDO
    40023732                      ENDIF
    40033733                   ENDDO
    40043734
    4005                    nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),  &
    4006                                            netcdf_data_2d, start = (/ 1, 1 /),   &
     3735                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),                    &
     3736                                           netcdf_data_2d, start = (/ 1, 1 /),                     &
    40073737                                           count = (/ nx+1, ns /) )
    40083738                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    40393769                   ELSE
    40403770                      DO  i = 0, nx
    4041                          eutm = init_model%origin_x                   &
    4042                               + cos_rot_angle * ( i + shift_x ) * dx  &
    4043                               + sin_rot_angle * ( section(j,2) + shift_y ) * dy
    4044                          nutm = init_model%origin_y                   &
    4045                               - sin_rot_angle * ( i + shift_x ) * dx  &
    4046                               + cos_rot_angle * ( section(j,2) + shift_y ) * dy
    4047 
    4048                          CALL  convert_utm_to_geographic( crs_list,          &
    4049                                                           eutm, nutm,        &
    4050                                                           lon(i,j), lat(i,j) )
     3771                         eutm = init_model%origin_x                                                &
     3772                                + cos_rot_angle * ( i + shift_x ) * dx                             &
     3773                                + sin_rot_angle * ( section(j,2) + shift_y ) * dy
     3774                         nutm = init_model%origin_y                                                &
     3775                                - sin_rot_angle * ( i + shift_x ) * dx                             &
     3776                                + cos_rot_angle * ( section(j,2) + shift_y ) * dy
     3777
     3778                         CALL  convert_utm_to_geographic( crs_list, eutm, nutm, lon(i,j), lat(i,j) )
    40513779                      ENDDO
    40523780                   ENDIF
    40533781                ENDDO
    40543782
    4055                 nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lon_xz(k,av), &
    4056                                      lon, start = (/ 1, 1 /),       &
    4057                                      count = (/ nx+1, ns /) )
     3783                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lon_xz(k,av),                        &
     3784                                        lon, start = (/ 1, 1 /),                                   &
     3785                                        count = (/ nx+1, ns /) )
    40583786                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    40593787
    4060                 nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lat_xz(k,av), &
    4061                                      lat, start = (/ 1, 1 /),       &
    4062                                      count = (/ nx+1, ns /) )
     3788                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lat_xz(k,av),                        &
     3789                                        lat, start = (/ 1, 1 /),                                   &
     3790                                        count = (/ nx+1, ns /) )
    40633791                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    40643792             ENDDO
     
    40743802!
    40753803!--       Get the list of variables and compare with the actual run.
    4076 !--       First var_list_old has to be reset, since GET_ATT does not assign
    4077 !--       trailing blanks.
     3804!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    40783805          var_list_old = ' '
    4079           nc_stat = NF90_GET_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
    4080                                   var_list_old )
     3806          nc_stat = NF90_GET_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', var_list_old )
    40813807          CALL netcdf_handle_error( 'netcdf_define_header', 168 )
    40823808
     
    40973823
    40983824          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    4099              message_string = 'netCDF file for cross-sections ' //           &
    4100                               TRIM( var ) // ' from previous run found,' //  &
    4101                               '&but this file cannot be extended due to' //  &
    4102                               ' variable mismatch.' //                       &
    4103                               '&New file is created instead.'
     3825             message_string = 'netCDF file for cross-sections ' // TRIM( var ) //                  &
     3826                              ' from previous run found,' //                                       &
     3827                              '&but this file cannot be extended due to' //                        &
     3828                              ' variable mismatch.' // '&New file is created instead.'
    41043829             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
    41053830             extend = .FALSE.
     
    41203845          CALL netcdf_handle_error( 'netcdf_define_header', 169 )
    41213846
    4122           nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_y_xz(av), &
     3847          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_y_xz(av),                         &
    41233848                                           dimids = id_dim_y_xz_old )
    41243849          CALL netcdf_handle_error( 'netcdf_define_header', 170 )
    41253850          id_dim_y_xz(av) = id_dim_y_xz_old(1)
    41263851
    4127           nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_y_xz(av), &
    4128                                             len = ns_old )
     3852          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_y_xz(av), LEN = ns_old )
    41293853          CALL netcdf_handle_error( 'netcdf_define_header', 171 )
    41303854
    41313855          IF ( ns /= ns_old )  THEN
    4132              message_string = 'netCDF file for cross-sections ' //          &
    4133                               TRIM( var ) // ' from previous run found,' // &
    4134                               '&but this file cannot be extended due to' // &
    4135                               ' mismatch in number of' //                   &
    4136                               ' cross sections.' //                         &
     3856             message_string = 'netCDF file for cross-sections ' // TRIM( var ) //                  &
     3857                              ' from previous run found,' //                                       &
     3858                              '&but this file cannot be extended due to' //                        &
     3859                              ' mismatch in number of' // ' cross sections.' //                    &
    41373860                              '&New file is created instead.'
    41383861             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
     
    41513874             IF ( section(i,2) /= -1 )  THEN
    41523875                IF ( ( ( section(i,2) + 0.5 ) * dy ) /= netcdf_data(i) )  THEN
    4153                    message_string = 'netCDF file for cross-sections ' //       &
    4154                                TRIM( var ) // ' from previous run found,' //   &
    4155                                ' but this file cannot be extended' //          &
    4156                                ' due to mismatch in cross' //                  &
    4157                                ' section levels.' //                           &
    4158                                ' New file is created instead.'
    4159                    CALL message( 'define_netcdf_header', 'PA0251',             &
    4160                                                                  0, 1, 0, 6, 0 )
     3876                   message_string = 'netCDF file for cross-sections ' // TRIM( var ) //            &
     3877                                    ' from previous run found,' //                                 &
     3878                                    ' but this file cannot be extended' //                         &
     3879                                    ' due to mismatch in cross' // ' section levels.' //           &
     3880                                     ' New file is created instead.'
     3881                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    41613882                   extend = .FALSE.
    41623883                   RETURN
     
    41643885             ELSE
    41653886                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    4166                    message_string = 'netCDF file for cross-sections ' //       &
    4167                                TRIM( var ) // ' from previous run found,' //   &
    4168                                ' but this file cannot be extended' //          &
    4169                                ' due to mismatch in cross' //                  &
    4170                                ' section levels.' //                           &
    4171                                ' New file is created instead.'
    4172                    CALL message( 'define_netcdf_header', 'PA0251',             &
    4173                                                                  0, 1, 0, 6, 0 )
     3887                   message_string = 'netCDF file for cross-sections ' // TRIM( var ) //            &
     3888                                    ' from previous run found,' //                                 &
     3889                                    ' but this file cannot be extended' //                         &
     3890                                     ' due to mismatch in cross' // ' section levels.' //          &
     3891                                     ' New file is created instead.'
     3892                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    41743893                   extend = .FALSE.
    41753894                   RETURN
     
    41813900
    41823901!
    4183 !--       Get the id of the time coordinate (unlimited coordinate) and its
    4184 !--       last index on the file. The next time level is do2d..count+1.
    4185 !--       The current time must be larger than the last output time
    4186 !--       on the file.
     3902!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     3903!--       The next time level is do2d..count+1.
     3904!--       The current time must be larger than the last output time on the file.
    41873905          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'time', id_var_time_xz(av) )
    41883906          CALL netcdf_handle_error( 'netcdf_define_header', 173 )
    41893907
    4190           nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_time_xz(av), &
     3908          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_time_xz(av),                      &
    41913909                                           dimids = id_dim_time_old )
    41923910          CALL netcdf_handle_error( 'netcdf_define_header', 174 )
    41933911          id_dim_time_xz(av) = id_dim_time_old(1)
    41943912
    4195           nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_time_xz(av), &
    4196                                             len = ntime_count )
     3913          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_time_xz(av), LEN = ntime_count )
    41973914          CALL netcdf_handle_error( 'netcdf_define_header', 175 )
    41983915
    41993916!
    4200 !--       For non-parallel output use the last output time level of the netcdf
    4201 !--       file because the time dimension is unlimited. In case of parallel
    4202 !--       output the variable ntime_count could get the value of 9*10E36 because
    4203 !--       the time dimension is limited.
     3917!--       For non-parallel output use the last output time level of the netcdf file because the time
     3918!--       dimension is unlimited. In case of parallel output the variable ntime_count could get the
     3919!--       value of 9*10E36 because the time dimension is limited.
    42043920          IF ( netcdf_data_format < 5 ) do2d_xz_time_count(av) = ntime_count
    42053921
    4206           nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_time_xz(av),           &
    4207                                   last_time_coordinate,                        &
    4208                                   start = (/ do2d_xz_time_count(av) /),        &
     3922          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_time_xz(av),                               &
     3923                                  last_time_coordinate,                                            &
     3924                                  start = (/ do2d_xz_time_count(av) /),                            &
    42093925                                  count = (/ 1 /) )
    42103926          CALL netcdf_handle_error( 'netcdf_define_header', 176 )
    42113927
    42123928          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    4213              message_string = 'netCDF file for cross sections ' //             &
    4214                               TRIM( var ) // ' from previous run found,' //    &
    4215                               '&but this file cannot be extended becaus' //    &
    4216                               'e the current output time' //                   &
    4217                               '&is less or equal than the last output t' //    &
    4218                               'ime on this file.' //                           &
     3929             message_string = 'netCDF file for cross sections ' // TRIM( var ) //                  &
     3930                              ' from previous run found,' //                                       &
     3931                              '&but this file cannot be extended because' //                       &
     3932                              ' the current output time' //                   &
     3933                              '&is less or equal than the last output time' // ' on this file.' // &
    42193934                              '&New file is created instead.'
    42203935             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
     
    42263941          IF ( netcdf_data_format > 4 )  THEN
    42273942!
    4228 !--          Check if the needed number of output time levels is increased
    4229 !--          compared to the number of time levels in the existing file.
     3943!--          Check if the needed number of output time levels is increased compared to the number of
     3944!--          time levels in the existing file.
    42303945             IF ( ntdim_2d_xz(av) > ntime_count )  THEN
    4231                 message_string = 'netCDF file for cross sections ' // &
    4232                                  TRIM( var ) // ' from previous run found,' // &
    4233                                  '&but this file cannot be extended becaus' // &
    4234                                  'e the number of output time levels has b' // &
    4235                                  'een increased compared to the previous s' // &
    4236                                  'imulation.' //                               &
     3946                message_string = 'netCDF file for cross sections ' // TRIM( var ) //               &
     3947                                 ' from previous run found,' //                                    &
     3948                                 '&but this file cannot be extended becaus' //                     &
     3949                                 'e the number of output time levels has b' //                     &
     3950                                 'een increased compared to the previous s' // 'imulation.' //     &
    42373951                                 '&New file is created instead.'
    42383952                CALL message( 'define_netcdf_header', 'PA0390', 0, 1, 0, 6, 0 )
     
    42423956!--             Recalculate the needed time levels for the new file.
    42433957                IF ( av == 0 )  THEN
    4244                    ntdim_2d_xz(0) = CEILING(                            &
    4245                            ( end_time - MAX( skip_time_do2d_xz,         &
    4246                                              simulated_time_at_begin )  &
    4247                            ) / dt_do2d_xz )
     3958                   ntdim_2d_xz(0) = CEILING( ( end_time - MAX( skip_time_do2d_xz,                  &
     3959                                                               simulated_time_at_begin )           &
     3960                                             ) / dt_do2d_xz )
    42483961                   IF ( do2d_at_begin )  ntdim_2d_xz(0) = ntdim_2d_xz(0) + 1
    42493962                ELSE
    4250                    ntdim_2d_xz(1) = CEILING(                            &
    4251                            ( end_time - MAX( skip_time_data_output_av,  &
    4252                                              simulated_time_at_begin )  &
    4253                            ) / dt_data_output_av )
     3963                   ntdim_2d_xz(1) = CEILING( ( end_time - MAX( skip_time_data_output_av,           &
     3964                                                               simulated_time_at_begin )           &
     3965                                             ) / dt_data_output_av )
    42543966                ENDIF
    42553967                RETURN
     
    42633975          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
    42643976             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
    4265                 nc_stat = NF90_INQ_VARID( id_set_xz(av), do2d(av,i), &
    4266                                           id_var_do2d(av,i) )
     3977                nc_stat = NF90_INQ_VARID( id_set_xz(av), do2d(av,i), id_var_do2d(av,i) )
    42673978                CALL netcdf_handle_error( 'netcdf_define_header', 177 )
    42683979#if defined( __netcdf4_parallel )
    42693980!
    4270 !--             Set independent io operations for parallel io. Collective io
    4271 !--             is only allowed in case of a 1d-decomposition along x, because
    4272 !--             otherwise, not all PEs have output data.
     3981!--             Set independent io operations for parallel io. Collective io is only allowed in case
     3982!--             of a 1d-decomposition along x, because otherwise, not all PEs have output data.
    42733983                IF ( netcdf_data_format > 4 )  THEN
    42743984                   IF ( npey == 1 )  THEN
    4275                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
    4276                                                      id_var_do2d(av,i), &
     3985                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3986                                                     id_var_do2d(av,i),                            &
    42773987                                                     NF90_COLLECTIVE )
    42783988                   ELSE
    42793989!
    4280 !--                   Test simulations showed that the output of cross sections
    4281 !--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
    4282 !--                   faster than the output by the first row of PEs in
    4283 !--                   x-direction using NF90_INDEPENDENT.
    4284                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
    4285                                                      id_var_do2d(av,i), &
     3990!--                   Test simulations showed that the output of cross sections by all PEs in
     3991!--                   data_output_2d using NF90_COLLECTIVE is faster than the output by the first
     3992!--                   row of PEs in x-direction using NF90_INDEPENDENT.
     3993                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3994                                                     id_var_do2d(av,i),                            &
    42863995                                                     NF90_COLLECTIVE )
    4287 !                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
    4288 !                                                     id_var_do2d(av,i), &
     3996!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),                                &
     3997!                                                     id_var_do2d(av,i),                            &
    42893998!                                                     NF90_INDEPENDENT )
    42903999                   ENDIF
     
    42974006
    42984007!
    4299 !--       Update the title attribute on file
    4300 !--       In order to avoid 'data mode' errors if updated attributes are larger
    4301 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    4302 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    4303 !--       performance loss due to data copying; an alternative strategy would be
    4304 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     4008!--       Update the title attribute on file.
     4009!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     4010!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     4011!--       calls. This implies a possible performance loss due to data copying; an alternative
     4012!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    43054013          IF ( av == 0 )  THEN
    43064014             time_average_text = ' '
    43074015          ELSE
    4308              WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
    4309                                                             averaging_interval
     4016             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' ) averaging_interval
    43104017          ENDIF
    43114018          nc_stat = NF90_REDEF( id_set_xz(av) )
    43124019          CALL netcdf_handle_error( 'netcdf_define_header', 433 )
    4313           nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title',         &
    4314                                   TRIM( run_description_header ) //            &
    4315                                   TRIM( time_average_text ) )
     4020          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title',                             &
     4021                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    43164022          CALL netcdf_handle_error( 'netcdf_define_header', 178 )
    43174023          nc_stat = NF90_ENDDEF( id_set_xz(av) )
    43184024          CALL netcdf_handle_error( 'netcdf_define_header', 434 )
    4319           message_string = 'netCDF file for cross-sections ' //                &
    4320                             TRIM( var ) // ' from previous run found.' //      &
    4321                            '&This file will be extended.'
     4025          message_string = 'netCDF file for cross-sections ' // TRIM( var ) //                     &
     4026                           ' from previous run found.' // '&This file will be extended.'
    43224027          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
    43234028
     
    43284033!--       Define some global attributes of the dataset
    43294034          IF ( av == 0 )  THEN
    4330              CALL netcdf_create_global_atts( id_set_yz(av), 'yz', TRIM( run_description_header ), 179 )
     4035             CALL netcdf_create_global_atts( id_set_yz(av), 'yz', TRIM( run_description_header ),  &
     4036                                             179 )
    43314037             time_average_text = ' '
    43324038          ELSE
    4333              CALL netcdf_create_global_atts( id_set_yz(av), 'yz_av', TRIM( run_description_header ), 179 )
     4039             CALL netcdf_create_global_atts( id_set_yz(av), 'yz_av',                               &
     4040                                             TRIM( run_description_header ), 179 )
    43344041             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    4335              nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'time_avg',   &
     4042             nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'time_avg',                       &
    43364043                                     TRIM( time_average_text ) )
    43374044             CALL netcdf_handle_error( 'netcdf_define_header', 180 )
     
    43404047!
    43414048!--       Define time coordinate for yz sections.
    4342 !--       For parallel output the time dimensions has to be limited, otherwise
    4343 !--       the performance drops significantly.
     4049!--       For parallel output the time dimensions has to be limited, otherwise the performance drops
     4050!--       significantly.
    43444051          IF ( netcdf_data_format < 5 )  THEN
    4345              CALL netcdf_create_dim( id_set_yz(av), 'time', NF90_UNLIMITED,    &
    4346                                      id_dim_time_yz(av), 181 )
     4052             CALL netcdf_create_dim( id_set_yz(av), 'time', NF90_UNLIMITED, id_dim_time_yz(av),    &
     4053                                     181 )
    43474054          ELSE
    4348              CALL netcdf_create_dim( id_set_yz(av), 'time', ntdim_2d_yz(av),   &
    4349                                      id_dim_time_yz(av), 526 )
    4350           ENDIF
    4351 
    4352           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_time_yz(av) /),     &
    4353                                   'time', NF90_DOUBLE, id_var_time_yz(av),     &
    4354                                   'seconds', 'time', 182, 183, 000 )
     4055             CALL netcdf_create_dim( id_set_yz(av), 'time', ntdim_2d_yz(av), id_dim_time_yz(av),   &
     4056                                     526 )
     4057          ENDIF
     4058
     4059          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_time_yz(av) /), 'time', NF90_DOUBLE,    &
     4060                                  id_var_time_yz(av), 'seconds', 'time', 182, 183, 000 )
    43554061          CALL netcdf_create_att( id_set_yz(av), id_var_time_yz(av), 'standard_name', 'time', 000)
    43564062          CALL netcdf_create_att( id_set_yz(av), id_var_time_yz(av), 'axis', 'T', 000)
     
    43624068          ELSE
    43634069             ns = 1
    4364              DO WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
     4070             DO  WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
    43654071                ns = ns + 1
    43664072             ENDDO
     
    43704076!
    43714077!--       Define x axis (for scalar position)
    4372           CALL netcdf_create_dim( id_set_yz(av), 'x_yz', ns, id_dim_x_yz(av),  &
    4373                                   184 )
    4374           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /),        &
    4375                                   'x_yz', NF90_DOUBLE, id_var_x_yz(av),        &
    4376                                   'meters', '', 185, 186, 000 )
    4377           CALL netcdf_create_att( id_set_yz(av), id_var_x_yz(av), 'axis',      &
    4378                                   'X', 000)
     4078          CALL netcdf_create_dim( id_set_yz(av), 'x_yz', ns, id_dim_x_yz(av), 184 )
     4079          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /), 'x_yz', NF90_DOUBLE,       &
     4080                                  id_var_x_yz(av), 'meters', '', 185, 186, 000 )
     4081          CALL netcdf_create_att( id_set_yz(av), id_var_x_yz(av), 'axis', 'X', 000)
    43794082!
    43804083!--       Define x axis (for u position)
    4381           CALL netcdf_create_dim( id_set_yz(av), 'xu_yz', ns,                  &
    4382                                   id_dim_xu_yz(av), 377 )
    4383           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_xu_yz(av) /),       &
    4384                                   'xu_yz', NF90_DOUBLE, id_var_xu_yz(av),      &
    4385                                   'meters', '', 378, 379, 000 )
    4386           CALL netcdf_create_att( id_set_yz(av), id_var_xu_yz(av), 'axis',     &
    4387                                   'X', 000)
    4388 !
    4389 !--       Define a variable to store the layer indices of the vertical cross
    4390 !--       sections
    4391           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /),        &
    4392                                   'ind_x_yz', NF90_DOUBLE,                     &
    4393                                   id_var_ind_x_yz(av), 'gridpoints', '', 187,  &
    4394                                   188, 000 )
     4084          CALL netcdf_create_dim( id_set_yz(av), 'xu_yz', ns, id_dim_xu_yz(av), 377 )
     4085          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_xu_yz(av) /), 'xu_yz', NF90_DOUBLE,     &
     4086                                  id_var_xu_yz(av), 'meters', '', 378, 379, 000 )
     4087          CALL netcdf_create_att( id_set_yz(av), id_var_xu_yz(av), 'axis', 'X', 000)
     4088!
     4089!--       Define a variable to store the layer indices of the vertical cross sections
     4090          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /), 'ind_x_yz', NF90_DOUBLE,   &
     4091                                  id_var_ind_x_yz(av), 'gridpoints', '', 187, 188, 000 )
    43954092!
    43964093!--       Define y-axis (for scalar position)
    4397           CALL netcdf_create_dim( id_set_yz(av), 'y', ny+1, id_dim_y_yz(av),   &
    4398                                   189 )
    4399           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_y_yz(av) /), 'y',   &
    4400                                   NF90_DOUBLE, id_var_y_yz(av), 'meters', '',  &
    4401                                   190, 191, 000 )
    4402           CALL netcdf_create_att( id_set_yz(av), id_var_y_yz(av), 'axis',      &
    4403                                   'Y', 000)
     4094          CALL netcdf_create_dim( id_set_yz(av), 'y', ny+1, id_dim_y_yz(av), 189 )
     4095          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_y_yz(av) /), 'y', NF90_DOUBLE,          &
     4096                                  id_var_y_yz(av), 'meters', '', 190, 191, 000 )
     4097          CALL netcdf_create_att( id_set_yz(av), id_var_y_yz(av), 'axis', 'Y', 000)
    44044098!
    44054099!--       Define y-axis (for v position)
    4406           CALL netcdf_create_dim( id_set_yz(av), 'yv', ny+1, id_dim_yv_yz(av), &
    4407                                   380 )
    4408           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_yv_yz(av) /), 'yv', &
    4409                                   NF90_DOUBLE, id_var_yv_yz(av), 'meters', '', &
    4410                                   381, 382, 000 )
    4411           CALL netcdf_create_att( id_set_yz(av), id_var_yv_yz(av), 'axis',     &
    4412                                   'Y', 000)
     4100          CALL netcdf_create_dim( id_set_yz(av), 'yv', ny+1, id_dim_yv_yz(av), 380 )
     4101          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_yv_yz(av) /), 'yv', NF90_DOUBLE,        &
     4102                                  id_var_yv_yz(av), 'meters', '', 381, 382, 000 )
     4103          CALL netcdf_create_att( id_set_yz(av), id_var_yv_yz(av), 'axis', 'Y', 000)
    44134104!
    44144105!--       Define the two z-axes (zu and zw)
    4415           CALL netcdf_create_dim( id_set_yz(av), 'zu', nz+2, id_dim_zu_yz(av), &
    4416                                   192 )
    4417           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zu_yz(av) /), 'zu', &
    4418                                   NF90_DOUBLE, id_var_zu_yz(av), 'meters', '', &
    4419                                   193, 194, 000 )
    4420           CALL netcdf_create_att( id_set_yz(av), id_var_zu_yz(av), 'axis',     &
    4421                                   'Z', 000)
    4422 
    4423           CALL netcdf_create_dim( id_set_yz(av), 'zw', nz+2, id_dim_zw_yz(av), &
    4424                                   195 )
    4425           CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zw_yz(av) /), 'zw', &
    4426                                   NF90_DOUBLE, id_var_zw_yz(av), 'meters', '', &
    4427                                   196, 197, 000 )
    4428           CALL netcdf_create_att( id_set_yz(av), id_var_zw_yz(av), 'axis',     &
    4429                                   'Z', 000)
     4106          CALL netcdf_create_dim( id_set_yz(av), 'zu', nz+2, id_dim_zu_yz(av), 192 )
     4107          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zu_yz(av) /), 'zu', NF90_DOUBLE,        &
     4108                                  id_var_zu_yz(av), 'meters', '', 193, 194, 000 )
     4109          CALL netcdf_create_att( id_set_yz(av), id_var_zu_yz(av), 'axis', 'Z', 000)
     4110
     4111          CALL netcdf_create_dim( id_set_yz(av), 'zw', nz+2, id_dim_zw_yz(av), 195 )
     4112          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zw_yz(av) /), 'zw', NF90_DOUBLE,        &
     4113                                  id_var_zw_yz(av), 'meters', '', 196, 197, 000 )
     4114          CALL netcdf_create_att( id_set_yz(av), id_var_zw_yz(av), 'axis', 'Z', 000)
    44304115!
    44314116!--       Define UTM and geographic coordinates
    4432           CALL define_geo_coordinates( id_set_yz(av),         &
    4433                   (/ id_dim_x_yz(av), id_dim_xu_yz(av) /),    &
    4434                   (/ id_dim_y_yz(av), id_dim_yv_yz(av) /),    &
    4435                   id_var_eutm_yz(:,av), id_var_nutm_yz(:,av), &
    4436                   id_var_lat_yz(:,av), id_var_lon_yz(:,av)    )
     4117          CALL define_geo_coordinates( id_set_yz(av),                                              &
     4118                                       (/ id_dim_x_yz(av), id_dim_xu_yz(av) /),                    &
     4119                                       (/ id_dim_y_yz(av), id_dim_yv_yz(av) /),                    &
     4120                                       id_var_eutm_yz(:,av), id_var_nutm_yz(:,av),                &
     4121                                       id_var_lat_yz(:,av), id_var_lon_yz(:,av)    )
    44374122!
    44384123!--       Define coordinate-reference system
     
    44414126          IF ( land_surface )  THEN
    44424127
    4443              CALL netcdf_create_dim( id_set_yz(av), 'zs', nzs,                 &
    4444                                      id_dim_zs_yz(av), 545 )
    4445              CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zs_yz(av) /),    &
    4446                                      'zs', NF90_DOUBLE, id_var_zs_yz(av),      &
    4447                                      'meters', '', 546, 547, 000 )
    4448              CALL netcdf_create_att( id_set_yz(av), id_var_zs_yz(av), 'axis',  &
    4449                                      'Z', 000)
     4128             CALL netcdf_create_dim( id_set_yz(av), 'zs', nzs, id_dim_zs_yz(av), 545 )
     4129             CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zs_yz(av) /), 'zs', NF90_DOUBLE,     &
     4130                                     id_var_zs_yz(av), 'meters', '', 546, 547, 000 )
     4131             CALL netcdf_create_att( id_set_yz(av), id_var_zs_yz(av), 'axis', 'Z', 000)
    44504132
    44514133          ENDIF
     
    45024184!--                   Check for land surface quantities
    45034185                      IF ( land_surface )  THEN
    4504                          CALL lsm_define_netcdf_grid( do2d(av,i), found,       &
    4505                                                       grid_x, grid_y, grid_z )
     4186                         CALL lsm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45064187                      ENDIF
    45074188
    45084189                      IF ( .NOT. found )  THEN
    4509                          CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
    4510                                                       grid_x, grid_y, grid_z )
     4190                         CALL tcm_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45114191                      ENDIF
    45124192
     
    45144194!--                   Check for ocean quantities
    45154195                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
    4516                          CALL ocean_define_netcdf_grid( do2d(av,i), found,     &
    4517                                                        grid_x, grid_y, grid_z )
     4196                         CALL ocean_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45184197                      ENDIF
    45194198!
    45204199!--                   Check for radiation quantities
    45214200                      IF ( .NOT. found  .AND.  radiation )  THEN
    4522                          CALL radiation_define_netcdf_grid( do2d(av,i), found, &
    4523                                                             grid_x, grid_y,    &
     4201                         CALL radiation_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y,     &
    45244202                                                            grid_z )
    45254203                      ENDIF
     
    45274205!--                   Check for SALSA quantities
    45284206                      IF ( .NOT. found  .AND.  salsa )  THEN
    4529                          CALL salsa_define_netcdf_grid( do2d(av,i), found,     &
    4530                                                         grid_x, grid_y, grid_z )
     4207                         CALL salsa_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45314208                      ENDIF
    45324209!
    45334210!--                   Check for gust module quantities
    45344211                      IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    4535                          CALL gust_define_netcdf_grid( do2d(av,i), found,      &
    4536                                                        grid_x, grid_y, grid_z )
     4212                         CALL gust_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45374213                      ENDIF
    45384214
     
    45404216!--                   Check for chemistry quantities
    45414217                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
    4542                          CALL chem_define_netcdf_grid( do2d(av,i), found,      &
    4543                                                        grid_x, grid_y,         &
    4544                                                        grid_z )
     4218                         CALL chem_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45454219                      ENDIF
    45464220
    4547                       IF ( .NOT. found )                                       &
    4548                          CALL doq_define_netcdf_grid(                          &
    4549                                                     do2d(av,i), found, grid_x, &
    4550                                                     grid_y, grid_z           )
     4221                      IF ( .NOT. found )                                                           &
     4222                         CALL doq_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45514223!
    45524224!--                   Check for user-defined quantities
    45534225                      IF ( .NOT. found  .AND.  user_module_enabled )  THEN
    4554                          CALL user_define_netcdf_grid( do2d(av,i), found,      &
    4555                                                        grid_x, grid_y, grid_z )
     4226                         CALL user_define_netcdf_grid( do2d(av,i), found, grid_x, grid_y, grid_z )
    45564227                      ENDIF
    45574228
    45584229                      IF ( .NOT. found )  THEN
    4559                          WRITE ( message_string, * ) 'no grid defined for',    &
    4560                                                 ' variable ', TRIM( do2d(av,i) )
    4561                          CALL message( 'define_netcdf_header', 'PA0244',       &
    4562                                        0, 1, 0, 6, 0 )
     4230                         WRITE ( message_string, * ) 'no grid defined for', ' variable ',          &
     4231                                                     TRIM( do2d(av,i) )
     4232                         CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
    45634233                      ENDIF
    45644234
     
    45894259!
    45904260!--             Define the grid
    4591                 CALL netcdf_create_var( id_set_yz(av),  (/ id_x, id_y, id_z,   &
    4592                                         id_dim_time_yz(av) /), do2d(av,i),     &
    4593                                         nc_precision(3), id_var_do2d(av,i),    &
    4594                                         TRIM( do2d_unit(av,i) ), do2d(av,i),   &
    4595                                         198, 199, 356, .TRUE. )
     4261                CALL netcdf_create_var( id_set_yz(av),  (/ id_x, id_y, id_z, id_dim_time_yz(av) /),&
     4262                                        do2d(av,i), nc_precision(3), id_var_do2d(av,i),            &
     4263                                        TRIM( do2d_unit(av,i) ), do2d(av,i), 198, 199, 356, .TRUE. )
    45964264
    45974265#if defined( __netcdf4_parallel )
     
    45994267!
    46004268!--                Set no fill for every variable to increase performance.
    4601                    nc_stat = NF90_DEF_VAR_FILL( id_set_yz(av),     &
    4602                                                 id_var_do2d(av,i), &
     4269                   nc_stat = NF90_DEF_VAR_FILL( id_set_yz(av),                                     &
     4270                                                id_var_do2d(av,i),                                 &
    46034271                                                NF90_NOFILL, 0 )
    46044272                   CALL netcdf_handle_error( 'netcdf_define_header', 535 )
    46054273!
    4606 !--                Set independent io operations for parallel io. Collective io
    4607 !--                is only allowed in case of a 1d-decomposition along y,
    4608 !--                because otherwise, not all PEs have output data.
     4274!--                Set independent io operations for parallel io. Collective io is only allowed in
     4275!--                case of a 1d-decomposition along y, because otherwise, not all PEs have output
     4276!--                data.
    46094277                   IF ( npex == 1 )  THEN
    4610                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    4611                                                      id_var_do2d(av,i), &
     4278                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4279                                                     id_var_do2d(av,i),                            &
    46124280                                                     NF90_COLLECTIVE )
    46134281                   ELSE
    46144282!
    4615 !--                   Test simulations showed that the output of cross sections
    4616 !--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
    4617 !--                   faster than the output by the first row of PEs in
    4618 !--                   y-direction using NF90_INDEPENDENT.
    4619                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    4620                                                      id_var_do2d(av,i), &
     4283!--                   Test simulations showed that the output of cross sections by all PEs in
     4284!--                   data_output_2d using NF90_COLLECTIVE is faster than the output by the first
     4285!--                   row of PEs in y-direction using NF90_INDEPENDENT.
     4286                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4287                                                     id_var_do2d(av,i),                            &
    46214288                                                     NF90_COLLECTIVE )
    4622 !                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    4623 !                                                     id_var_do2d(av,i), &
     4289!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4290!                                                     id_var_do2d(av,i),                            &
    46244291!                                                     NF90_INDEPENDENT )
    46254292                   ENDIF
     
    46404307
    46414308!
    4642 !--       Write the list of variables as global attribute (this is used by
    4643 !--       restart runs and by combine_plot_fields)
    4644           nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
    4645                                   var_list )
     4309!--       Write the list of variables as global attribute (this is used by restart runs and by
     4310!--       combine_plot_fields)
     4311          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', var_list )
    46464312          CALL netcdf_handle_error( 'netcdf_define_header', 200 )
    46474313
    46484314!
    4649 !--       Set general no fill, otherwise the performance drops significantly for
    4650 !--       parallel output.
     4315!--       Set general no fill, otherwise the performance drops significantly for parallel output.
    46514316          nc_stat = NF90_SET_FILL( id_set_yz(av), NF90_NOFILL, oldmode )
    46524317          CALL netcdf_handle_error( 'netcdf_define_header', 531 )
     
    46584323
    46594324!
    4660 !--       These data are only written by PE0 for parallel output to increase
    4661 !--       the performance.
     4325!--       These data are only written by PE0 for parallel output to increase the performance.
    46624326          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
    46634327
     
    46754339                ENDIF
    46764340             ENDDO
    4677              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), &
    4678                                      netcdf_data, start = (/ 1 /),   &
     4341             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av),                               &
     4342                                     netcdf_data, start = (/ 1 /),                                 &
    46794343                                     count = (/ ns /) )
    46804344             CALL netcdf_handle_error( 'netcdf_define_header', 202 )
     
    46894353                ENDIF
    46904354             ENDDO
    4691              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av), &
    4692                                      netcdf_data, start = (/ 1 /),    &
     4355             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av),                              &
     4356                                     netcdf_data, start = (/ 1 /),                                 &
    46934357                                     count = (/ ns /) )
    46944358             CALL netcdf_handle_error( 'netcdf_define_header', 383 )
     
    46974361!--          Write gridpoint number data
    46984362             netcdf_data(1:ns) = section(1:ns,3)
    4699              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_ind_x_yz(av), &
    4700                                      netcdf_data, start = (/ 1 /),       &
     4363             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_ind_x_yz(av),                           &
     4364                                     netcdf_data, start = (/ 1 /),                                 &
    47014365                                     count = (/ ns /) )
    47024366             CALL netcdf_handle_error( 'netcdf_define_header', 203 )
     
    47124376             ENDDO
    47134377
    4714              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av), &
    4715                                      netcdf_data, start = (/ 1 /),   &
     4378             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av),                               &
     4379                                     netcdf_data, start = (/ 1 /),                                 &
    47164380                                     count = (/ ny+1 /) )
    47174381             CALL netcdf_handle_error( 'netcdf_define_header', 204 )
     
    47214385             ENDDO
    47224386
    4723              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_yv_yz(av), &
    4724                                      netcdf_data, start = (/ 1 /),    &
     4387             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_yv_yz(av),                              &
     4388                                     netcdf_data, start = (/ 1 /),                                 &
    47254389                                     count = (/ ny+1 /) )
    47264390             CALL netcdf_handle_error( 'netcdf_define_header', 384 )
     
    47334397
    47344398             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
    4735              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zu_yz(av), &
    4736                                      netcdf_data, start = (/ 1 /),    &
     4399             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zu_yz(av),                              &
     4400                                     netcdf_data, start = (/ 1 /),                                 &
    47374401                                     count = (/ nz+2 /) )
    47384402             CALL netcdf_handle_error( 'netcdf_define_header', 205 )
    47394403
    47404404             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
    4741              nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zw_yz(av), &
    4742                                      netcdf_data, start = (/ 1 /),    &
     4405             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zw_yz(av),                              &
     4406                                     netcdf_data, start = (/ 1 /),                                 &
    47434407                                     count = (/ nz+2 /) )
    47444408             CALL netcdf_handle_error( 'netcdf_define_header', 206 )
     
    47734437                         netcdf_data(i) = -1.0_wp  ! section averaged along x
    47744438                      ELSE
    4775                          netcdf_data(i) = init_model%origin_x &
    4776                                      + cos_rot_angle * ( section(i,3) + shift_x ) * dx
     4439                         netcdf_data(i) = init_model%origin_x                                      &
     4440                                          + cos_rot_angle * ( section(i,3) + shift_x ) * dx
    47774441                      ENDIF
    47784442                   ENDDO
    47794443
    4780                    nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),&
    4781                                            netcdf_data, start = (/ 1 /),   &
     4444                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),                    &
     4445                                           netcdf_data, start = (/ 1 /),                           &
    47824446                                           count = (/ ns /) )
    47834447                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    48044468
    48054469                   DO  i = 0, ny
    4806                      netcdf_data(i) = init_model%origin_y                      &
    4807                                     + cos_rot_angle * ( i + shift_y ) * dy
     4470                     netcdf_data(i) = init_model%origin_y + cos_rot_angle * ( i + shift_y ) * dy
    48084471                   ENDDO
    48094472
    4810                    nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),&
    4811                                            netcdf_data, start = (/ 1 /),   &
     4473                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),                    &
     4474                                           netcdf_data, start = (/ 1 /),                           &
    48124475                                           count = (/ ny+1 /) )
    48134476                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    48434506                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
    48444507                         ELSE
    4845                             netcdf_data_2d(i,j) = init_model%origin_x                 &
    4846                                     + cos_rot_angle * ( section(i,3) + shift_x ) * dx &
    4847                                     + sin_rot_angle * ( j + shift_y ) * dy
     4508                            netcdf_data_2d(i,j) = init_model%origin_x                              &
     4509                                                 + cos_rot_angle * ( section(i,3) + shift_x ) * dx &
     4510                                                 + sin_rot_angle * ( j + shift_y ) * dy
    48484511                         ENDIF
    48494512                      ENDDO
    48504513                   ENDDO
    48514514
    4852                    nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),  &
    4853                                            netcdf_data_2d, start = (/ 1, 1 /),   &
     4515                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),                    &
     4516                                           netcdf_data_2d, start = (/ 1, 1 /),                     &
    48544517                                           count = (/ ns, ny+1 /) )
    48554518                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     
    48604523                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
    48614524                         ELSE
    4862                             netcdf_data_2d(i,j) = init_model%origin_y                 &
    4863                                     - sin_rot_angle * ( section(i,3) + shift_x ) * dx &
    4864                                     + cos_rot_angle * ( j + shift_y ) * dy
     4525                            netcdf_data_2d(i,j) = init_model%origin_y                              &
     4526                                                 - sin_rot_angle * ( section(i,3) + shift_x ) * dx &
     4527                                                 + cos_rot_angle * ( j + shift_y ) * dy
    48654528                         ENDIF
    48664529                      ENDDO
    48674530                   ENDDO
    48684531
    4869                    nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),  &
    4870                                            netcdf_data_2d, start = (/ 1, 1 /),   &
     4532                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),                    &
     4533                                           netcdf_data_2d, start = (/ 1, 1 /),                     &
    48714534                                           count = (/ ns, ny+1 /) )
    48724535                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     
    49034566                         lon(i,:) = -180.0_wp  ! section averaged along x
    49044567                      ELSE
    4905                          eutm = init_model%origin_x                              &
    4906                               + cos_rot_angle * ( section(i,3) + shift_x ) * dx  &
    4907                               + sin_rot_angle * ( j + shift_y ) * dy
    4908                          nutm = init_model%origin_y                              &
    4909                               - sin_rot_angle * ( section(i,3) + shift_x ) * dx  &
    4910                               + cos_rot_angle * ( j + shift_y ) * dy
    4911 
    4912                          CALL  convert_utm_to_geographic( crs_list,          &
    4913                                                           eutm, nutm,        &
    4914                                                           lon(i,j), lat(i,j) )
     4568                         eutm = init_model%origin_x                                                &
     4569                                + cos_rot_angle * ( section(i,3) + shift_x ) * dx                  &
     4570                                + sin_rot_angle * ( j + shift_y ) * dy
     4571                         nutm = init_model%origin_y                                                &
     4572                                - sin_rot_angle * ( section(i,3) + shift_x ) * dx                  &
     4573                                + cos_rot_angle * ( j + shift_y ) * dy
     4574
     4575                         CALL convert_utm_to_geographic( crs_list, eutm, nutm, lon(i,j), lat(i,j) )
    49154576                      ENDIF
    49164577                   ENDDO
    49174578                ENDDO
    49184579
    4919                 nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lon_yz(k,av), &
    4920                                      lon, start = (/ 1, 1 /),       &
    4921                                      count = (/ ns, ny+1 /) )
     4580                nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lon_yz(k,av),                        &
     4581                                        lon, start = (/ 1, 1 /),                                   &
     4582                                        count = (/ ns, ny+1 /) )
    49224583                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    49234584
    4924                 nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lat_yz(k,av), &
    4925                                      lat, start = (/ 1, 1 /),       &
    4926                                      count = (/ ns, ny+1 /) )
     4585                nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lat_yz(k,av),                        &
     4586                                        lat, start = (/ 1, 1 /),                                   &
     4587                                        count = (/ ns, ny+1 /) )
    49274588                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
    49284589             ENDDO
     
    49384599!
    49394600!--       Get the list of variables and compare with the actual run.
    4940 !--       First var_list_old has to be reset, since GET_ATT does not assign
    4941 !--       trailing blanks.
     4601!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    49424602          var_list_old = ' '
    4943           nc_stat = NF90_GET_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
    4944                                   var_list_old )
     4603          nc_stat = NF90_GET_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', var_list_old )
    49454604          CALL netcdf_handle_error( 'netcdf_define_header', 207 )
    49464605
    49474606          var_list = ';'
    49484607          i = 1
    4949           DO WHILE ( do2d(av,i)(1:1) /= ' ' )
     4608          DO  WHILE ( do2d(av,i)(1:1) /= ' ' )
    49504609             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
    49514610                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
     
    49614620
    49624621          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    4963              message_string = 'netCDF file for cross-sections ' //           &
    4964                               TRIM( var ) // ' from previous run found,' //  &
    4965                               '&but this file cannot be extended due to' //  &
    4966                               ' variable mismatch.' //                       &
    4967                               '&New file is created instead.'
     4622             message_string = 'netCDF file for cross-sections ' // TRIM( var ) //                  &
     4623                              ' from previous run found,' //                                       &
     4624                              '&but this file cannot be extended due to' //                        &
     4625                              ' variable mismatch.' // '&New file is created instead.'
    49684626             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
    49694627             extend = .FALSE.
     
    49894647          id_dim_x_yz(av) = id_dim_x_yz_old(1)
    49904648
    4991           nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_x_yz(av), &
    4992                                             len = ns_old )
     4649          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_x_yz(av), LEN = ns_old )
    49934650          CALL netcdf_handle_error( 'netcdf_define_header', 210 )
    49944651
    49954652          IF ( ns /= ns_old )  THEN
    4996              message_string = 'netCDF file for cross-sections ' //          &
    4997                               TRIM( var ) // ' from previous run found,' // &
    4998                               '&but this file cannot be extended due to' // &
    4999                               ' mismatch in number of' //                   &
    5000                               ' cross sections.' //                         &
     4653             message_string = 'netCDF file for cross-sections ' // TRIM( var ) //                  &
     4654                              ' from previous run found,' //                                       &
     4655                              '&but this file cannot be extended due to' //                        &
     4656                              ' mismatch in number of' // ' cross sections.' //                    &
    50014657                              '&New file is created instead.'
    50024658             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
     
    50154671             IF ( section(i,3) /= -1 )  THEN
    50164672                IF ( ( ( section(i,3) + 0.5 ) * dx ) /= netcdf_data(i) )  THEN
    5017                    message_string = 'netCDF file for cross-sections ' //       &
    5018                               TRIM( var ) // ' from previous run found,' //    &
    5019                               ' but this file cannot be extended' //           &
    5020                               ' due to mismatch in cross' //                   &
    5021                               ' section levels.' //                            &
    5022                               ' New file is created instead.'
    5023                    CALL message( 'define_netcdf_header', 'PA0251',             &
    5024                                                                  0, 1, 0, 6, 0 )
     4673                   message_string = 'netCDF file for cross-sections ' // TRIM( var ) //            &
     4674                                    ' from previous run found,' //                                 &
     4675                                    ' but this file cannot be extended' //                         &
     4676                                    ' due to mismatch in cross' // ' section levels.' //           &
     4677                                    ' New file is created instead.'
     4678                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    50254679                   extend = .FALSE.
    50264680                   RETURN
     
    50284682             ELSE
    50294683                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    5030                    message_string = 'netCDF file for cross-sections ' //       &
    5031                               TRIM( var ) // ' from previous run found,' //    &
    5032                               ' but this file cannot be extended' //           &
    5033                               ' due to mismatch in cross' //                   &
    5034                               ' section levels.' //                            &
    5035                               ' New file is created instead.'
    5036                    CALL message( 'define_netcdf_header', 'PA0251',             &
    5037                                                                  0, 1, 0, 6, 0 )
     4684                   message_string = 'netCDF file for cross-sections ' // TRIM( var ) //            &
     4685                                    ' from previous run found,' //                                 &
     4686                                    ' but this file cannot be extended' //                         &
     4687                                    ' due to mismatch in cross' // ' section levels.' //           &
     4688                                    ' New file is created instead.'
     4689                   CALL message( 'define_netcdf_header', 'PA0251', 0, 1, 0, 6, 0 )
    50384690                   extend = .FALSE.
    50394691                   RETURN
     
    50454697
    50464698!
    5047 !--       Get the id of the time coordinate (unlimited coordinate) and its
    5048 !--       last index on the file. The next time level is pl2d..count+1.
    5049 !--       The current time must be larger than the last output time
    5050 !--       on the file.
     4699!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     4700!--       The next time level is pl2d..count+1.
     4701!--       The current time must be larger than the last output time on the file.
    50514702          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'time', id_var_time_yz(av) )
    50524703          CALL netcdf_handle_error( 'netcdf_define_header', 212 )
    50534704
    5054           nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_time_yz(av), &
     4705          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_time_yz(av),                      &
    50554706                                           dimids = id_dim_time_old )
    50564707          CALL netcdf_handle_error( 'netcdf_define_header', 213 )
    50574708          id_dim_time_yz(av) = id_dim_time_old(1)
    50584709
    5059           nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_time_yz(av), &
    5060                                             len = ntime_count )
     4710          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_time_yz(av), LEN = ntime_count )
    50614711          CALL netcdf_handle_error( 'netcdf_define_header', 214 )
    50624712
    50634713!
    5064 !--       For non-parallel output use the last output time level of the netcdf
    5065 !--       file because the time dimension is unlimited. In case of parallel
    5066 !--       output the variable ntime_count could get the value of 9*10E36 because
    5067 !--       the time dimension is limited.
     4714!--       For non-parallel output use the last output time level of the netcdf file because the time
     4715!--       dimension is unlimited. In case of parallel output the variable ntime_count could get the
     4716!--       value of 9*10E36 because the time dimension is limited.
    50684717          IF ( netcdf_data_format < 5 ) do2d_yz_time_count(av) = ntime_count
    50694718
    5070           nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_time_yz(av),           &
    5071                                   last_time_coordinate,                        &
    5072                                   start = (/ do2d_yz_time_count(av) /),        &
     4719          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_time_yz(av),                               &
     4720                                  last_time_coordinate,                                            &
     4721                                  start = (/ do2d_yz_time_count(av) /),                            &
    50734722                                  count = (/ 1 /) )
    50744723          CALL netcdf_handle_error( 'netcdf_define_header', 215 )
    50754724
    50764725          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    5077              message_string = 'netCDF file for cross sections ' //             &
    5078                               TRIM( var ) // ' from previous run found,' //    &
    5079                               '&but this file cannot be extended becaus' //    &
    5080                               'e the current output time' //                   &
    5081                               '&is less or equal than the last output t' //    &
    5082                               'ime on this file.' //                           &
     4726             message_string = 'netCDF file for cross sections ' // TRIM( var ) //                  &
     4727                              ' from previous run found,' //                                       &
     4728                              '&but this file cannot be extended because' //                       &
     4729                              ' the current output time' //                                        &
     4730                              '&is less or equal than the last output time' // ' on this file.' // &
    50834731                              '&New file is created instead.'
    50844732             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
     
    50934741!--          compared to the number of time levels in the existing file.
    50944742             IF ( ntdim_2d_yz(av) > ntime_count )  THEN
    5095                 message_string = 'netCDF file for cross sections ' //          &
    5096                                  TRIM( var ) // ' from previous run found,' // &
    5097                                  '&but this file cannot be extended becaus' // &
    5098                                  'e the number of output time levels has b' // &
    5099                                  'een increased compared to the previous s' // &
    5100                                  'imulation.' //                               &
     4743                message_string = 'netCDF file for cross sections ' // TRIM( var ) //               &
     4744                                 ' from previous run found,' //                                    &
     4745                                 '&but this file cannot be extended because' //                    &
     4746                                 ' the number of output time levels has ' //                       &
     4747                                 'been increased compared to the previous ' // 'simulation.' //    &
    51014748                                 '&New file is created instead.'
    51024749                CALL message( 'define_netcdf_header', 'PA0391', 0, 1, 0, 6, 0 )
     
    51064753!--             Recalculate the needed time levels for the new file.
    51074754                IF ( av == 0 )  THEN
    5108                    ntdim_2d_yz(0) = CEILING(                            &
    5109                            ( end_time - MAX( skip_time_do2d_yz,         &
    5110                                              simulated_time_at_begin )  &
    5111                            ) / dt_do2d_yz )
     4755                   ntdim_2d_yz(0) = CEILING( ( end_time - MAX( skip_time_do2d_yz,                  &
     4756                                                               simulated_time_at_begin )           &
     4757                                             ) / dt_do2d_yz )
    51124758                   IF ( do2d_at_begin )  ntdim_2d_yz(0) = ntdim_2d_yz(0) + 1
    51134759                ELSE
    5114                    ntdim_2d_yz(1) = CEILING(                            &
    5115                            ( end_time - MAX( skip_time_data_output_av,  &
    5116                                              simulated_time_at_begin )  &
    5117                            ) / dt_data_output_av )
     4760                   ntdim_2d_yz(1) = CEILING( ( end_time - MAX( skip_time_data_output_av,           &
     4761                                                               simulated_time_at_begin )           &
     4762                                             ) / dt_data_output_av )
    51184763                ENDIF
    51194764                RETURN
     
    51274772          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
    51284773             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
    5129                 nc_stat = NF90_INQ_VARID( id_set_yz(av), do2d(av,i), &
    5130                                           id_var_do2d(av,i) )
     4774                nc_stat = NF90_INQ_VARID( id_set_yz(av), do2d(av,i), id_var_do2d(av,i) )
    51314775                CALL netcdf_handle_error( 'netcdf_define_header', 216 )
    51324776#if defined( __netcdf4_parallel )
    51334777!
    5134 !--             Set independent io operations for parallel io. Collective io
    5135 !--             is only allowed in case of a 1d-decomposition along y, because
    5136 !--             otherwise, not all PEs have output data.
     4778!--             Set independent io operations for parallel io. Collective io is only allowed in case
     4779!--             of a 1d-decomposition along y, because otherwise, not all PEs have output data.
    51374780                IF ( netcdf_data_format > 4 )  THEN
    51384781                   IF ( npex == 1 )  THEN
    5139                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    5140                                                      id_var_do2d(av,i), &
     4782                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4783                                                     id_var_do2d(av,i),                            &
    51414784                                                     NF90_COLLECTIVE )
    51424785                   ELSE
    51434786!
    5144 !--                   Test simulations showed that the output of cross sections
    5145 !--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
    5146 !--                   faster than the output by the first row of PEs in
    5147 !--                   y-direction using NF90_INDEPENDENT.
    5148                       nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    5149                                                      id_var_do2d(av,i), &
     4787!--                   Test simulations showed that the output of cross sections by all PEs in
     4788!--                   data_output_2d using NF90_COLLECTIVE is faster than the output by the first
     4789!--                   row of PEs in y-direction using NF90_INDEPENDENT.
     4790                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4791                                                     id_var_do2d(av,i),                            &
    51504792                                                     NF90_COLLECTIVE )
    5151 !                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
    5152 !                                                     id_var_do2d(av,i), &
     4793!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),                                &
     4794!                                                     id_var_do2d(av,i),                            &
    51534795!                                                     NF90_INDEPENDENT )
    51544796                   ENDIF
     
    51614803
    51624804!
    5163 !--       Update the title attribute on file
    5164 !--       In order to avoid 'data mode' errors if updated attributes are larger
    5165 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    5166 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    5167 !--       performance loss due to data copying; an alternative strategy would be
    5168 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     4805!--       Update the title attribute on file.
     4806!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     4807!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     4808!--       calls. This implies a possible performance loss due to data copying; an alternative
     4809!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    51694810          IF ( av == 0 )  THEN
    51704811             time_average_text = ' '
    51714812          ELSE
    5172              WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
    5173                                                             averaging_interval
     4813             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' )  averaging_interval
    51744814          ENDIF
    51754815          nc_stat = NF90_REDEF( id_set_yz(av) )
    51764816          CALL netcdf_handle_error( 'netcdf_define_header', 435 )
    5177           nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title',         &
    5178                                   TRIM( run_description_header ) //            &
    5179                                   TRIM( time_average_text ) )
     4817          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title',                             &
     4818                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    51804819          CALL netcdf_handle_error( 'netcdf_define_header', 217 )
    51814820          nc_stat = NF90_ENDDEF( id_set_yz(av) )
    51824821          CALL netcdf_handle_error( 'netcdf_define_header', 436 )
    5183           message_string = 'netCDF file for cross-sections ' //                &
    5184                             TRIM( var ) // ' from previous run found.' //      &
     4822          message_string = 'netCDF file for cross-sections ' //                                    &
     4823                            TRIM( var ) // ' from previous run found.' //                          &
    51854824                           '&This file will be extended.'
    51864825          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
     
    51934832
    51944833          IF ( averaging_interval_pr /= 0.0_wp )  THEN
    5195              CALL netcdf_create_global_atts( id_set_pr, 'podsprav', TRIM( run_description_header ), 451 )
     4834             CALL netcdf_create_global_atts( id_set_pr, 'podsprav', TRIM( run_description_header ),&
     4835                                             451 )
    51964836             WRITE ( time_average_text,'(F7.1,'' s avg'')' ) averaging_interval_pr
    5197              nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'time_avg',       &
    5198                                      TRIM( time_average_text ) )
     4837             nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'time_avg', TRIM( time_average_text ) )
    51994838          ELSE
    5200              CALL netcdf_create_global_atts( id_set_pr, 'podspr', TRIM( run_description_header ), 451 )
     4839             CALL netcdf_create_global_atts( id_set_pr, 'podspr', TRIM( run_description_header ),  &
     4840                                             451 )
    52014841          ENDIF
    52024842          CALL netcdf_handle_error( 'netcdf_define_header', 219 )
    52034843!
    5204 !--       Write number of columns and rows of coordinate systems to be plotted
    5205 !--       on one page to the netcdf header.
     4844!--       Write number of columns and rows of coordinate systems to be plotted on one page to the
     4845!--       netcdf header.
    52064846!--       This information can be used by palmplot.
    5207           nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
    5208                                   'no_rows',                                  &
     4847          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                                          &
     4848                                  'no_rows',                                                       &
    52094849                                  profile_rows )
    52104850          CALL netcdf_handle_error( 'netcdf_define_header', 519 )
    52114851
    5212           nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
    5213                                   'no_columns',                               &
     4852          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                                          &
     4853                                  'no_columns',                                                    &
    52144854                                  profile_columns )
    52154855          CALL netcdf_handle_error( 'netcdf_define_header', 520 )
     
    52214861
    52224862!
    5223 !--       Each profile defined in cross_profiles is written to an array
    5224 !--       (cross_profiles_char). The number of the respective coordinate
    5225 !--       system is assigned in a second array (cross_profiles_numb).
     4863!--       Each profile defined in cross_profiles is written to an array (cross_profiles_char). The
     4864!--       number of the respective coordinate system is assigned in a second array
     4865!--       (cross_profiles_numb).
    52264866          k = 1
    52274867
     
    52354875                IF ( delim == 1 )  EXIT
    52364876                kk = MIN( crmax, k )
    5237                 cross_profiles_char(kk) = cross_profiles_adj(i)(delim_old+1: &
    5238                                                               delim_old+delim-1)
     4877                cross_profiles_char(kk) = cross_profiles_adj(i)(delim_old+1:delim_old+delim-1)
    52394878                cross_profiles_numb(kk) = i
    52404879                k = k + 1
     
    52474886          cross_profiles_count = MIN( crmax, k-1 )
    52484887!
    5249 !--       Check if all profiles defined in cross_profiles are defined in
    5250 !--       data_output_pr. If not, they will be skipped.
     4888!--       Check if all profiles defined in cross_profiles are defined in data_output_pr. If not,
     4889!--       they will be skipped.
    52514890          DO  i = 1, cross_profiles_count
    52524891             DO  j = 1, dopr_n
    52534892
    5254                 IF ( TRIM(cross_profiles_char(i)) == TRIM(data_output_pr(j)) ) &
    5255                 THEN
     4893                IF ( TRIM( cross_profiles_char(i) ) == TRIM( data_output_pr(j) ) )  THEN
    52564894                   EXIT
    52574895                ENDIF
     
    52674905             IF ( cross_profiles_numb(i) == 999999 ) THEN
    52684906                DO j = i + 1, crmax
    5269                    IF ( cross_profiles_numb(j) /= 999999 ) THEN
     4907                   IF ( cross_profiles_numb(j) /= 999999 )  THEN
    52704908                      cross_profiles_char(i) = cross_profiles_char(j)
    52714909                      cross_profiles_numb(i) = cross_profiles_numb(j)
     
    52844922          ENDDO
    52854923!
    5286 !--       Check if all profiles defined in data_output_pr are defined in
    5287 !--       cross_profiles. If not, they will be added to cross_profiles.
     4924!--       Check if all profiles defined in data_output_pr are defined in cross_profiles. If not,
     4925!-        they will be added to cross_profiles.
    52884926          DO  i = 1, dopr_n
    52894927             DO  j = 1, cross_profiles_count
    52904928
    5291                 IF ( TRIM(cross_profiles_char(j)) == TRIM(data_output_pr(i)))  &
    5292                 THEN
     4929                IF ( TRIM( cross_profiles_char(j) ) == TRIM( data_output_pr(i) ) )  THEN
    52934930                   EXIT
    52944931                ENDIF
    52954932
    5296                 IF (( j == cross_profiles_count ) .AND.                        &
    5297                     ( cross_profiles_count <= crmax - 1))  THEN
     4933                IF ( ( j == cross_profiles_count )  .AND.  ( cross_profiles_count <= crmax - 1) )  &
     4934                THEN
    52984935                   cross_profiles_count = cross_profiles_count + 1
    52994936                   cross_profiles_maxi  = cross_profiles_maxi  + 1
    5300                    cross_profiles_char(MIN( crmax, cross_profiles_count )) =   &
    5301                                                       TRIM( data_output_pr(i) )
    5302                    cross_profiles_numb(MIN( crmax, cross_profiles_count )) =   &
    5303                                                       cross_profiles_maxi
     4937                   cross_profiles_char(MIN( crmax, cross_profiles_count )) =                       &
     4938                                                                           TRIM( data_output_pr(i) )
     4939                   cross_profiles_numb(MIN( crmax, cross_profiles_count )) = cross_profiles_maxi
    53044940                ENDIF
    53054941
     
    53084944
    53094945          IF ( cross_profiles_count >= crmax )  THEN
    5310              message_string = 'It is not allowed to arrange more than '        &
    5311                               // '100 profiles with & cross_profiles. Apart'   &
    5312                               // ' from that, all profiles are saved & to '    &
    5313                               // 'the netCDF file.'
     4946             message_string = 'It is not allowed to arrange more than ' //                         &
     4947                              '100 profiles with & cross_profiles. Apart' //                       &
     4948                              ' from that, all profiles are saved & to ' // 'the netCDF file.'
    53144949             CALL message( 'define_netcdf_header', 'PA0354', 0, 0, 0, 6, 0 )
    53154950          ENDIF
    53164951
    53174952!
    5318 !--       Writing cross_profiles to netcdf header. This information can be
    5319 !--       used by palmplot. Each profile is separated by ",", each cross is
    5320 !--       separated by ";".
     4953!--       Writing cross_profiles to netcdf header. This information can be used by palmplot. Each
     4954!--       profile is separated by ",", each cross is separated by ";".
    53214955          char_cross_profiles = ';'
    53224956          id_last = 1
     
    53274961             IF ( cross_profiles_numb(i) /= 999999 )  THEN
    53284962                IF ( TRIM( char_cross_profiles ) == ';' )  THEN
    5329                    char_cross_profiles = TRIM( char_cross_profiles ) // &
     4963                   char_cross_profiles = TRIM( char_cross_profiles ) //                            &
    53304964                                         TRIM( cross_profiles_char(i) )
    53314965                ELSEIF ( id_last == cross_profiles_numb(i) )  THEN
    5332                    char_cross_profiles = TRIM( char_cross_profiles ) // &
     4966                   char_cross_profiles = TRIM( char_cross_profiles ) //                            &
    53334967                                         ',' // TRIM( cross_profiles_char(i) )
    53344968                ELSE
    5335                    char_cross_profiles = TRIM( char_cross_profiles ) // &
     4969                   char_cross_profiles = TRIM( char_cross_profiles ) //                            &
    53364970                                         ';' // TRIM( cross_profiles_char(i) )
    53374971                ENDIF
     
    53434977          char_cross_profiles = TRIM( char_cross_profiles ) // ';'
    53444978
    5345           nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',   &
     4979          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',                        &
    53464980                                  TRIM( char_cross_profiles ) )
    53474981          CALL netcdf_handle_error( 'netcdf_define_header', 521 )
     
    53494983!
    53504984!--       Define time coordinate for profiles (unlimited dimension)
    5351           CALL netcdf_create_dim( id_set_pr, 'time', NF90_UNLIMITED,           &
    5352                                   id_dim_time_pr, 220 )
    5353           CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /), 'time',     &
    5354                                   NF90_DOUBLE, id_var_time_pr, 'seconds', 'time',  &
    5355                                   221, 222, 000 )
     4985          CALL netcdf_create_dim( id_set_pr, 'time', NF90_UNLIMITED, id_dim_time_pr, 220 )
     4986          CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /), 'time', NF90_DOUBLE,            &
     4987                                  id_var_time_pr, 'seconds', 'time', 221, 222, 000 )
    53564988          CALL netcdf_create_att( id_set_pr, id_var_time_pr, 'standard_name', 'time', 000)
    53574989          CALL netcdf_create_att( id_set_pr, id_var_time_pr, 'axis', 'T', 000)
     
    53654997!
    53664998!--             Define the z-axes (each variable gets its own z-axis)
    5367                 CALL netcdf_create_dim( id_set_pr,                             &
    5368                                         'z' // TRIM( data_output_pr(i) ),      &
    5369                                         nzt+2-nzb, id_dim_z_pr(i,0), 223 )
    5370                 CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0) /),     &
    5371                                         'z' // TRIM( data_output_pr(i) ),      &
    5372                                        NF90_DOUBLE, id_var_z_pr(i,0),          &
     4999                CALL netcdf_create_dim( id_set_pr, 'z' // TRIM( data_output_pr(i) ), nzt+2-nzb,    &
     5000                                        id_dim_z_pr(i,0), 223 )
     5001                CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0) /), 'z' //                  &
     5002                                        TRIM( data_output_pr(i) ), NF90_DOUBLE, id_var_z_pr(i,0),  &
    53735003                                       'meters', '', 224, 225, 000 )
    5374                 CALL netcdf_create_att( id_set_pr, id_var_z_pr(i,0), 'axis',   &
    5375                                         'Z', 000)
     5004                CALL netcdf_create_att( id_set_pr, id_var_z_pr(i,0), 'axis', 'Z', 000)
    53765005!
    53775006!--             Define the variable
    5378                 CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0),        &
    5379                                         id_dim_time_pr /), data_output_pr(i),  &
    5380                                         nc_precision(5), id_var_dopr(i,0),     &
    5381                                         TRIM( dopr_unit(i) ),                  &
    5382                                         TRIM( data_output_pr(i) ), 226, 227,   &
     5007                CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0), id_dim_time_pr /),         &
     5008                                        data_output_pr(i), nc_precision(5), id_var_dopr(i,0),      &
     5009                                        TRIM( dopr_unit(i) ), TRIM( data_output_pr(i) ), 226, 227, &
    53835010                                        228 )
    53845011
     
    53875014             ELSE
    53885015!
    5389 !--             If statistic regions are defined, add suffix _SR+#SR to the
    5390 !--             names
     5016!--             If statistic regions are defined, add suffix _SR+#SR to the names.
    53915017                DO  j = 0, statistic_regions
    53925018                   WRITE ( suffix, '(''_'',I2.2)' )  j
     
    53945020!
    53955021!--                Define the z-axes (each variable gets it own z-axis)
    5396                    CALL netcdf_create_dim( id_set_pr, 'z' //                   &
    5397                                            TRIM(data_output_pr(i)) // suffix,  &
     5022                   CALL netcdf_create_dim( id_set_pr, 'z' // TRIM(data_output_pr(i)) // suffix,    &
    53985023                                           nzt+2-nzb, id_dim_z_pr(i,j), 229 )
    5399                    CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j) /),  &
    5400                                            'z' // TRIM(data_output_pr(i)) //   &
    5401                                            suffix, NF90_DOUBLE,                &
    5402                                            id_var_z_pr(i,j), 'meters', '',     &
    5403                                            230, 231, 000 )
    5404                    CALL netcdf_create_att( id_set_pr, id_var_z_pr(i,j), 'axis',&
    5405                                            'Z', 000)
     5024                   CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j) /),'z' //                &
     5025                                           TRIM(data_output_pr(i)) // suffix, NF90_DOUBLE,         &
     5026                                           id_var_z_pr(i,j), 'meters', '', 230, 231, 000 )
     5027                   CALL netcdf_create_att( id_set_pr, id_var_z_pr(i,j), 'axis', 'Z', 000)
    54065028!
    54075029!--                Define the variable
    5408                    CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j),     &
    5409                                            id_dim_time_pr /),                  &
    5410                                            TRIM(data_output_pr(i)) // suffix,  &
    5411                                            nc_precision(5), id_var_dopr(i,j),  &
    5412                                            TRIM( dopr_unit(i) ),               &
    5413                                            TRIM( data_output_pr(i) ) //        &
    5414                                            ' SR ', 232, 233, 234 )
    5415 
    5416                    var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
    5417                               suffix // ';'
     5030                   CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j), id_dim_time_pr /),      &
     5031                                           TRIM(data_output_pr(i)) // suffix, nc_precision(5),     &
     5032                                           id_var_dopr(i,j), TRIM( dopr_unit(i) ),                 &
     5033                                           TRIM( data_output_pr(i) ) // ' SR ', 232, 233, 234 )
     5034
     5035                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // suffix // ';'
    54185036
    54195037                ENDDO
     
    54245042
    54255043!
    5426 !--       Write the list of variables as global attribute (this is used by
    5427 !--       restart runs)
     5044!--       Write the list of variables as global attribute (this is used by restart runs).
    54285045          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', var_list )
    54295046          CALL netcdf_handle_error( 'netcdf_define_header', 235 )
     
    54335050          DO  i = 1, dopr_norm_num
    54345051
    5435              CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /),          &
    5436                                      'NORM_' // TRIM( dopr_norm_names(i) ),    &
    5437                                      nc_precision(5), id_var_norm_dopr(i),     &
    5438                                      '', TRIM( dopr_norm_longnames(i) ), 236,  &
     5052             CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /), 'NORM_' //                   &
     5053                                     TRIM( dopr_norm_names(i) ), nc_precision(5),                  &
     5054                                     id_var_norm_dopr(i), '', TRIM( dopr_norm_longnames(i) ), 236, &
    54395055                                     000, 237 )
    54405056
     
    54515067             DO  j = 0, statistic_regions
    54525068
    5453                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_z_pr(i,j),      &
    5454                                         hom(nzb:nzt+1,2,dopr_index(i),0), &
    5455                                         start = (/ 1 /),                  &
     5069                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_z_pr(i,j),                               &
     5070                                        hom(nzb:nzt+1,2,dopr_index(i),0),                          &
     5071                                        start = (/ 1 /),                                           &
    54565072                                        count = (/ nzt-nzb+2 /) )
    54575073                CALL netcdf_handle_error( 'netcdf_define_header', 239 )
     
    54655081!
    54665082!--       Get the list of variables and compare with the actual run.
    5467 !--       First var_list_old has to be reset, since GET_ATT does not assign
    5468 !--       trailing blanks.
     5083!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    54695084          var_list_old = ' '
    5470           nc_stat = NF90_GET_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', &
    5471                                   var_list_old )
     5085          nc_stat = NF90_GET_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', var_list_old )
    54725086          CALL netcdf_handle_error( 'netcdf_define_header', 240 )
    54735087
     
    54805094                DO  j = 0, statistic_regions
    54815095                   WRITE ( suffix, '(''_'',I2.2)' )  j
    5482                    var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
    5483                               suffix // ';'
     5096                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // suffix // ';'
    54845097                ENDDO
    54855098             ENDIF
     
    54885101
    54895102          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    5490              message_string = 'netCDF file for vertical profiles ' //          &
    5491                               'from previous run found,' //                    &
    5492                               '&but this file cannot be extended due to' //    &
    5493                               ' variable mismatch.' //                         &
    5494                               '&New file is created instead.'
     5103             message_string = 'netCDF file for vertical profiles ' // 'from previous run found,' //&
     5104                              '&but this file cannot be extended due to' //                        &
     5105                              ' variable mismatch.' // '&New file is created instead.'
    54955106             CALL message( 'define_netcdf_header', 'PA0254', 0, 1, 0, 6, 0 )
    54965107             extend = .FALSE.
     
    54995110
    55005111!
    5501 !--       Get the id of the time coordinate (unlimited coordinate) and its
    5502 !--       last index on the file. The next time level is dopr..count+1.
    5503 !--       The current time must be larger than the last output time
    5504 !--       on the file.
     5112!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     5113!--       The next time level is dopr..count+1.
     5114!--       The current time must be larger than the last output time on the file.
    55055115          nc_stat = NF90_INQ_VARID( id_set_pr, 'time', id_var_time_pr )
    55065116          CALL netcdf_handle_error( 'netcdf_define_header', 241 )
    55075117
    5508           nc_stat = NF90_INQUIRE_VARIABLE( id_set_pr, id_var_time_pr, &
    5509                                            dimids = id_dim_time_old )
     5118          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pr, id_var_time_pr, dimids = id_dim_time_old )
    55105119          CALL netcdf_handle_error( 'netcdf_define_header', 242 )
    55115120          id_dim_time_pr = id_dim_time_old(1)
    55125121
    5513           nc_stat = NF90_INQUIRE_DIMENSION( id_set_pr, id_dim_time_pr, &
    5514                                             len = dopr_time_count )
     5122          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pr, id_dim_time_pr, LEN = dopr_time_count )
    55155123          CALL netcdf_handle_error( 'netcdf_define_header', 243 )
    55165124
    5517           nc_stat = NF90_GET_VAR( id_set_pr, id_var_time_pr,        &
    5518                                   last_time_coordinate,             &
    5519                                   start = (/ dopr_time_count /), &
     5125          nc_stat = NF90_GET_VAR( id_set_pr, id_var_time_pr,                                       &
     5126                                  last_time_coordinate,                                            &
     5127                                  start = (/ dopr_time_count /),                                   &
    55205128                                  count = (/ 1 /) )
    55215129          CALL netcdf_handle_error( 'netcdf_define_header', 244 )
    55225130
    55235131          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    5524              message_string = 'netCDF file for vertical profiles ' //          &
    5525                               'from previous run found,' //                    &
    5526                               '&but this file cannot be extended becaus' //    &
    5527                               'e the current output time' //                   &
    5528                               '&is less or equal than the last output t' //    &
    5529                               'ime on this file.' //                           &
     5132             message_string = 'netCDF file for vertical profiles ' // 'from previous run found,' //&
     5133                              '&but this file cannot be extended because' //                       &
     5134                              ' the current output time' //                                        &
     5135                              '&is less or equal than the last output ' // 'time on this file.' // &
    55305136                              '&New file is created instead.'
    55315137             CALL message( 'define_netcdf_header', 'PA0255', 0, 1, 0, 6, 0 )
     
    55425148
    55435149             IF ( statistic_regions == 0 )  THEN
    5544                 nc_stat = NF90_INQ_VARID( id_set_pr, data_output_pr(i),        &
    5545                                           id_var_dopr(i,0) )
     5150                nc_stat = NF90_INQ_VARID( id_set_pr, data_output_pr(i), id_var_dopr(i,0) )
    55465151                CALL netcdf_handle_error( 'netcdf_define_header', 245 )
    55475152             ELSE
     
    55495154                   WRITE ( suffix, '(''_'',I2.2)' )  j
    55505155                   netcdf_var_name = TRIM( data_output_pr(i) ) // suffix
    5551                    nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name,       &
    5552                                              id_var_dopr(i,j) )
     5156                   nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name, id_var_dopr(i,j) )
    55535157                   CALL netcdf_handle_error( 'netcdf_define_header', 246 )
    55545158                ENDDO
     
    55605164!--       Get ids of the normalization variables
    55615165          DO  i = 1, dopr_norm_num
    5562              nc_stat = NF90_INQ_VARID( id_set_pr,                             &
    5563                                        'NORM_' // TRIM( dopr_norm_names(i) ), &
     5166             nc_stat = NF90_INQ_VARID( id_set_pr, 'NORM_' // TRIM( dopr_norm_names(i) ),           &
    55645167                                       id_var_norm_dopr(i) )
    55655168             CALL netcdf_handle_error( 'netcdf_define_header', 247 )
     
    55675170
    55685171!
    5569 !--       Update the title attribute on file
    5570 !--       In order to avoid 'data mode' errors if updated attributes are larger
    5571 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    5572 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    5573 !--       performance loss due to data copying; an alternative strategy would be
    5574 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     5172!--       Update the title attribute on file.
     5173!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     5174!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     5175!--       calls. This implies a possible performance loss due to data copying; an alternative
     5176!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    55755177          IF ( averaging_interval_pr == 0.0_wp )  THEN
    55765178             time_average_text = ' '
    55775179          ELSE
    5578              WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
    5579                                                             averaging_interval_pr
     5180             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' )  averaging_interval_pr
    55805181          ENDIF
    55815182          nc_stat = NF90_REDEF( id_set_pr )
    55825183          CALL netcdf_handle_error( 'netcdf_define_header', 437 )
    5583           nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title',             &
    5584                                   TRIM( run_description_header ) //            &
    5585                                   TRIM( time_average_text ) )
     5184          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title',                                 &
     5185                                  TRIM( run_description_header ) // TRIM( time_average_text ) )
    55865186          CALL netcdf_handle_error( 'netcdf_define_header', 248 )
    55875187
    55885188          nc_stat = NF90_ENDDEF( id_set_pr )
    55895189          CALL netcdf_handle_error( 'netcdf_define_header', 438 )
    5590           message_string = 'netCDF file for vertical profiles ' //             &
    5591                            'from previous run found.' //                       &
     5190          message_string = 'netCDF file for vertical profiles ' // 'from previous run found.' //   &
    55925191                           '&This file will be extended.'
    55935192          CALL message( 'define_netcdf_header', 'PA0256', 0, 0, 0, 6, 0 )
     
    56005199          CALL netcdf_create_global_atts( id_set_ts, 'podsts', TRIM(run_description_header), 329 )
    56015200
    5602           ! nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title',             &
    5603           !                         TRIM( run_description_header ) )
     5201          ! nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    56045202          ! CALL netcdf_handle_error( 'netcdf_define_header', 249 )
    56055203
    56065204!
    56075205!--       Define time coordinate for time series (unlimited dimension)
    5608           CALL netcdf_create_dim( id_set_ts, 'time', NF90_UNLIMITED,           &
    5609                                   id_dim_time_ts, 250 )
    5610           CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /), 'time',     &
    5611                                   NF90_DOUBLE, id_var_time_ts, 'seconds', 'time',  &
    5612                                   251, 252, 000 )
     5206          CALL netcdf_create_dim( id_set_ts, 'time', NF90_UNLIMITED, id_dim_time_ts, 250 )
     5207          CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /), 'time', NF90_DOUBLE,            &
     5208                                  id_var_time_ts, 'seconds', 'time', 251, 252, 000 )
    56135209          CALL netcdf_create_att( id_set_ts, id_var_time_ts, 'standard_name', 'time', 000)
    56145210          CALL netcdf_create_att( id_set_ts, id_var_time_ts, 'axis', 'T', 000)
     
    56205216             IF ( statistic_regions == 0 )  THEN
    56215217
    5622                 CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /),       &
    5623                                         dots_label(i), nc_precision(6),        &
    5624                                         id_var_dots(i,0),                      &
    5625                                         TRIM( dots_unit(i) ),                  &
     5218                CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /), dots_label(i),            &
     5219                                        nc_precision(6), id_var_dots(i,0), TRIM( dots_unit(i) ),   &
    56265220                                        TRIM( dots_label(i) ), 253, 254, 255 )
    56275221
     
    56305224             ELSE
    56315225!
    5632 !--             If statistic regions are defined, add suffix _SR+#SR to the
    5633 !--             names
     5226!--             If statistic regions are defined, add suffix _SR+#SR to the names.
    56345227                DO  j = 0, statistic_regions
    56355228                   WRITE ( suffix, '(''_'',I2.2)' )  j
    56365229
    5637                    CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /),    &
    5638                                            TRIM( dots_label(i) ) // suffix,    &
    5639                                            nc_precision(6), id_var_dots(i,j),  &
    5640                                            TRIM( dots_unit(i) ),               &
    5641                                            TRIM( dots_label(i) ) // ' SR ' //  &
     5230                   CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /), TRIM( dots_label(i) )  &
     5231                                           // suffix, nc_precision(6), id_var_dots(i,j),           &
     5232                                           TRIM( dots_unit(i) ), TRIM( dots_label(i) ) // ' SR ' //&
    56425233                                           suffix(2:2), 256, 257, 347)
    56435234
     
    56525243
    56535244!
    5654 !--       Write the list of variables as global attribute (this is used by
    5655 !--       restart runs)
     5245!--       Write the list of variables as global attribute (this is used by restart runs).
    56565246          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', var_list )
    56575247          CALL netcdf_handle_error( 'netcdf_define_header', 258 )
     
    56675257!
    56685258!--       Get the list of variables and compare with the actual run.
    5669 !--       First var_list_old has to be reset, since GET_ATT does not assign
    5670 !--       trailing blanks.
     5259!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    56715260          var_list_old = ' '
    5672           nc_stat = NF90_GET_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', &
    5673                                   var_list_old )
     5261          nc_stat = NF90_GET_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', var_list_old )
    56745262          CALL netcdf_handle_error( 'netcdf_define_header', 260 )
    56755263
     
    56835271                DO  j = 0, statistic_regions
    56845272                   WRITE ( suffix, '(''_'',I2.2)' )  j
    5685                    var_list = TRIM( var_list ) // TRIM( dots_label(i) ) //     &
    5686                               suffix // ';'
     5273                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // suffix // ';'
    56875274                ENDDO
    56885275             ENDIF
     
    56915278
    56925279          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    5693              message_string = 'netCDF file for time series ' //                &
    5694                               'from previous run found,' //                    &
    5695                               '&but this file cannot be extended due to' //    &
    5696                               ' variable mismatch.' //                         &
    5697                               '&New file is created instead.'
     5280             message_string = 'netCDF file for time series ' // 'from previous run found,' //      &
     5281                              '&but this file cannot be extended due to' //                        &
     5282                              ' variable mismatch.' // '&New file is created instead.'
    56985283             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
    56995284             extend = .FALSE.
     
    57025287
    57035288!
    5704 !--       Get the id of the time coordinate (unlimited coordinate) and its
    5705 !--       last index on the file. The next time level is dots..count+1.
    5706 !--       The current time must be larger than the last output time
    5707 !--       on the file.
     5289!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     5290!--       The next time level is dots..count+1.
     5291!--       The current time must be larger than the last output time on the file.
    57085292          nc_stat = NF90_INQ_VARID( id_set_ts, 'time', id_var_time_ts )
    57095293          CALL netcdf_handle_error( 'netcdf_define_header', 261 )
    57105294
    5711           nc_stat = NF90_INQUIRE_VARIABLE( id_set_ts, id_var_time_ts,          &
    5712                                            dimids = id_dim_time_old )
     5295          nc_stat = NF90_INQUIRE_VARIABLE( id_set_ts, id_var_time_ts, dimids = id_dim_time_old )
    57135296          CALL netcdf_handle_error( 'netcdf_define_header', 262 )
    57145297          id_dim_time_ts = id_dim_time_old(1)
    57155298
    5716           nc_stat = NF90_INQUIRE_DIMENSION( id_set_ts, id_dim_time_ts,         &
    5717                                             len = dots_time_count )
     5299          nc_stat = NF90_INQUIRE_DIMENSION( id_set_ts, id_dim_time_ts, LEN = dots_time_count )
    57185300          CALL netcdf_handle_error( 'netcdf_define_header', 263 )
    57195301
    5720           nc_stat = NF90_GET_VAR( id_set_ts, id_var_time_ts,                   &
    5721                                   last_time_coordinate,                        &
    5722                                   start = (/ dots_time_count /),               &
     5302          nc_stat = NF90_GET_VAR( id_set_ts, id_var_time_ts,                                       &
     5303                                  last_time_coordinate,                                            &
     5304                                  start = (/ dots_time_count /),                                   &
    57235305                                  count = (/ 1 /) )
    57245306          CALL netcdf_handle_error( 'netcdf_define_header', 264 )
    57255307
    57265308          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    5727              message_string = 'netCDF file for time series ' //                &
    5728                               'from previous run found,' //                    &
    5729                               '&but this file cannot be extended becaus' //    &
    5730                               'e the current output time' //                   &
    5731                               '&is less or equal than the last output t' //    &
    5732                               'ime on this file.' //                           &
     5309             message_string = 'netCDF file for time series ' // 'from previous run found,' //      &
     5310                              '&but this file cannot be extended because' //                       &
     5311                              ' the current output time' //                                        &
     5312                              '&is less or equal than the last output ' // 'time on this file.' // &
    57335313                              '&New file is created instead.'
    57345314             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
     
    57455325
    57465326             IF ( statistic_regions == 0 )  THEN
    5747                 nc_stat = NF90_INQ_VARID( id_set_ts, dots_label(i), &
    5748                                           id_var_dots(i,0) )
     5327                nc_stat = NF90_INQ_VARID( id_set_ts, dots_label(i), id_var_dots(i,0) )
    57495328                CALL netcdf_handle_error( 'netcdf_define_header', 265 )
    57505329             ELSE
     
    57525331                   WRITE ( suffix, '(''_'',I2.2)' )  j
    57535332                   netcdf_var_name = TRIM( dots_label(i) ) // suffix
    5754                    nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, &
    5755                                              id_var_dots(i,j) )
     5333                   nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, id_var_dots(i,j) )
    57565334                   CALL netcdf_handle_error( 'netcdf_define_header', 266 )
    57575335                ENDDO
     
    57615339
    57625340!
    5763 !--       Update the title attribute on file
    5764 !--       In order to avoid 'data mode' errors if updated attributes are larger
    5765 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    5766 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    5767 !--       performance loss due to data copying; an alternative strategy would be
    5768 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     5341!--       Update the title attribute on file.
     5342!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     5343!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     5344!--       calls. This implies a possible performance loss due to data copying; an alternative
     5345!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    57695346          nc_stat = NF90_REDEF( id_set_ts )
    57705347          CALL netcdf_handle_error( 'netcdf_define_header', 439 )
    5771           nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title',             &
    5772                                   TRIM( run_description_header ) )
     5348          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    57735349          CALL netcdf_handle_error( 'netcdf_define_header', 267 )
    57745350          nc_stat = NF90_ENDDEF( id_set_ts )
    57755351          CALL netcdf_handle_error( 'netcdf_define_header', 440 )
    5776           message_string = 'netCDF file for time series ' //                   &
    5777                            'from previous run found.' //                       &
     5352          message_string = 'netCDF file for time series ' // 'from previous run found.' //         &
    57785353                           '&This file will be extended.'
    57795354          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
     
    57855360!--       Define some global attributes of the dataset
    57865361          IF ( averaging_interval_sp /= 0.0_wp )  THEN
    5787              WRITE (time_average_text,'('', '',F7.1,'' s average'')')          &
    5788                                                             averaging_interval_sp
    5789              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',          &
    5790                                      TRIM( run_description_header ) //         &
    5791                                      TRIM( time_average_text ) )
     5362             WRITE ( time_average_text,'('', '',F7.1,'' s average'')' )  averaging_interval_sp
     5363             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',                              &
     5364                                     TRIM( run_description_header ) // TRIM( time_average_text ) )
    57925365             CALL netcdf_handle_error( 'netcdf_define_header', 268 )
    57935366
    57945367             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
    5795              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', &
    5796                                      TRIM( time_average_text ) )
     5368             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', TRIM( time_average_text ) )
    57975369          ELSE
    5798              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title', &
     5370             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',                              &
    57995371                                     TRIM( run_description_header ) )
    58005372          ENDIF
     
    58035375!
    58045376!--       Define time coordinate for spectra (unlimited dimension)
    5805           CALL netcdf_create_dim( id_set_sp, 'time', NF90_UNLIMITED,           &
    5806                                   id_dim_time_sp, 270 )
    5807           CALL netcdf_create_var( id_set_sp, (/ id_dim_time_sp /), 'time',     &
    5808                                   NF90_DOUBLE, id_var_time_sp, 'seconds', 'time',  &
    5809                                   271, 272, 000 )
     5377          CALL netcdf_create_dim( id_set_sp, 'time', NF90_UNLIMITED, id_dim_time_sp, 270 )
     5378          CALL netcdf_create_var( id_set_sp, (/ id_dim_time_sp /), 'time', NF90_DOUBLE,            &
     5379                                  id_var_time_sp, 'seconds', 'time', 271, 272, 000 )
    58105380          CALL netcdf_create_att( id_set_sp, id_var_time_sp, 'standard_name', 'time', 000)
    58115381          CALL netcdf_create_att( id_set_sp, id_var_time_sp, 'axis', 'T', 000)
    58125382!
    58135383!--       Define the spatial dimensions and coordinates for spectra.
    5814 !--       First, determine the number of vertical levels for which spectra
    5815 !--       are to be output.
     5384!--       First, determine the number of vertical levels for which spectra are to be output.
    58165385          ns = 1
    58175386          DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
     
    58235392!--       Define vertical coordinate grid (zu grid)
    58245393          CALL netcdf_create_dim( id_set_sp, 'zu_sp', ns, id_dim_zu_sp, 273 )
    5825           CALL netcdf_create_var( id_set_sp, (/ id_dim_zu_sp /), 'zu_sp',      &
    5826                                   NF90_DOUBLE, id_var_zu_sp, 'meters', '',     &
    5827                                   274, 275, 000 )
     5394          CALL netcdf_create_var( id_set_sp, (/ id_dim_zu_sp /), 'zu_sp', NF90_DOUBLE,             &
     5395                                  id_var_zu_sp, 'meters', '', 274, 275, 000 )
    58285396          CALL netcdf_create_att( id_set_sp, id_var_zu_sp, 'axis', 'Z', 000)
    58295397!
    58305398!--       Define vertical coordinate grid (zw grid)
    58315399          CALL netcdf_create_dim( id_set_sp, 'zw_sp', ns, id_dim_zw_sp, 276 )
    5832           CALL netcdf_create_var( id_set_sp, (/ id_dim_zw_sp /), 'zw_sp',      &
    5833                                   NF90_DOUBLE, id_var_zw_sp, 'meters', '',     &
    5834                                   277, 278, 000 )
     5400          CALL netcdf_create_var( id_set_sp, (/ id_dim_zw_sp /), 'zw_sp', NF90_DOUBLE,             &
     5401                                  id_var_zw_sp, 'meters', '', 277, 278, 000 )
    58355402          CALL netcdf_create_att( id_set_sp, id_var_zw_sp, 'axis', 'Z', 000)
    58365403!
    58375404!--       Define x-axis
    58385405          CALL netcdf_create_dim( id_set_sp, 'k_x', nx/2, id_dim_x_sp, 279 )
    5839           CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp /), 'k_x',         &
    5840                                   NF90_DOUBLE, id_var_x_sp, 'm-1', '', 280,    &
    5841                                   281, 000 )
     5406          CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp /), 'k_x', NF90_DOUBLE,                &
     5407                                  id_var_x_sp, 'm-1', '', 280, 281, 000 )
    58425408          CALL netcdf_create_att( id_set_sp, id_var_x_sp, 'axis', 'X', 000)
    58435409!
    58445410!--       Define y-axis
    58455411          CALL netcdf_create_dim( id_set_sp, 'k_y', ny/2, id_dim_y_sp, 282 )
    5846           CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp /), 'k_y',         &
    5847                                   NF90_DOUBLE, id_var_y_sp, 'm-1', '', 283,    &
    5848                                   284, 000 )
     5412          CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp /), 'k_y', NF90_DOUBLE,                &
     5413                                  id_var_y_sp, 'm-1', '', 283, 284, 000 )
    58495414          CALL netcdf_create_att( id_set_sp, id_var_y_sp, 'axis', 'Y', 000)
    58505415!
     
    58735438                CASE DEFAULT
    58745439!
    5875 !--                Check for user-defined quantities (found, grid_x and grid_y
    5876 !--                are dummies)
     5440!--                Check for user-defined quantities (found, grid_x and grid_y are dummies).
    58775441                   IF ( user_module_enabled )  THEN
    5878                       CALL user_define_netcdf_grid( data_output_sp(i), found, &
    5879                                                     grid_x, grid_y, grid_z )
     5442                      CALL user_define_netcdf_grid( data_output_sp(i), found, grid_x, grid_y,      &
     5443                                                    grid_z )
    58805444                   ENDIF
    58815445
     
    58885452                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
    58895453                IF ( TRIM( grid_z ) == 'zw' )  THEN
    5890                    CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp,          &
    5891                                            id_dim_zw_sp, id_dim_time_sp /),    &
    5892                                            netcdf_var_name, nc_precision(7),   &
    5893                                            id_var_dospx(i), 'unknown',         &
    5894                                            netcdf_var_name, 285, 286, 287 )
     5454                   CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp, id_dim_zw_sp,                &
     5455                                           id_dim_time_sp /), netcdf_var_name, nc_precision(7),    &
     5456                                           id_var_dospx(i), 'unknown', netcdf_var_name, 285, 286,  &
     5457                                           287 )
    58955458                ELSE
    5896                    CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp,          &
    5897                                            id_dim_zu_sp, id_dim_time_sp /),    &
    5898                                            netcdf_var_name, nc_precision(7),   &
    5899                                            id_var_dospx(i), 'unknown',         &
    5900                                            netcdf_var_name, 285, 286, 287 )
     5459                   CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp, id_dim_zu_sp,                &
     5460                                           id_dim_time_sp /), netcdf_var_name, nc_precision(7),    &
     5461                                           id_var_dospx(i), 'unknown', netcdf_var_name, 285, 286,  &
     5462                                           287 )
    59015463                ENDIF
    59025464
     
    59115473                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
    59125474                IF ( TRIM( grid_z ) == 'zw' )  THEN
    5913                    CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp,          &
    5914                                            id_dim_zw_sp, id_dim_time_sp /),    &
    5915                                            netcdf_var_name, nc_precision(7),   &
    5916                                            id_var_dospy(i), 'unknown',         &
    5917                                            netcdf_var_name, 288, 289, 290 )
     5475                   CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp, id_dim_zw_sp,                &
     5476                                           id_dim_time_sp /), netcdf_var_name, nc_precision(7),    &
     5477                                           id_var_dospy(i), 'unknown', netcdf_var_name, 288, 289,  &
     5478                                           290 )
    59185479                ELSE
    5919                    CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp,          &
    5920                                            id_dim_zu_sp, id_dim_time_sp /),    &
    5921                                            netcdf_var_name, nc_precision(7),   &
    5922                                            id_var_dospy(i), 'unknown',         &
    5923                                            netcdf_var_name, 288, 289, 290 )
     5480                   CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp, id_dim_zu_sp,                &
     5481                                           id_dim_time_sp /), netcdf_var_name, nc_precision(7),    &
     5482                                           id_var_dospy(i), 'unknown', netcdf_var_name, 288, 289,  &
     5483                                           290 )
    59245484                ENDIF
    59255485
     
    59335493
    59345494!
    5935 !--       Write the list of variables as global attribute (this is used by
    5936 !--       restart runs)
     5495!--       Write the list of variables as global attribute (this is used by restart runs)
    59375496          nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', var_list )
    59385497          CALL netcdf_handle_error( 'netcdf_define_header', 291 )
     
    59505509!--       Write zu data
    59515510          netcdf_data(1:ns) = zu( comp_spectra_level(1:ns) )
    5952           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zu_sp, netcdf_data, &
    5953                                   start = (/ 1 /), count = (/ ns /) )
     5511          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zu_sp, netcdf_data,                            &
     5512                                  start = (/ 1 /),                                                 &
     5513                                  count = (/ ns /) )
    59545514          CALL netcdf_handle_error( 'netcdf_define_header', 293 )
    59555515
     
    59575517!--       Write zw data
    59585518          netcdf_data(1:ns) = zw( comp_spectra_level(1:ns) )
    5959           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zw_sp, netcdf_data, &
    5960                                   start = (/ 1 /), count = (/ ns /) )
     5519          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zw_sp, netcdf_data,                            &
     5520                                  start = (/ 1 /),                                                 &
     5521                                  count = (/ ns /) )
    59615522          CALL netcdf_handle_error( 'netcdf_define_header', 294 )
    59625523
     
    59705531          ENDDO
    59715532
    5972           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_x_sp, netcdf_data, &
    5973                                   start = (/ 1 /), count = (/ nx/2 /) )
     5533          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_x_sp, netcdf_data,                             &
     5534                                  start = (/ 1 /),                                                 &
     5535                                  count = (/ nx/2 /) )
    59745536          CALL netcdf_handle_error( 'netcdf_define_header', 295 )
    59755537
     
    59815543          ENDDO
    59825544
    5983           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_y_sp, netcdf_data, &
    5984                                   start = (/ 1 /), count = (/ ny/2 /) )
     5545          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_y_sp, netcdf_data,                             &
     5546                                  start = (/ 1 /),                                                 &
     5547                                  count = (/ ny/2 /) )
    59855548          CALL netcdf_handle_error( 'netcdf_define_header', 296 )
    59865549
     
    59925555!
    59935556!--       Get the list of variables and compare with the actual run.
    5994 !--       First var_list_old has to be reset, since GET_ATT does not assign
    5995 !--       trailing blanks.
     5557!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    59965558          var_list_old = ' '
    5997           nc_stat = NF90_GET_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', &
    5998                                   var_list_old )
     5559          nc_stat = NF90_GET_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', var_list_old )
    59995560          CALL netcdf_handle_error( 'netcdf_define_header', 297 )
    60005561          var_list = ';'
    60015562          i = 1
    6002           DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
     5563          DO  WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
    60035564
    60045565             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
     
    60175578
    60185579          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    6019              message_string = 'netCDF file for spectra  ' //                   &
    6020                               'from previous run found,' //                    &
    6021                               '&but this file cannot be extended due to' //    &
    6022                               ' variable mismatch.' //                         &
    6023                               '&New file is created instead.'
     5580             message_string = 'netCDF file for spectra  ' // 'from previous run found,' //         &
     5581                              '&but this file cannot be extended due to' //                        &
     5582                              ' variable mismatch.' // '&New file is created instead.'
    60245583             CALL message( 'define_netcdf_header', 'PA0260', 0, 1, 0, 6, 0 )
    60255584             extend = .FALSE.
     
    60285587
    60295588!
    6030 !--       Determine the number of current vertical levels for which spectra
    6031 !--       shall be output
     5589!--       Determine the number of current vertical levels for which spectra shall be output.
    60325590          ns = 1
    6033           DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
     5591          DO  WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
    60345592             ns = ns + 1
    60355593          ENDDO
     
    60415599          CALL netcdf_handle_error( 'netcdf_define_header', 298 )
    60425600
    6043           nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_zu_sp, &
    6044                                            dimids = id_dim_zu_sp_old )
     5601          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_zu_sp, dimids = id_dim_zu_sp_old )
    60455602          CALL netcdf_handle_error( 'netcdf_define_header', 299 )
    60465603          id_dim_zu_sp = id_dim_zu_sp_old(1)
    60475604
    6048           nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_zu_sp, &
    6049                                             len = ns_old )
     5605          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_zu_sp, LEN = ns_old )
    60505606          CALL netcdf_handle_error( 'netcdf_define_header', 300 )
    60515607
    60525608          IF ( ns /= ns_old )  THEN
    6053              message_string = 'netCDF file for spectra ' //                    &
    6054                               ' from previous run found,' //                   &
    6055                               '&but this file cannot be extended due to' //    &
    6056                               ' mismatch in number of' //                      &
    6057                               ' vertical levels.' //                           &
     5609             message_string = 'netCDF file for spectra ' // ' from previous run found,' //         &
     5610                              '&but this file cannot be extended due to' //                        &
     5611                              ' mismatch in number of' // ' vertical levels.' //                   &
    60585612                              '&New file is created instead.'
    60595613             CALL message( 'define_netcdf_header', 'PA0261', 0, 1, 0, 6, 0 )
     
    60715625          DO  i = 1, ns
    60725626             IF ( zu(comp_spectra_level(i)) /= netcdf_data(i) )  THEN
    6073                 message_string = 'netCDF file for spectra ' //                 &
    6074                                  ' from previous run found,' //                &
    6075                                  '&but this file cannot be extended due to' // &
    6076                                  ' mismatch in heights of' //                  &
    6077                                  ' vertical levels.' //                        &
     5627                message_string = 'netCDF file for spectra ' // ' from previous run found,' //      &
     5628                                 '&but this file cannot be extended due to' //                     &
     5629                                 ' mismatch in heights of' // ' vertical levels.' //               &
    60785630                                 '&New file is created instead.'
    60795631                CALL message( 'define_netcdf_header', 'PA0262', 0, 1, 0, 6, 0 )
     
    60865638
    60875639!
    6088 !--       Get the id of the time coordinate (unlimited coordinate) and its
    6089 !--       last index on the file. The next time level is plsp..count+1.
    6090 !--       The current time must be larger than the last output time
    6091 !--       on the file.
     5640!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     5641!--       The next time level is plsp..count+1.
     5642!--       The current time must be larger than the last output time on the file.
    60925643          nc_stat = NF90_INQ_VARID( id_set_sp, 'time', id_var_time_sp )
    60935644          CALL netcdf_handle_error( 'netcdf_define_header', 302 )
    60945645
    6095           nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_time_sp, &
    6096                                            dimids = id_dim_time_old )
     5646          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_time_sp, dimids = id_dim_time_old )
    60975647          CALL netcdf_handle_error( 'netcdf_define_header', 303 )
    60985648          id_dim_time_sp = id_dim_time_old(1)
    60995649
    6100           nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_time_sp, &
    6101                                             len = dosp_time_count )
     5650          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_time_sp, LEN = dosp_time_count )
    61025651          CALL netcdf_handle_error( 'netcdf_define_header', 304 )
    61035652
    6104           nc_stat = NF90_GET_VAR( id_set_sp, id_var_time_sp,        &
    6105                                   last_time_coordinate,             &
    6106                                   start = (/ dosp_time_count /), &
     5653          nc_stat = NF90_GET_VAR( id_set_sp, id_var_time_sp,                                       &
     5654                                  last_time_coordinate,                                            &
     5655                                  start = (/ dosp_time_count /),                                   &
    61075656                                  count = (/ 1 /) )
    61085657          CALL netcdf_handle_error( 'netcdf_define_header', 305 )
    61095658
    61105659          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    6111              message_string = 'netCDF file for spectra ' //                    &
    6112                               'from previous run found,' //                    &
    6113                               '&but this file cannot be extended becaus' //    &
    6114                               'e the current output time' //                   &
    6115                               '&is less or equal than the last output t' //    &
    6116                               'ime on this file.' //                           &
     5660             message_string = 'netCDF file for spectra ' // 'from previous run found,' //          &
     5661                              '&but this file cannot be extended because' //                       &
     5662                              ' the current output time' //                                        &
     5663                              '&is less or equal than the last output ' // 'time on this file.' // &
    61175664                              '&New file is created instead.'
    61185665             CALL message( 'define_netcdf_header', 'PA0263', 0, 1, 0, 6, 0 )
     
    61265673!--       Now get the variable ids.
    61275674          i = 1
    6128           DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
     5675          DO  WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
    61295676
    61305677             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
    61315678                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
    6132                 nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
    6133                                           id_var_dospx(i) )
     5679                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, id_var_dospx(i) )
    61345680                CALL netcdf_handle_error( 'netcdf_define_header', 306 )
    61355681             ENDIF
     
    61375683             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
    61385684                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
    6139                 nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
    6140                                           id_var_dospy(i) )
     5685                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, id_var_dospy(i) )
    61415686                CALL netcdf_handle_error( 'netcdf_define_header', 307 )
    61425687             ENDIF
     
    61475692
    61485693!
    6149 !--       Update the title attribute on file
    6150 !--       In order to avoid 'data mode' errors if updated attributes are larger
    6151 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    6152 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    6153 !--       performance loss due to data copying; an alternative strategy would be
    6154 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     5694!--       Update the title attribute on file.
     5695!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     5696!--       size, NF90_PUT_ATT is called in 'define mode'enclosed by NF90_REDEF and NF90_ENDDEF
     5697!--       calls. This implies a possible performance loss due to data copying; an alternative
     5698!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    61555699          nc_stat = NF90_REDEF( id_set_sp )
    61565700          CALL netcdf_handle_error( 'netcdf_define_header', 441 )
    61575701          IF ( averaging_interval_sp /= 0.0_wp )  THEN
    6158              WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
    6159                                                            averaging_interval_sp
    6160              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',  &
    6161                                      TRIM( run_description_header ) // &
    6162                                      TRIM( time_average_text ) )
     5702             WRITE ( time_average_text, '('', '',F7.1,'' s average'')' ) averaging_interval_sp
     5703             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',                              &
     5704                                     TRIM( run_description_header ) // TRIM( time_average_text ) )
    61635705             CALL netcdf_handle_error( 'netcdf_define_header', 308 )
    61645706
    61655707             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
    6166              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg',       &
    6167                                      TRIM( time_average_text ) )
     5708             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', TRIM( time_average_text ) )
    61685709          ELSE
    6169              nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',          &
     5710             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',                              &
    61705711                                     TRIM( run_description_header ) )
    61715712          ENDIF
     
    61735714          nc_stat = NF90_ENDDEF( id_set_sp )
    61745715          CALL netcdf_handle_error( 'netcdf_define_header', 442 )
    6175           message_string = 'netCDF file for spectra ' //                       &
    6176                            'from previous run found.' //                       &
     5716          message_string = 'netCDF file for spectra ' // 'from previous run found.' //             &
    61775717                           '&This file will be extended.'
    61785718          CALL message( 'define_netcdf_header', 'PA0264', 0, 0, 0, 6, 0 )
     
    61845724!
    61855725!--       Define some global attributes of the dataset
    6186 !          nc_stat = NF90_PUT_ATT( id_set_prt, NF90_GLOBAL, 'title',            &
    6187 !                                  TRIM( run_description_header ) )
     5726!          nc_stat = NF90_PUT_ATT( id_set_prt, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    61885727!          CALL netcdf_handle_error( 'netcdf_define_header', 310 )
    61895728
    61905729!
    61915730!--       Define time coordinate for particles (unlimited dimension)
    6192 !          CALL netcdf_create_dim( id_set_prt, 'time', NF90_UNLIMITED,          &
    6193 !                                  id_dim_time_prt, 311 )
    6194 !          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /), 'time',   &
    6195 !                                  NF90_DOUBLE, id_var_time_prt, 'seconds', '', &
    6196 !                                  312, 313, 000 )
     5731!          CALL netcdf_create_dim( id_set_prt, 'time', NF90_UNLIMITED, id_dim_time_prt, 311 )
     5732!          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /), 'time', NF90_DOUBLE,          &
     5733!                                  id_var_time_prt, 'seconds', '', 312, 313, 000 )
    61975734!
    61985735!--       netCDF4 allows more than one unlimited dimension
    6199 !          CALL netcdf_create_dim( id_set_prt, 'particle_number',            &
    6200 !                                  NF90_UNLIMITED, id_dim_prtnum, 314 )
    6201 
    6202 !          CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum /),             &
    6203 !                                  'particle_number', NF90_DOUBLE,              &
    6204 !                                  id_var_prtnum, 'particle number', '', 315,   &
    6205 !                                  316, 000 )
     5736!          CALL netcdf_create_dim( id_set_prt, 'particle_number', NF90_UNLIMITED, id_dim_prtnum,    &
     5737!                                  314 )
     5738
     5739!          CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum /), 'particle_number', NF90_DOUBLE, &
     5740!                                  id_var_prtnum, 'particle number', '', 315, 316, 000 )
    62065741!
    62075742!--       Define variable which contains the real number of particles in use
    6208 !          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /),           &
    6209 !                                  'real_num_of_prt', NF90_DOUBLE,              &
    6210 !                                  id_var_rnop_prt, 'particle number', '', 317, &
    6211 !                                  318, 000 )
     5743!          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /), 'real_num_of_prt',            &
     5744!                                  NF90_DOUBLE, id_var_rnop_prt, 'particle number', '', 317, 318,   &
     5745!                                  000 )
    62125746!
    62135747!--       Define the variables
    62145748!          DO  i = 1, 17
    62155749
    6216 !             CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum,             &
    6217 !                                     id_dim_time_prt /), prt_var_names(i),     &
    6218 !                                     nc_precision(8), id_var_prt(i),           &
    6219 !                                     TRIM( prt_var_units(i) ),                 &
    6220 !                                     TRIM( prt_var_names(i) ), 319, 320, 321 )
     5750!             CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum, id_dim_time_prt /),             &
     5751!                                     prt_var_names(i), nc_precision(8), id_var_prt(i),             &
     5752!                                     TRIM( prt_var_units(i) ), TRIM( prt_var_names(i) ), 319, 320, &
     5753!                                     321 )
    62215754
    62225755!          ENDDO
     
    62325765
    62335766!
    6234 !--       Get the id of the time coordinate (unlimited coordinate) and its
    6235 !--       last index on the file. The next time level is prt..count+1.
    6236 !--       The current time must be larger than the last output time
    6237 !--       on the file.
     5767!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     5768!--       The next time level is prt..count+1.
     5769!--       The current time must be larger than the last output time on the file.
    62385770!          nc_stat = NF90_INQ_VARID( id_set_prt, 'time', id_var_time_prt )
    62395771!          CALL netcdf_handle_error( 'netcdf_define_header', 323 )
    62405772
    6241 !          nc_stat = NF90_INQUIRE_VARIABLE( id_set_prt, id_var_time_prt, &
    6242 !                                           dimids = id_dim_time_old )
     5773!          nc_stat = NF90_INQUIRE_VARIABLE( id_set_prt, id_var_time_prt, dimids = id_dim_time_old )
    62435774!          CALL netcdf_handle_error( 'netcdf_define_header', 324 )
    62445775!          id_dim_time_prt = id_dim_time_old(1)
    62455776
    6246 !          nc_stat = NF90_INQUIRE_DIMENSION( id_set_prt, id_dim_time_prt, &
    6247 !                                            len = prt_time_count )
     5777!          nc_stat = NF90_INQUIRE_DIMENSION( id_set_prt, id_dim_time_prt, LEN = prt_time_count )
    62485778!          CALL netcdf_handle_error( 'netcdf_define_header', 325 )
    62495779
    6250 !          nc_stat = NF90_GET_VAR( id_set_prt, id_var_time_prt,  &
    6251 !                                  last_time_coordinate,         &
    6252 !                                  start = (/ prt_time_count /), &
     5780!          nc_stat = NF90_GET_VAR( id_set_prt, id_var_time_prt,                                     &
     5781!                                  last_time_coordinate,                                            &
     5782!                                  start = (/ prt_time_count /),                                    &
    62535783!                                  count = (/ 1 /) )
    62545784!          CALL netcdf_handle_error( 'netcdf_define_header', 326 )
    62555785
    62565786!          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    6257 !             message_string = 'netCDF file for particles ' //                  &
    6258 !                              'from previous run found,' //                    &
    6259 !                              '&but this file cannot be extended becaus' //    &
    6260 !                              'e the current output time' //                   &
    6261 !                              '&is less or equal than the last output t' //    &
    6262 !                              'ime on this file.' //                           &
     5787!             message_string = 'netCDF file for particles ' // 'from previous run found,' //        &
     5788!                              '&but this file cannot be extended because' //                       &
     5789!                              ' the current output time' //                                        &
     5790!                              '&is less or equal than the last output ' // 'time on this file.' // &
    62635791!                              '&New file is created instead.'
    62645792!             CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
     
    62715799!--       Dataset seems to be extendable.
    62725800!--       Now get the variable ids.
    6273 !         nc_stat = NF90_INQ_VARID( id_set_prt, 'real_num_of_prt',             &
    6274 !                                   id_var_rnop_prt )
     5801!         nc_stat = NF90_INQ_VARID( id_set_prt, 'real_num_of_prt',id_var_rnop_prt )
    62755802!         CALL netcdf_handle_error( 'netcdf_define_header', 327 )
    62765803
    62775804!          DO  i = 1, 17
    62785805
    6279 !             nc_stat = NF90_INQ_VARID( id_set_prt, prt_var_names(i),           &
    6280 !                                       id_var_prt(i) )
     5806!             nc_stat = NF90_INQ_VARID( id_set_prt, prt_var_names(i), id_var_prt(i) )
    62815807!             CALL netcdf_handle_error( 'netcdf_define_header', 328 )
    62825808
    62835809!          ENDDO
    62845810
    6285 !          message_string = 'netCDF file for particles ' //                     &
    6286 !                           'from previous run found.' //                       &
     5811!          message_string = 'netCDF file for particles ' // 'from previous run found.' //           &
    62875812!                           '&This file will be extended.'
    62885813!          CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
     
    62945819!
    62955820!--       Define some global attributes of the dataset
    6296           nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title',            &
    6297                                   TRIM( run_description_header ) )
     5821          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    62985822          CALL netcdf_handle_error( 'netcdf_define_header', 396 )
    62995823
    63005824!
    63015825!--       Define time coordinate for particle time series (unlimited dimension)
    6302           CALL netcdf_create_dim( id_set_pts, 'time', NF90_UNLIMITED,          &
    6303                                   id_dim_time_pts, 397 )
    6304           CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /), 'time',   &
    6305                                   NF90_DOUBLE, id_var_time_pts, 'seconds', 'time', &
    6306                                   398, 399, 000 )
     5826          CALL netcdf_create_dim( id_set_pts, 'time', NF90_UNLIMITED, id_dim_time_pts, 397 )
     5827          CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /), 'time', NF90_DOUBLE,          &
     5828                                  id_var_time_pts, 'seconds', 'time', 398, 399, 000 )
    63075829          CALL netcdf_create_att( id_set_pts, id_var_time_pts, 'standard_name', 'time', 000)
    63085830          CALL netcdf_create_att( id_set_pts, id_var_time_pts, 'axis', 'T', 000)
    63095831!
    6310 !--       Define the variables. If more than one particle group is defined,
    6311 !--       define seperate variables for each group
     5832!--       Define the variables. If more than one particle group is defined, define seperate
     5833!--       variables for each group.
    63125834          var_list = ';'
    63135835          DO  i = 1, dopts_num
     
    63225844
    63235845                IF ( j == 0 )  THEN
    6324                    CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
    6325                                            TRIM( dopts_label(i) ) // suffix,  &
    6326                                            nc_precision(6), id_var_dopts(i,j), &
    6327                                            TRIM( dopts_unit(i) ),              &
    6328                                            TRIM( dopts_label(i) ), 400, 401,   &
    6329                                            402 )
     5846                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),                      &
     5847                                           TRIM( dopts_label(i) ) // suffix, nc_precision(6),      &
     5848                                           id_var_dopts(i,j), TRIM( dopts_unit(i) ),               &
     5849                                           TRIM( dopts_label(i) ), 400, 401, 402 )
    63305850                ELSE
    6331                    CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
    6332                                            TRIM( dopts_label(i) ) // suffix,  &
    6333                                            nc_precision(6), id_var_dopts(i,j), &
    6334                                            TRIM( dopts_unit(i) ),              &
    6335                                            TRIM( dopts_label(i) ) // ' PG ' // &
    6336                                            suffix(2:3), 400, 401, 402 )
     5851                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),                      &
     5852                                           TRIM( dopts_label(i) ) // suffix, nc_precision(6),      &
     5853                                           id_var_dopts(i,j), TRIM( dopts_unit(i) ),               &
     5854                                           TRIM( dopts_label(i) ) // ' PG ' // suffix(2:3),        &
     5855                                           400, 401, 402 )
    63375856                ENDIF
    63385857
    6339                 var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
    6340                            suffix // ';'
     5858                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // suffix // ';'
    63415859
    63425860                IF ( number_of_particle_groups == 1 )  EXIT
     
    63475865
    63485866!
    6349 !--       Write the list of variables as global attribute (this is used by
    6350 !--       restart runs)
    6351           nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
    6352                                   var_list )
     5867!--       Write the list of variables as global attribute (this is used by restart runs)
     5868          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', var_list )
    63535869          CALL netcdf_handle_error( 'netcdf_define_header', 403 )
    63545870
     
    63645880!
    63655881!--       Get the list of variables and compare with the actual run.
    6366 !--       First var_list_old has to be reset, since GET_ATT does not assign
    6367 !--       trailing blanks.
     5882!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    63685883          var_list_old = ' '
    6369           nc_stat = NF90_GET_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
    6370                                   var_list_old )
     5884          nc_stat = NF90_GET_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', var_list_old )
    63715885          CALL netcdf_handle_error( 'netcdf_define_header', 405 )
    63725886
     
    63835897                ENDIF
    63845898
    6385                 var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
    6386                            suffix // ';'
     5899                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // suffix // ';'
    63875900
    63885901                IF ( number_of_particle_groups == 1 )  EXIT
     
    63935906
    63945907          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    6395              message_string = 'netCDF file for particle time series ' //       &
    6396                               'from previous run found,' //                    &
    6397                               '&but this file cannot be extended due to' //    &
    6398                               ' variable mismatch.' //                         &
    6399                               '&New file is created instead.'
     5908             message_string = 'netCDF file for particle time series ' //                           &
     5909                              'from previous run found,' //                                        &
     5910                              '&but this file cannot be extended due to' //                        &
     5911                              ' variable mismatch.' // '&New file is created instead.'
    64005912             CALL message( 'define_netcdf_header', 'PA0267', 0, 1, 0, 6, 0 )
    64015913             extend = .FALSE.
     
    64045916
    64055917!
    6406 !--       Get the id of the time coordinate (unlimited coordinate) and its
    6407 !--       last index on the file. The next time level is dots..count+1.
    6408 !--       The current time must be larger than the last output time
    6409 !--       on the file.
     5918!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     5919!--       The next time level is dots..count+1.
     5920!--       The current time must be larger than the last output time on the file.
    64105921          nc_stat = NF90_INQ_VARID( id_set_pts, 'time', id_var_time_pts )
    64115922          CALL netcdf_handle_error( 'netcdf_define_header', 406 )
    64125923
    6413           nc_stat = NF90_INQUIRE_VARIABLE( id_set_pts, id_var_time_pts, &
    6414                                            dimids = id_dim_time_old )
     5924          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pts, id_var_time_pts, dimids = id_dim_time_old )
    64155925          CALL netcdf_handle_error( 'netcdf_define_header', 407 )
    64165926          id_dim_time_pts = id_dim_time_old(1)
    64175927
    6418           nc_stat = NF90_INQUIRE_DIMENSION( id_set_pts, id_dim_time_pts, &
    6419                                             len = dopts_time_count )
     5928          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pts, id_dim_time_pts, LEN = dopts_time_count )
    64205929          CALL netcdf_handle_error( 'netcdf_define_header', 408 )
    64215930
    6422           nc_stat = NF90_GET_VAR( id_set_pts, id_var_time_pts,    &
    6423                                   last_time_coordinate,           &
    6424                                   start = (/ dopts_time_count /), &
     5931          nc_stat = NF90_GET_VAR( id_set_pts, id_var_time_pts,                                     &
     5932                                  last_time_coordinate,                                            &
     5933                                  start = (/ dopts_time_count /),                                  &
    64255934                                  count = (/ 1 /) )
    64265935          CALL netcdf_handle_error( 'netcdf_define_header', 409 )
    64275936
    64285937          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    6429              message_string = 'netCDF file for particle time series ' //       &
    6430                               'from previous run found,' //                    &
    6431                               '&but this file cannot be extended becaus' //    &
    6432                               'e the current output time' //                   &
    6433                               '&is less or equal than the last output t' //    &
    6434                               'ime on this file.' //                           &
     5938             message_string = 'netCDF file for particle time series ' //                           &
     5939                              'from previous run found,' //                                        &
     5940                              '&but this file cannot be extended because' //                       &
     5941                              ' the current output time' //                                        &
     5942                              '&is less or equal than the last output ' // 'time on this file.' // &
    64355943                              '&New file is created instead.'
    64365944             CALL message( 'define_netcdf_header', 'PA0268', 0, 1, 0, 6, 0 )
     
    64565964                netcdf_var_name = TRIM( dopts_label(i) ) // suffix
    64575965
    6458                 nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, &
    6459                                           id_var_dopts(i,j) )
     5966                nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, id_var_dopts(i,j) )
    64605967                CALL netcdf_handle_error( 'netcdf_define_header', 410 )
    64615968
     
    64675974
    64685975!
    6469 !--       Update the title attribute on file
    6470 !--       In order to avoid 'data mode' errors if updated attributes are larger
    6471 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    6472 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    6473 !--       performance loss due to data copying; an alternative strategy would be
    6474 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     5976!--       Update the title attribute on file.
     5977!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     5978!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     5979!--       calls. This implies a possible performance loss due to data copying; an alternative
     5980!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    64755981          nc_stat = NF90_REDEF( id_set_pts )
    64765982          CALL netcdf_handle_error( 'netcdf_define_header', 443 )
    6477           nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title',            &
    6478                                   TRIM( run_description_header ) )
     5983          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    64795984          CALL netcdf_handle_error( 'netcdf_define_header', 411 )
    64805985          nc_stat = NF90_ENDDEF( id_set_pts )
    64815986          CALL netcdf_handle_error( 'netcdf_define_header', 444 )
    6482           message_string = 'netCDF file for particle time series ' //          &
    6483                            'from previous run found.' //                       &
     5987          message_string = 'netCDF file for particle time series ' // 'from previous run found.' //&
    64845988                           '&This file will be extended.'
    64855989          CALL message( 'netcdf_define_header', 'PA0269', 0, 0, 0, 6, 0 )
     
    64905994!
    64915995!--       Define some global attributes of the dataset
    6492           nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
    6493                                   TRIM( run_description_header ) )
     5996          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    64945997          CALL netcdf_handle_error( 'netcdf_define_header', 249 )
    64955998
    64965999!
    6497 !--       Define time and location coordinates for flight space-time series
    6498 !--       (unlimited dimension)
     6000!--       Define time and location coordinates for flight space-time series (unlimited dimension).
    64996001!--       Error number must still be set appropriately.
    6500           CALL netcdf_create_dim( id_set_fl, 'time', NF90_UNLIMITED,           &
    6501                                   id_dim_time_fl, 250 )
    6502           CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /), 'time',     &
    6503                                   NF90_DOUBLE, id_var_time_fl, 'seconds', 'time',  &
    6504                                   251, 252, 000 )
     6002          CALL netcdf_create_dim( id_set_fl, 'time', NF90_UNLIMITED, id_dim_time_fl, 250 )
     6003          CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /), 'time', NF90_DOUBLE,            &
     6004                                  id_var_time_fl, 'seconds', 'time', 251, 252, 000 )
    65056005          CALL netcdf_create_att( id_set_fl, id_var_time_fl, 'standard_name', 'time', 000)
    65066006          CALL netcdf_create_att( id_set_fl, id_var_time_fl, 'axis', 'T', 000)
    65076007
    65086008          DO l = 1, num_leg
    6509              CALL netcdf_create_dim( id_set_fl, dofl_dim_label_x(l),           &
    6510                                      NF90_UNLIMITED, id_dim_x_fl(l), 250 )
    6511              CALL netcdf_create_dim( id_set_fl, dofl_dim_label_y(l),           &
    6512                                      NF90_UNLIMITED, id_dim_y_fl(l), 250 )
    6513              CALL netcdf_create_dim( id_set_fl, dofl_dim_label_z(l),           &
    6514                                      NF90_UNLIMITED, id_dim_z_fl(l), 250 )
    6515 
    6516              CALL netcdf_create_var( id_set_fl, (/ id_dim_x_fl(l) /),          &
    6517                                      dofl_dim_label_x(l), NF90_DOUBLE,         &
    6518                                      id_var_x_fl(l), 'm', '', 251, 252, 000 )
    6519              CALL netcdf_create_var( id_set_fl, (/ id_dim_y_fl(l) /),          &
    6520                                      dofl_dim_label_y(l), NF90_DOUBLE,         &
    6521                                      id_var_y_fl(l), 'm', '', 251, 252, 000 )
    6522              CALL netcdf_create_var( id_set_fl, (/ id_dim_z_fl(l) /),          &
    6523                                      dofl_dim_label_z(l), NF90_DOUBLE,         &
    6524                                      id_var_z_fl(l), 'm', '', 251, 252, 000 )
     6009             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_x(l), NF90_UNLIMITED,               &
     6010                                     id_dim_x_fl(l), 250 )
     6011             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_y(l), NF90_UNLIMITED,               &
     6012                                     id_dim_y_fl(l), 250 )
     6013             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_z(l), NF90_UNLIMITED,               &
     6014                                     id_dim_z_fl(l), 250 )
     6015
     6016             CALL netcdf_create_var( id_set_fl, (/ id_dim_x_fl(l) /), dofl_dim_label_x(l),         &
     6017                                     NF90_DOUBLE, id_var_x_fl(l), 'm', '', 251, 252, 000 )
     6018             CALL netcdf_create_var( id_set_fl, (/ id_dim_y_fl(l) /), dofl_dim_label_y(l),         &
     6019                                     NF90_DOUBLE, id_var_y_fl(l), 'm', '', 251, 252, 000 )
     6020             CALL netcdf_create_var( id_set_fl, (/ id_dim_z_fl(l) /), dofl_dim_label_z(l),         &
     6021                                     NF90_DOUBLE, id_var_z_fl(l), 'm', '', 251, 252, 000 )
    65256022          ENDDO
    65266023!
     
    65316028             DO i = 1, num_var_fl
    65326029
    6533                 CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /),       &
    6534                                         dofl_label(k), nc_precision(9),        &
    6535                                         id_var_dofl(k),                        &
    6536                                         TRIM( dofl_unit(k) ),                  &
     6030                CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /), dofl_label(k),            &
     6031                                        nc_precision(9), id_var_dofl(k), TRIM( dofl_unit(k) ),     &
    65376032                                        TRIM( dofl_label(k) ), 253, 254, 255 )
    65386033
     
    65446039
    65456040!
    6546 !--       Write the list of variables as global attribute (this is used by
    6547 !--       restart runs)
     6041!--       Write the list of variables as global attribute (this is used by restart runs).
    65486042          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST', var_list )
    65496043          CALL netcdf_handle_error( 'netcdf_define_header', 258 )
     
    65596053!
    65606054!--       Get the list of variables and compare with the actual run.
    6561 !--       First var_list_old has to be reset, since GET_ATT does not assign
    6562 !--       trailing blanks.
     6055!--       First var_list_old has to be reset, since GET_ATT does not assign trailing blanks.
    65636056          var_list_old = ' '
    6564           nc_stat = NF90_GET_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST',          &
    6565                                   var_list_old )
     6057          nc_stat = NF90_GET_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST', var_list_old )
    65666058          CALL netcdf_handle_error( 'netcdf_define_header', 260 )
    65676059
     
    65756067
    65766068          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
    6577              message_string = 'netCDF file for flight time series ' //         &
    6578                               'from previous run found,' //                    &
    6579                               '&but this file cannot be extended due to' //    &
    6580                               ' variable mismatch.' //                         &
    6581                               '&New file is created instead.'
     6069             message_string = 'netCDF file for flight time series ' //                             &
     6070                              'from previous run found,' //                                        &
     6071                              '&but this file cannot be extended due to' //                        &
     6072                              ' variable mismatch.' // '&New file is created instead.'
    65826073             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
    65836074             extend = .FALSE.
     
    65866077
    65876078!
    6588 !--       Get the id of the time coordinate (unlimited coordinate) and its
    6589 !--       last index on the file. The next time level is dofl_time_count+1.
    6590 !--       The current time must be larger than the last output time
    6591 !--       on the file.
     6079!--       Get the id of the time coordinate (unlimited coordinate) and its last index on the file.
     6080!--       The next time level is dofl_time_count+1.
     6081!--       The current time must be larger than the last output time on the file.
    65926082          nc_stat = NF90_INQ_VARID( id_set_fl, 'time', id_var_time_fl )
    65936083          CALL netcdf_handle_error( 'netcdf_define_header', 261 )
    65946084
    6595           nc_stat = NF90_INQUIRE_VARIABLE( id_set_fl, id_var_time_fl,          &
    6596                                            dimids = id_dim_time_old )
     6085          nc_stat = NF90_INQUIRE_VARIABLE( id_set_fl, id_var_time_fl, dimids = id_dim_time_old )
    65976086          CALL netcdf_handle_error( 'netcdf_define_header', 262 )
    65986087          id_dim_time_fl = id_dim_time_old(1)
    65996088
    6600           nc_stat = NF90_INQUIRE_DIMENSION( id_set_fl, id_dim_time_fl,         &
    6601                                             len = dofl_time_count )
     6089          nc_stat = NF90_INQUIRE_DIMENSION( id_set_fl, id_dim_time_fl, LEN = dofl_time_count )
    66026090          CALL netcdf_handle_error( 'netcdf_define_header', 263 )
    66036091
    6604           nc_stat = NF90_GET_VAR( id_set_fl, id_var_time_fl,        &
    6605                                   last_time_coordinate,             &
    6606                                   start = (/ dofl_time_count /), &
     6092          nc_stat = NF90_GET_VAR( id_set_fl, id_var_time_fl,                                       &
     6093                                  last_time_coordinate,                                            &
     6094                                  start = (/ dofl_time_count /),                                   &
    66076095                                  count = (/ 1 /) )
    66086096          CALL netcdf_handle_error( 'netcdf_define_header', 264 )
    66096097
    66106098          IF ( last_time_coordinate(1) >= simulated_time )  THEN
    6611              message_string = 'netCDF file for flight-time series ' //         &
    6612                               'from previous run found,' //                    &
    6613                               '&but this file cannot be extended becaus' //    &
    6614                               'e the current output time' //                   &
    6615                               '&is less or equal than the last output t' //    &
    6616                               'ime on this file.' //                           &
     6099             message_string = 'netCDF file for flight-time series ' //                             &
     6100                              'from previous run found,' //                                        &
     6101                              '&but this file cannot be extended because' //                       &
     6102                              ' the current output time' //                                        &
     6103                              '&is less or equal than the last output ' // 'time on this file.' // &
    66176104                              '&New file is created instead.'
    66186105             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
     
    66246111!
    66256112!--       Dataset seems to be extendable.
    6626 !--       Now get the remaining dimension and variable ids
     6113!--       Now get the remaining dimension and variable ids.
    66276114          DO l = 1, num_leg
    6628              nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_x(l),         &
    6629                                        id_var_x_fl(l) )
     6115             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_x(l), id_var_x_fl(l) )
    66306116             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
    6631              nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_y(l),         &
    6632                                        id_var_y_fl(l) )
     6117             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_y(l), id_var_y_fl(l) )
    66336118             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
    6634              nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_z(l),         &
    6635                                        id_var_z_fl(l) )
     6119             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_z(l), id_var_z_fl(l) )
    66366120             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
    66376121
     
    66416125          DO  i = 1, num_leg * num_var_fl
    66426126
    6643             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_label(i), &
    6644                                        id_var_dofl(i) )
     6127            nc_stat = NF90_INQ_VARID( id_set_fl, dofl_label(i), id_var_dofl(i) )
    66456128            CALL netcdf_handle_error( 'netcdf_define_header', 265 )
    66466129
     
    66486131
    66496132!
    6650 !--       Update the title attribute on file
    6651 !--       In order to avoid 'data mode' errors if updated attributes are larger
    6652 !--       than their original size, NF90_PUT_ATT is called in 'define mode'
    6653 !--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
    6654 !--       performance loss due to data copying; an alternative strategy would be
    6655 !--       to ensure equal attribute size in a job chain. Maybe revise later.
     6133!--       Update the title attribute on file.
     6134!--       In order to avoid 'data mode' errors if updated attributes are larger than their original
     6135!--       size, NF90_PUT_ATT is called in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF
     6136!--       calls. This implies a possible performance loss due to data copying; an alternative
     6137!--       strategy would be to ensure equal attribute size in a job chain. Maybe revise later.
    66566138          nc_stat = NF90_REDEF( id_set_fl )
    66576139          CALL netcdf_handle_error( 'netcdf_define_header', 439 )
    6658           nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
    6659                                   TRIM( run_description_header ) )
     6140          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title', TRIM( run_description_header ) )
    66606141          CALL netcdf_handle_error( 'netcdf_define_header', 267 )
    66616142          nc_stat = NF90_ENDDEF( id_set_fl )
    66626143          CALL netcdf_handle_error( 'netcdf_define_header', 440 )
    6663           message_string = 'netCDF file for flight-time series ' //            &
    6664                            'from previous run found.' //                       &
     6144          message_string = 'netCDF file for flight-time series ' // 'from previous run found.' //  &
    66656145                           '&This file will be extended.'
    66666146          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
     
    66786158
    66796159
    6680 !------------------------------------------------------------------------------!
     6160!--------------------------------------------------------------------------------------------------!
    66816161! Description:
    66826162! ------------
    6683 !> Creates a netCDF file and give back the id. The parallel flag has to be TRUE
    6684 !> for parallel netCDF output support.
    6685 !------------------------------------------------------------------------------!
    6686 
     6163!> Creates a netCDF file and give back the id. The parallel flag has to be TRUE for parallel netCDF
     6164!> output support.
     6165!--------------------------------------------------------------------------------------------------!
    66876166 SUBROUTINE netcdf_create_file( filename , id, parallel, errno )
    66886167#if defined( __netcdf )
     
    66936172
    66946173    CHARACTER (LEN=*), INTENT(IN) :: filename
     6174
    66956175    INTEGER, INTENT(IN)           :: errno
    66966176    INTEGER, INTENT(OUT)          :: id
    66976177    INTEGER                       :: idum  !< dummy variable used to avoid compiler warnings about unused variables
     6178
    66986179    LOGICAL, INTENT(IN)           :: parallel
    66996180
     
    67126193!
    67136194!--    64bit-offset format
    6714        nc_stat = NF90_CREATE( filename,                                        &
    6715                               IOR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ), id )
     6195       nc_stat = NF90_CREATE( filename, IOR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ), id )
    67166196
    67176197#if defined( __netcdf4 )
    6718     ELSEIF ( netcdf_data_format == 3  .OR.                                     &
    6719              ( .NOT. parallel  .AND.  netcdf_data_format == 5 ) )  THEN
     6198    ELSEIF ( netcdf_data_format == 3  .OR.  ( .NOT. parallel  .AND.  netcdf_data_format == 5 ) )   &
     6199    THEN
    67206200!
    67216201!--    netCDF4/HDF5 format
    67226202       nc_stat = NF90_CREATE( filename, IOR( NF90_NOCLOBBER, NF90_NETCDF4 ), id )
    67236203
    6724     ELSEIF ( netcdf_data_format == 4  .OR.                                     &
    6725              ( .NOT. parallel  .AND.  netcdf_data_format == 6 ) )  THEN
     6204    ELSEIF ( netcdf_data_format == 4  .OR.  ( .NOT. parallel  .AND.  netcdf_data_format == 6 ) )   &
     6205    THEN
    67266206!
    67276207!--    netCDF4/HDF5 format with classic model flag
    6728        nc_stat = NF90_CREATE( filename,                                        &
    6729                               IOR( NF90_NOCLOBBER,                             &
    6730                               IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), id )
     6208       nc_stat = NF90_CREATE( filename,                                                            &
     6209                              IOR( NF90_NOCLOBBER, IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), id )
    67316210
    67326211#if defined( __netcdf4_parallel )
     
    67346213!
    67356214!--    netCDF4/HDF5 format, parallel
    6736        nc_stat = NF90_CREATE( filename,                                        &
    6737                               IOR( NF90_NOCLOBBER,                             &
    6738                               IOR( NF90_NETCDF4, NF90_MPIIO ) ),               &
     6215       nc_stat = NF90_CREATE( filename, IOR( NF90_NOCLOBBER, IOR( NF90_NETCDF4, NF90_MPIIO ) ),    &
    67396216                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
    67406217
     
    67426219!
    67436220!--    netCDF4/HDF5 format with classic model flag, parallel
    6744        nc_stat = NF90_CREATE( filename,                                        &
    6745                               IOR( NF90_NOCLOBBER,                             &
    6746                               IOR( NF90_MPIIO,                                 &
    6747                               IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),        &
     6221       nc_stat = NF90_CREATE( filename,                                                            &
     6222                              IOR( NF90_NOCLOBBER,                                                 &
     6223                                   IOR( NF90_MPIIO, IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),      &
    67486224                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
    67496225
     
    67566232 END SUBROUTINE netcdf_create_file
    67576233
    6758 !------------------------------------------------------------------------------!
     6234!--------------------------------------------------------------------------------------------------!
    67596235! Description:
    67606236! ------------
    67616237!> Opens an existing netCDF file for writing and gives back the id.
    67626238!> The parallel flag has to be TRUE for parallel netCDF output support.
    6763 !------------------------------------------------------------------------------!
     6239!--------------------------------------------------------------------------------------------------!
    67646240 SUBROUTINE netcdf_open_write_file( filename, id, parallel, errno )
    67656241#if defined( __netcdf )
     
    67706246
    67716247    CHARACTER (LEN=*), INTENT(IN) :: filename
     6248
    67726249    INTEGER, INTENT(IN)           :: errno
    67736250    INTEGER, INTENT(OUT)          :: id
     
    67806257#if defined( __netcdf4_parallel )
    67816258    ELSEIF ( netcdf_data_format > 4  .AND.  parallel )  THEN
    6782        nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id, &
    6783                             COMM = comm2d, INFO = MPI_INFO_NULL )
     6259       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id, COMM = comm2d,            &
     6260                            INFO = MPI_INFO_NULL )
    67846261#endif
    67856262#endif
     
    67916268
    67926269
    6793 !------------------------------------------------------------------------------!
     6270!--------------------------------------------------------------------------------------------------!
    67946271! Description:
    67956272! ------------
    67966273!> Prints out a text message corresponding to the current status.
    6797 !------------------------------------------------------------------------------!
    6798 
     6274!--------------------------------------------------------------------------------------------------!
    67996275 SUBROUTINE netcdf_handle_error( routine_name, errno )
    68006276#if defined( __netcdf )
    68016277
    68026278
    6803     USE control_parameters,                                                    &
     6279    USE control_parameters,                                                                        &
    68046280        ONLY:  message_string
    68056281
     
    68116287    INTEGER(iwp) ::  errno
    68126288
     6289
    68136290    IF ( nc_stat /= NF90_NOERR )  THEN
    68146291
     
    68256302
    68266303
    6827 !------------------------------------------------------------------------------!
     6304!--------------------------------------------------------------------------------------------------!
    68286305! Description:
    68296306! ------------
    68306307!> Create a dimension in NetCDF file
    6831 !------------------------------------------------------------------------------!
    6832 
    6833  SUBROUTINE netcdf_create_dim(ncid, dim_name, ncdim_type, ncdim_id, error_no)
     6308!--------------------------------------------------------------------------------------------------!
     6309
     6310 SUBROUTINE netcdf_create_dim( ncid, dim_name, ncdim_type, ncdim_id, error_no )
    68346311
    68356312#if defined( __netcdf )
     
    68566333
    68576334
    6858 !------------------------------------------------------------------------------!
     6335!--------------------------------------------------------------------------------------------------!
    68596336! Description:
    68606337! ------------
    68616338!> Create a one dimensional variable in specific units in NetCDF file
    6862 !------------------------------------------------------------------------------!
    6863 
    6864  SUBROUTINE netcdf_create_var( ncid, dim_id, var_name, var_type, var_id,       &
    6865                                unit_name, long_name, error_no1, error_no2,     &
    6866                                error_no3, fill )
     6339!--------------------------------------------------------------------------------------------------!
     6340
     6341 SUBROUTINE netcdf_create_var( ncid, dim_id, var_name, var_type, var_id, unit_name, long_name,     &
     6342                               error_no1, error_no2, error_no3, fill )
    68676343
    68686344#if defined( __netcdf )
     
    68726348    CHARACTER(LEN=*), INTENT(IN) ::  unit_name
    68736349    CHARACTER(LEN=*), INTENT(IN) ::  var_name
    6874 
    6875     LOGICAL, OPTIONAL ::  fill  !< indicates setting of _FillValue attribute
    68766350
    68776351    INTEGER, INTENT(IN)  ::  error_no1
     
    68846358    INTEGER, DIMENSION(:), INTENT(IN) ::  dim_id
    68856359
     6360    LOGICAL, OPTIONAL ::  fill  !< indicates setting of _FillValue attribute
     6361
     6362
    68866363!
    68876364!-- Define variable
     
    68916368#if defined( __netcdf4 )
    68926369!
    6893 !-- Check if variable should be deflate (including shuffling)
    6894 !-- and if it is possible (only NetCDF4 with HDF5 supports compression)
     6370!-- Check if variable should be deflate (including shuffling) and if it is possible (only NetCDF4
     6371!-- with HDF5 supports compression).
    68956372    IF ( netcdf_data_format > 2  .AND.  netcdf_deflate > 0 )  THEN
    68966373       nc_stat = NF90_DEF_VAR_DEFLATE( ncid, var_id, 1, 1, netcdf_deflate )
     
    69176394    IF ( PRESENT( fill ) )  THEN
    69186395       IF ( var_type == NF90_REAL4 )  THEN
    6919           nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
    6920                                   REAL( fill_value, KIND = 4 ) )
     6396          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue', REAL( fill_value, KIND = 4 ) )
    69216397          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
    69226398       ELSE
    6923           nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
    6924                                   REAL( fill_value, KIND = 8 ) )
     6399          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue', REAL( fill_value, KIND = 8 ) )
    69256400          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
    69266401       ENDIF
     
    69316406
    69326407
    6933 !------------------------------------------------------------------------------!
     6408!--------------------------------------------------------------------------------------------------!
    69346409! Description:
    69356410! ------------
    69366411!> Write attributes to file.
    6937 !------------------------------------------------------------------------------!
     6412!--------------------------------------------------------------------------------------------------!
    69386413 SUBROUTINE netcdf_create_att_string( ncid, varid, name, value, err )
    69396414
     
    69476422
    69486423    INTEGER, INTENT(IN), OPTIONAL ::  varid  !< variable id
     6424
    69496425
    69506426#if defined( __netcdf )
     
    69606436
    69616437
    6962 !------------------------------------------------------------------------------!
     6438!--------------------------------------------------------------------------------------------------!
    69636439! Description:
    69646440! ------------
    69656441!> Write a set of global attributes to file.
    6966 !------------------------------------------------------------------------------!
     6442!--------------------------------------------------------------------------------------------------!
    69676443 SUBROUTINE netcdf_create_global_atts( ncid, data_content, title, error_no )
    69686444
    6969     USE control_parameters,                                                    &
     6445    USE control_parameters,                                                                        &
    69706446        ONLY:  revision, run_date, run_time, run_zone, runnr, version
    69716447
    6972     USE netcdf_data_input_mod,                                                 &
     6448    USE netcdf_data_input_mod,                                                                     &
    69736449        ONLY:  input_file_atts
    69746450
    6975     USE palm_date_time_mod,                                                    &
     6451    USE palm_date_time_mod,                                                                        &
    69766452        ONLY:  date_time_str_len, get_date_time
    69776453
     
    69856461    INTEGER, INTENT(IN)  ::  error_no  !< error number
    69866462    INTEGER, INTENT(IN)  ::  ncid      !< file id
     6463
    69876464!
    69886465!-- Get date-time string for origin_time
     
    69946471    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'Conventions', 'CF-1.7' )
    69956472    CALL netcdf_handle_error( 'netcdf_create_global_atts 2', error_no )
    6996     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'creation_time', TRIM( run_date )//' '//TRIM( run_time )//' '//run_zone(1:3) )
     6473    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'creation_time', TRIM( run_date ) // ' ' //         &
     6474                            TRIM( run_time ) // ' ' // run_zone(1:3) )
    69976475    CALL netcdf_handle_error( 'netcdf_create_global_atts 3', error_no )
    6998     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'data_content', TRIM(data_content) )
     6476    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'data_content', TRIM( data_content ) )
    69996477    CALL netcdf_handle_error( 'netcdf_create_global_atts 4', error_no )
    70006478    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'version', runnr+1 )
     
    70216499    CALL netcdf_handle_error( 'netcdf_create_global_atts 14', error_no )
    70226500
    7023     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%author_char ), TRIM( input_file_atts%author ) )
     6501    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%author_char ),                &
     6502                            TRIM( input_file_atts%author ) )
    70246503    CALL netcdf_handle_error( 'netcdf_create_global_atts 15', error_no )
    7025     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%contact_person_char ), TRIM( input_file_atts%contact_person ) )
     6504    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%contact_person_char ),        &
     6505                            TRIM( input_file_atts%contact_person ) )
    70266506    CALL netcdf_handle_error( 'netcdf_create_global_atts 16', error_no )
    7027     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%institution_char ), TRIM( input_file_atts%institution ) )
     6507    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%institution_char ),           &
     6508                            TRIM( input_file_atts%institution ) )
    70286509    CALL netcdf_handle_error( 'netcdf_create_global_atts 17', error_no )
    7029     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%acronym_char ), TRIM( input_file_atts%acronym ) )
     6510    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%acronym_char ),               &
     6511                            TRIM( input_file_atts%acronym ) )
    70306512    CALL netcdf_handle_error( 'netcdf_create_global_atts 18', error_no )
    70316513
    7032     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%campaign_char ), TRIM( input_file_atts%campaign ) )
     6514    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%campaign_char ),              &
     6515                            TRIM( input_file_atts%campaign ) )
    70336516    CALL netcdf_handle_error( 'netcdf_create_global_atts 19', error_no )
    7034     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%location_char ), TRIM( input_file_atts%location ) )
     6517    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%location_char ),              &
     6518                            TRIM( input_file_atts%location ) )
    70356519    CALL netcdf_handle_error( 'netcdf_create_global_atts 20', error_no )
    7036     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%site_char ), TRIM( input_file_atts%site ) )
     6520    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%site_char ),                  &
     6521                            TRIM( input_file_atts%site ) )
    70376522    CALL netcdf_handle_error( 'netcdf_create_global_atts 21', error_no )
    70386523
    7039     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'source', TRIM( version )//' '//TRIM( revision ) )
     6524    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'source', TRIM( version ) // ' ' //                 &
     6525                            TRIM( revision ) )
    70406526    CALL netcdf_handle_error( 'netcdf_create_global_atts 22', error_no )
    7041     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%references_char ), TRIM( input_file_atts%references ) )
     6527    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%references_char ),            &
     6528                            TRIM( input_file_atts%references ) )
    70426529    CALL netcdf_handle_error( 'netcdf_create_global_atts 23', error_no )
    7043     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%keywords_char ), TRIM( input_file_atts%keywords ) )
     6530    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%keywords_char ),              &
     6531                            TRIM( input_file_atts%keywords ) )
    70446532    CALL netcdf_handle_error( 'netcdf_create_global_atts 24', error_no )
    7045     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%licence_char ), TRIM( input_file_atts%licence ) )
     6533    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%licence_char ),               &
     6534                            TRIM( input_file_atts%licence ) )
    70466535    CALL netcdf_handle_error( 'netcdf_create_global_atts 25', error_no )
    7047     nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%comment_char ), TRIM( input_file_atts%comment ) )
     6536    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%comment_char ),               &
     6537                            TRIM( input_file_atts%comment ) )
    70486538    CALL netcdf_handle_error( 'netcdf_create_global_atts 26', error_no )
    70496539
     
    70526542 END SUBROUTINE netcdf_create_global_atts
    70536543
    7054 !------------------------------------------------------------------------------!
     6544!--------------------------------------------------------------------------------------------------!
    70556545! Description:
    70566546! ------------
    70576547!> Create a variable holding the coordinate-reference-system information.
    7058 !------------------------------------------------------------------------------!
     6548!--------------------------------------------------------------------------------------------------!
    70596549 SUBROUTINE netcdf_create_crs( ncid, error_no )
    70606550
     
    70726562!
    70736563!-- Set attributes
    7074     nc_stat = NF90_PUT_ATT( ncid, var_id, 'epsg_code', &
    7075                             coord_ref_sys%epsg_code )
     6564    nc_stat = NF90_PUT_ATT( ncid, var_id, 'epsg_code', coord_ref_sys%epsg_code )
    70766565    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70776566
    7078     nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_easting', &
    7079                             coord_ref_sys%false_easting )
     6567    nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_easting', coord_ref_sys%false_easting )
    70806568    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70816569
    7082     nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_northing', &
    7083                             coord_ref_sys%false_northing )
     6570    nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_northing', coord_ref_sys%false_northing )
    70846571    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70856572
    7086     nc_stat = NF90_PUT_ATT( ncid, var_id, 'grid_mapping_name', &
    7087                             coord_ref_sys%grid_mapping_name )
     6573    nc_stat = NF90_PUT_ATT( ncid, var_id, 'grid_mapping_name', coord_ref_sys%grid_mapping_name )
    70886574    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70896575
    7090     nc_stat = NF90_PUT_ATT( ncid, var_id, 'inverse_flattening', &
    7091                             coord_ref_sys%inverse_flattening )
     6576    nc_stat = NF90_PUT_ATT( ncid, var_id, 'inverse_flattening', coord_ref_sys%inverse_flattening )
    70926577    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70936578
    7094     nc_stat = NF90_PUT_ATT( ncid, var_id, 'latitude_of_projection_origin', &
     6579    nc_stat = NF90_PUT_ATT( ncid, var_id, 'latitude_of_projection_origin',                         &
    70956580                            coord_ref_sys%latitude_of_projection_origin )
    70966581    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    70976582
    7098     nc_stat = NF90_PUT_ATT( ncid, var_id, 'long_name', &
    7099                             coord_ref_sys%long_name )
     6583    nc_stat = NF90_PUT_ATT( ncid, var_id, 'long_name', coord_ref_sys%long_name )
    71006584    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71016585
    7102     nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_central_meridian', &
     6586    nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_central_meridian',                         &
    71036587                            coord_ref_sys%longitude_of_central_meridian )
    71046588    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71056589
    7106     nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_prime_meridian', &
     6590    nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_prime_meridian',                           &
    71076591                            coord_ref_sys%longitude_of_prime_meridian )
    71086592    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71096593
    7110     nc_stat = NF90_PUT_ATT( ncid, var_id, 'scale_factor_at_central_meridian', &
     6594    nc_stat = NF90_PUT_ATT( ncid, var_id, 'scale_factor_at_central_meridian',                      &
    71116595                            coord_ref_sys%scale_factor_at_central_meridian )
    71126596    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71136597
    7114     nc_stat = NF90_PUT_ATT( ncid, var_id, 'semi_major_axis', &
    7115                             coord_ref_sys%semi_major_axis )
     6598    nc_stat = NF90_PUT_ATT( ncid, var_id, 'semi_major_axis', coord_ref_sys%semi_major_axis )
    71166599    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71176600
    7118     nc_stat = NF90_PUT_ATT( ncid, var_id, 'units', &
    7119                             coord_ref_sys%units )
     6601    nc_stat = NF90_PUT_ATT( ncid, var_id, 'units', coord_ref_sys%units )
    71206602    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
    71216603
     
    71246606
    71256607
    7126 !------------------------------------------------------------------------------!
     6608!--------------------------------------------------------------------------------------------------!
    71276609! Description:
    71286610! ------------
    71296611!> Define UTM coordinates and longitude and latitude in file.
    7130 !------------------------------------------------------------------------------!
    7131  SUBROUTINE define_geo_coordinates( id_set, id_dim_x, id_dim_y, id_var_eutm, id_var_nutm, id_var_lat, id_var_lon )
     6612!--------------------------------------------------------------------------------------------------!
     6613 SUBROUTINE define_geo_coordinates( id_set, id_dim_x, id_dim_y, id_var_eutm, id_var_nutm,          &
     6614                                    id_var_lat, id_var_lon )
    71326615
    71336616    IMPLICIT NONE
     
    71436626    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_lon   !< variable id for longitude coordinates
    71446627    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_nutm  !< variable id for N_UTM coordinates
     6628
    71456629
    71466630!
     
    71556639!-- Define UTM coordinates
    71566640    IF ( rotation_angle == 0.0_wp )  THEN
    7157        CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting', 000, 000, 000 )
    7158        CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing', 000, 000, 000 )
    7159        CALL netcdf_create_var( id_set, (/ id_dim_x(1) /), 'Eu_UTM', NF90_DOUBLE, id_var_eutm(1), 'm', 'easting', 000, 000, 000 )
    7160        CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'Nu_UTM', NF90_DOUBLE, id_var_nutm(1), 'm', 'northing', 000, 000, 000 )
    7161        CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'Ev_UTM', NF90_DOUBLE, id_var_eutm(2), 'm', 'easting', 000, 000, 000 )
    7162        CALL netcdf_create_var( id_set, (/ id_dim_y(1) /), 'Nv_UTM', NF90_DOUBLE, id_var_nutm(2), 'm', 'northing', 000, 000, 000 )
     6641       CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'E_UTM', NF90_DOUBLE, id_var_eutm(0),    &
     6642                               'm', 'easting', 000, 000, 000 )
     6643       CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'N_UTM', NF90_DOUBLE, id_var_nutm(0),    &
     6644                               'm', 'northing', 000, 000, 000 )
     6645       CALL netcdf_create_var( id_set, (/ id_dim_x(1) /), 'Eu_UTM', NF90_DOUBLE, id_var_eutm(1),   &
     6646                               'm', 'easting', 000, 000, 000 )
     6647       CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'Nu_UTM', NF90_DOUBLE, id_var_nutm(1),   &
     6648                               'm', 'northing', 000, 000, 000 )
     6649       CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'Ev_UTM', NF90_DOUBLE, id_var_eutm(2),   &
     6650                               'm', 'easting', 000, 000, 000 )
     6651       CALL netcdf_create_var( id_set, (/ id_dim_y(1) /), 'Nv_UTM', NF90_DOUBLE, id_var_nutm(2),   &
     6652                               'm', 'northing', 000, 000, 000 )
    71636653    ELSE
    7164        CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), &
    7165                                'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting', 000, 000, 000 )
    7166        CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), &
    7167                                'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing', 000, 000, 000 )
    7168        CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), &
    7169                                'Eu_UTM', NF90_DOUBLE, id_var_eutm(1), 'm', 'easting', 000, 000, 000 )
    7170        CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), &
    7171                                'Nu_UTM', NF90_DOUBLE, id_var_nutm(1), 'm', 'northing', 000, 000, 000 )
    7172        CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), &
    7173                                'Ev_UTM', NF90_DOUBLE, id_var_eutm(2), 'm', 'easting', 000, 000, 000 )
    7174        CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), &
    7175                                'Nv_UTM', NF90_DOUBLE, id_var_nutm(2), 'm', 'northing', 000, 000, 000 )
     6654       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /),                             &
     6655                               'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting',               &
     6656                               000, 000, 000 )
     6657       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /),                             &
     6658                               'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing',              &
     6659                               000, 000, 000 )
     6660       CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /),                             &
     6661                               'Eu_UTM', NF90_DOUBLE, id_var_eutm(1), 'm', 'easting',              &
     6662                               000, 000, 000 )
     6663       CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /),                             &
     6664                               'Nu_UTM', NF90_DOUBLE, id_var_nutm(1), 'm', 'northing',             &
     6665                               000, 000, 000 )
     6666       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /),                             &
     6667                               'Ev_UTM', NF90_DOUBLE, id_var_eutm(2), 'm', 'easting',              &
     6668                               000, 000, 000 )
     6669       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /),                             &
     6670                               'Nv_UTM', NF90_DOUBLE, id_var_nutm(2), 'm', 'northing',             &
     6671                               000, 000, 000 )
    71766672    ENDIF
    71776673!
    71786674!-- Define geographic coordinates
    7179     CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lon', NF90_DOUBLE, id_var_lon(0), &
    7180                             'degrees_east', 'longitude', 000, 000, 000 )
    7181     CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lat', NF90_DOUBLE, id_var_lat(0), &
    7182                             'degrees_north', 'latitude', 000, 000, 000 )
    7183     CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'lonu', NF90_DOUBLE, id_var_lon(1), &
    7184                             'degrees_east', 'longitude', 000, 000, 000 )
    7185     CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'latu', NF90_DOUBLE, id_var_lat(1), &
    7186                             'degrees_north', 'latitude', 000, 000, 000 )
    7187     CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'lonv', NF90_DOUBLE, id_var_lon(2), &
    7188                             'degrees_east', 'longitude', 000, 000, 000 )
    7189     CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'latv', NF90_DOUBLE, id_var_lat(2), &
    7190                             'degrees_north', 'latitude', 000, 000, 000 )
     6675    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lon', NF90_DOUBLE,           &
     6676                            id_var_lon(0), 'degrees_east', 'longitude', 000, 000, 000 )
     6677    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lat', NF90_DOUBLE,           &
     6678                            id_var_lat(0), 'degrees_north', 'latitude', 000, 000, 000 )
     6679    CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'lonu', NF90_DOUBLE,           &
     6680                            id_var_lon(1), 'degrees_east', 'longitude', 000, 000, 000 )
     6681    CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'latu', NF90_DOUBLE,           &
     6682                            id_var_lat(1), 'degrees_north', 'latitude', 000, 000, 000 )
     6683    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'lonv', NF90_DOUBLE,           &
     6684                            id_var_lon(2), 'degrees_east', 'longitude', 000, 000, 000 )
     6685    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'latv', NF90_DOUBLE,           &
     6686                            id_var_lat(2), 'degrees_north', 'latitude', 000, 000, 000 )
    71916687
    71926688    DO  i = 0, 2
    7193        CALL netcdf_create_att( id_set, id_var_eutm(i), 'standard_name', 'projection_x_coordinate', 000)
    7194        CALL netcdf_create_att( id_set, id_var_nutm(i), 'standard_name', 'projection_y_coordinate', 000)
    7195 
    7196        CALL netcdf_create_att( id_set, id_var_lat(i), 'standard_name', 'latitude', 000)
    7197        CALL netcdf_create_att( id_set, id_var_lon(i), 'standard_name', 'longitude', 000)
     6689       CALL netcdf_create_att( id_set, id_var_eutm(i), 'standard_name', 'projection_x_coordinate', &
     6690                               000 )
     6691       CALL netcdf_create_att( id_set, id_var_nutm(i), 'standard_name', 'projection_y_coordinate', &
     6692                               000 )
     6693
     6694       CALL netcdf_create_att( id_set, id_var_lat(i), 'standard_name', 'latitude', 000 )
     6695       CALL netcdf_create_att( id_set, id_var_lon(i), 'standard_name', 'longitude', 000 )
    71986696    ENDDO
    71996697
Note: See TracChangeset for help on using the changeset viewer.