source: palm/trunk/SOURCE/netcdf_interface_mod.f90 @ 4182

Last change on this file since 4182 was 4182, checked in by scharf, 6 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 319.2 KB
Line 
1!> @file netcdf_interface_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
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/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: netcdf_interface_mod.f90 4182 2019-08-22 15:20:23Z scharf $
27! Corrected "Former revisions" section
28!
29! 4127 2019-07-30 14:47:10Z suehring
30! -Introduce new vertical dimension for plant-canopy output.
31! -Temporarlily disable masked output for soil (merge from branch resler)
32!
33! 4069 2019-07-01 14:05:51Z Giersch
34! Masked output running index mid has been introduced as a local variable to
35! avoid runtime error (Loop variable has been modified) in time_integration
36!
37! 4046 2019-06-21 17:32:04Z knoop
38! removal of special treatment for usm_define_netcdf_grid call
39!
40! 4039 2019-06-18 10:32:41Z suehring
41! Rename subroutines in module for diagnostic quantities
42!
43! 4029 2019-06-14 14:04:35Z raasch
44! netcdf variable NF90_NOFILL is used as argument instead of "1" in calls to NF90_DEF_VAR_FILL
45!
46! 3995 2019-05-22 18:59:54Z suehring
47! output of turbulence intensity added
48!
49! 3994 2019-05-22 18:08:09Z suehring
50! remove origin time from time unit, compose origin_time_string within
51! subroutine netcdf_create_global_atts
52!
53! 3954 2019-05-06 12:49:42Z gronemeier
54! bugfix: corrected format for date_time_string
55!
56! 3953 2019-05-06 12:11:55Z gronemeier
57! bugfix: set origin_time and starting point of time coordinate according to
58!         day_of_year_init and time_utc_init
59!
60! 3942 2019-04-30 13:08:30Z kanani
61! Add specifier to netcdf_handle_error to simplify identification of attribute
62! causing the error
63!
64! 3766 2019-02-26 16:23:41Z raasch
65! bugfix in im_define_netcdf_grid argument list
66!
67! 3745 2019-02-15 18:57:56Z suehring
68! Add indoor model
69!
70! 3744 2019-02-15 18:38:58Z suehring
71! Bugfix: - initialize return values to ensure they are set before returning
72!           (routine define_geo_coordinates)
73!         - change order of dimensions for some variables
74!
75! 3727 2019-02-08 14:52:10Z gronemeier
76! make several routines publicly available
77!
78! 3701 2019-01-26 18:57:21Z knoop
79! Statement added to prevent compiler warning about unused variable
80!
81! 3655 2019-01-07 16:51:22Z knoop
82! Move the control parameter "salsa" from salsa_mod to control_parameters
83! (M. Kurppa)
84!
85! Revision 1.1  2005/05/18 15:37:16  raasch
86! Initial revision
87!
88!
89! Description:
90! ------------
91!> In case of extend = .FALSE.:
92!> Define all necessary dimensions, axes and variables for the different
93!> netCDF datasets. This subroutine is called from check_open after a new
94!> dataset is created. It leaves the open netCDF files ready to write.
95!>
96!> In case of extend = .TRUE.:
97!> Find out if dimensions and variables of an existing file match the values
98!> of the actual run. If so, get all necessary information (ids, etc.) from
99!> this file.
100!>
101!> Parameter av can assume values 0 (non-averaged data) and 1 (time averaged
102!> data)
103!>
104!> @todo calculation of output time levels for parallel NetCDF still does not
105!>       cover every exception (change of dt_do, end_time in restart)
106!> @todo timeseries and profile output still needs to be rewritten to allow
107!>       modularization
108!> @todo output 2d UTM coordinates without global arrays
109!> @todo output longitude/latitude also with non-parallel output (3d and xy)
110!------------------------------------------------------------------------------!
111 MODULE netcdf_interface
112
113    USE control_parameters,                                                    &
114        ONLY:  biometeorology, fl_max,                                         &
115               max_masks, multi_agent_system_end,                              &
116               multi_agent_system_start, var_fl_max, varnamelength
117    USE kinds
118#if defined( __netcdf )
119    USE NETCDF
120#endif
121    USE mas_global_attributes,                                                 &
122        ONLY:  dim_size_agtnum
123
124    USE netcdf_data_input_mod,                                                 &
125        ONLY: coord_ref_sys, init_model
126
127    PRIVATE
128
129    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_names =                      &
130          (/ 'ag_id           ', 'ag_x            ', 'ag_y            ',       &
131             'ag_wind         ', 'ag_temp         ', 'ag_group        ',       &
132             'PM10            ', 'PM25            ', 'ag_iPT          ',       &
133             'ag_uv           ', 'not_used        ', 'not_used        ',       &
134             'not_used        ' /)
135
136    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_units = &
137          (/ 'dim_less        ', 'meters          ', 'meters          ',       &
138             'm/s             ', 'K               ', 'dim_less        ',       &
139             'tbd             ', 'tbd             ', 'tbd             ',       &
140             'tbd             ', 'not_used        ', 'not_used        ',       &
141             'not_used        ' /)
142
143    INTEGER(iwp), PARAMETER ::  dopr_norm_num = 7, dopts_num = 29, dots_max = 100
144
145    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_names =          &
146         (/ 'wtheta0', 'ws2    ', 'tsw2   ', 'ws3    ', 'ws2tsw ', 'wstsw2 ',  &
147            'z_i    ' /)
148
149    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames =      &
150         (/ 'wtheta0', 'w*2    ', 't*w2   ', 'w*3    ', 'w*2t*w ', 'w*t*w2 ',  &
151            'z_i    ' /)
152
153    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_label =                   &
154          (/ 'tnpt   ', 'x_     ', 'y_     ', 'z_     ', 'z_abs  ', 'u      ', &
155             'v      ', 'w      ', 'u"     ', 'v"     ', 'w"     ', 'npt_up ', &
156             'w_up   ', 'w_down ', 'radius ', 'r_min  ', 'r_max  ', 'npt_max', &
157             'npt_min', 'x*2    ', 'y*2    ', 'z*2    ', 'u*2    ', 'v*2    ', &
158             'w*2    ', 'u"2    ', 'v"2    ', 'w"2    ', 'npt*2  ' /)
159
160    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_unit =                    &
161          (/ 'number ', 'm      ', 'm      ', 'm      ', 'm      ', 'm/s    ', &
162             'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'number ', &
163             'm/s    ', 'm/s    ', 'm      ', 'm      ', 'm      ', 'number ', &
164             'number ', 'm2     ', 'm2     ', 'm2     ', 'm2/s2  ', 'm2/s2  ', &
165             'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'number2' /)
166
167    INTEGER(iwp) ::  dots_num  = 25  !< number of timeseries defined by default
168    INTEGER(iwp) ::  dots_soil = 26  !< starting index for soil-timeseries
169    INTEGER(iwp) ::  dots_rad  = 32  !< starting index for radiation-timeseries
170
171    CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label =                    &
172          (/ 'E            ', 'E*           ', 'dt           ',                &
173             'us*          ', 'th*          ', 'umax         ',                &
174             'vmax         ', 'wmax         ', 'div_new      ',                &
175             'div_old      ', 'zi_wtheta    ', 'zi_theta     ',                &
176             'w*           ', 'w"theta"0    ', 'w"theta"     ',                &
177             'wtheta       ', 'theta(0)     ', 'theta(z_mo)  ',                &
178             'w"u"0        ', 'w"v"0        ', 'w"q"0        ',                &
179             'ol           ', 'q*           ', 'w"s"         ',                &
180             's*           ', 'ghf          ', 'qsws_liq     ',                &
181             'qsws_soil    ', 'qsws_veg     ', 'r_a          ',                &
182             'r_s          ',                                                  &
183             'rad_net      ', 'rad_lw_in    ', 'rad_lw_out   ',                &
184             'rad_sw_in    ', 'rad_sw_out   ', 'rrtm_aldif   ',                &
185             'rrtm_aldir   ', 'rrtm_asdif   ', 'rrtm_asdir   ',                &
186             ( 'unknown      ', i9 = 1, dots_max-40 ) /)
187
188    CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_unit =                     &
189          (/ 'm2/s2        ', 'm2/s2        ', 's            ',                &
190             'm/s          ', 'K            ', 'm/s          ',                &
191             'm/s          ', 'm/s          ', 's-1          ',                &
192             's-1          ', 'm            ', 'm            ',                &
193             'm/s          ', 'K m/s        ', 'K m/s        ',                &
194             'K m/s        ', 'K            ', 'K            ',                &
195             'm2/s2        ', 'm2/s2        ', 'kg m/s       ',                &
196             'm            ', 'kg/kg        ', 'kg m/(kg s)  ',                &
197             'kg/kg        ', 'W/m2         ', 'W/m2         ',                &
198             'W/m2         ', 'W/m2         ', 's/m          ',                &
199             's/m          ',                                                  &
200             'W/m2         ', 'W/m2         ', 'W/m2         ',                &
201             'W/m2         ', 'W/m2         ', '             ',                &
202             '             ', '             ', '             ',                &
203             ( 'unknown      ', i9 = 1, dots_max-40 ) /)
204
205    CHARACTER (LEN=16) :: heatflux_output_unit     !< unit for heatflux output
206    CHARACTER (LEN=16) :: waterflux_output_unit    !< unit for waterflux output
207    CHARACTER (LEN=16) :: momentumflux_output_unit !< unit for momentumflux output
208
209    CHARACTER (LEN=9), DIMENSION(300) ::  dopr_unit = 'unknown'
210
211    CHARACTER (LEN=7), DIMENSION(0:1,500) ::  do2d_unit, do3d_unit
212
213!    CHARACTER (LEN=16), DIMENSION(25) ::  prt_var_names = &
214!          (/ 'pt_age          ', 'pt_dvrp_size    ', 'pt_origin_x     ', &
215!             'pt_origin_y     ', 'pt_origin_z     ', 'pt_radius       ', &
216!             'pt_speed_x      ', 'pt_speed_y      ', 'pt_speed_z      ', &
217!             'pt_weight_factor', 'pt_x            ', 'pt_y            ', &
218!             'pt_z            ', 'pt_color        ', 'pt_group        ', &
219!             'pt_tailpoints   ', 'pt_tail_id      ', 'pt_density_ratio', &
220!             'pt_exp_arg      ', 'pt_exp_term     ', 'not_used        ', &
221!             'not_used        ', 'not_used        ', 'not_used        ', &
222!             'not_used        ' /)
223
224!    CHARACTER (LEN=16), DIMENSION(25) ::  prt_var_units = &
225!          (/ 'seconds         ', 'meters          ', 'meters          ', &
226!             'meters          ', 'meters          ', 'meters          ', &
227!             'm/s             ', 'm/s             ', 'm/s             ', &
228!             'factor          ', 'meters          ', 'meters          ', &
229!             'meters          ', 'none            ', 'none            ', &
230!             'none            ', 'none            ', 'ratio           ', &
231!             'none            ', 'none            ', 'not_used        ', &
232!             'not_used        ', 'not_used        ', 'not_used        ', &
233!             'not_used        ' /)
234
235    CHARACTER(LEN=20), DIMENSION(11) ::  netcdf_precision = ' '
236    CHARACTER(LEN=40) ::  netcdf_data_format_string
237
238    INTEGER(iwp) ::  id_dim_agtnum, id_dim_time_agt,                           &
239                     id_dim_time_fl, id_dim_time_pr,                           &
240                     id_dim_time_pts, id_dim_time_sp, id_dim_time_ts,          &
241                     id_dim_x_sp, id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp,     &
242                     id_set_agt, id_set_fl, id_set_pr, id_set_prt, id_set_pts, &
243                     id_set_sp, id_set_ts, id_var_agtnum, id_var_time_agt,     &
244                     id_var_time_fl, id_var_rnoa_agt, id_var_time_pr,          &
245                     id_var_time_pts, id_var_time_sp, id_var_time_ts,          &
246                     id_var_x_sp, id_var_y_sp, id_var_zu_sp, id_var_zw_sp,     &
247                     nc_stat
248
249
250    INTEGER(iwp), DIMENSION(0:1) ::  id_dim_time_xy, id_dim_time_xz, &
251                    id_dim_time_yz, id_dim_time_3d, id_dim_x_xy, id_dim_xu_xy, &
252                    id_dim_x_xz, id_dim_xu_xz, id_dim_x_yz, id_dim_xu_yz, &
253                    id_dim_x_3d, id_dim_xu_3d, id_dim_y_xy, id_dim_yv_xy, &
254                    id_dim_y_xz, id_dim_yv_xz, id_dim_y_yz, id_dim_yv_yz, &
255                    id_dim_y_3d, id_dim_yv_3d, id_dim_zs_xy, id_dim_zs_xz, &
256                    id_dim_zs_yz, id_dim_zs_3d, id_dim_zpc_3d, &
257                    id_dim_zu_xy, id_dim_zu1_xy, &
258                    id_dim_zu_xz, id_dim_zu_yz, id_dim_zu_3d, id_dim_zw_xy, &
259                    id_dim_zw_xz, id_dim_zw_yz, id_dim_zw_3d, id_set_xy, &
260                    id_set_xz, id_set_yz, id_set_3d, id_var_ind_x_yz, &
261                    id_var_ind_y_xz, id_var_ind_z_xy, id_var_time_xy, &
262                    id_var_time_xz, id_var_time_yz, id_var_time_3d, id_var_x_xy, &
263                    id_var_xu_xy, id_var_x_xz, id_var_xu_xz, id_var_x_yz, &
264                    id_var_xu_yz, id_var_x_3d, id_var_xu_3d, id_var_y_xy, &
265                    id_var_yv_xy, id_var_y_xz, id_var_yv_xz, id_var_y_yz, &
266                    id_var_yv_yz, id_var_y_3d, id_var_yv_3d, id_var_zs_xy, &
267                    id_var_zs_xz, id_var_zs_yz, id_var_zs_3d, id_var_zpc_3d, &
268                    id_var_zusi_xy, id_var_zusi_3d, id_var_zu_xy, id_var_zu1_xy, id_var_zu_xz, &
269                    id_var_zu_yz, id_var_zu_3d, id_var_zwwi_xy, id_var_zwwi_3d, &
270                    id_var_zw_xy, id_var_zw_xz, id_var_zw_yz, id_var_zw_3d
271
272    INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_eutm_3d, id_var_nutm_3d, &
273                                         id_var_eutm_xy, id_var_nutm_xy, &
274                                         id_var_eutm_xz, id_var_nutm_xz, &
275                                         id_var_eutm_yz, id_var_nutm_yz
276
277    INTEGER(iwp), DIMENSION(0:2,0:1) ::  id_var_lat_3d, id_var_lon_3d, &
278                                         id_var_lat_xy, id_var_lon_xy, &
279                                         id_var_lat_xz, id_var_lon_xz, &
280                                         id_var_lat_yz, id_var_lon_yz
281
282    INTEGER ::  netcdf_data_format = 2  !< NetCDF3 64bit offset format
283    INTEGER ::  netcdf_deflate = 0      !< NetCDF compression, default: no
284                                        !< compression
285
286    INTEGER(iwp)                 ::  dofl_time_count
287    INTEGER(iwp), DIMENSION(10)  ::  id_var_dospx, id_var_dospy
288    INTEGER(iwp), DIMENSION(20)  ::  id_var_agt
289!    INTEGER(iwp), DIMENSION(20)  ::  id_var_prt
290    INTEGER(iwp), DIMENSION(11)  ::  nc_precision
291    INTEGER(iwp), DIMENSION(dopr_norm_num) ::  id_var_norm_dopr
292
293    INTEGER(iwp), DIMENSION(fl_max) ::  id_dim_x_fl, id_dim_y_fl, id_dim_z_fl
294    INTEGER(iwp), DIMENSION(fl_max) ::  id_var_x_fl, id_var_y_fl, id_var_z_fl
295
296    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_label
297    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_unit
298    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_x
299    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_y
300    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_z
301
302    INTEGER(iwp), DIMENSION(fl_max*var_fl_max) :: id_var_dofl
303
304    INTEGER(iwp), DIMENSION(dopts_num,0:10) ::  id_var_dopts
305    INTEGER(iwp), DIMENSION(0:1,500)        ::  id_var_do2d, id_var_do3d
306    INTEGER(iwp), DIMENSION(100,0:99)       ::  id_dim_z_pr, id_var_dopr, &
307                                                id_var_z_pr
308    INTEGER(iwp), DIMENSION(dots_max,0:99)  ::  id_var_dots
309
310!
311!-- Masked output
312    CHARACTER (LEN=7), DIMENSION(max_masks,0:1,100) ::  domask_unit
313
314    LOGICAL ::  output_for_t0 = .FALSE.
315
316    INTEGER(iwp), DIMENSION(1:max_masks,0:1) ::  id_dim_time_mask, id_dim_x_mask, &
317                   id_dim_xu_mask, id_dim_y_mask, id_dim_yv_mask, id_dim_zs_mask, &
318                   id_dim_zu_mask, id_dim_zw_mask, &
319                   id_set_mask, &
320                   id_var_time_mask, id_var_x_mask, id_var_xu_mask, &
321                   id_var_y_mask, id_var_yv_mask, id_var_zs_mask, &
322                   id_var_zu_mask, id_var_zw_mask, &
323                   id_var_zusi_mask, id_var_zwwi_mask
324
325    INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_eutm_mask, &
326                                                     id_var_nutm_mask
327
328    INTEGER(iwp), DIMENSION(0:2,1:max_masks,0:1) ::  id_var_lat_mask, &
329                                                     id_var_lon_mask
330
331    INTEGER(iwp), DIMENSION(1:max_masks,0:1,100) ::  id_var_domask
332
333    REAL(wp) ::  fill_value = -9999.0_wp    !< value for the _FillValue attribute
334
335
336    PUBLIC  dofl_dim_label_x, dofl_dim_label_y, dofl_dim_label_z, dofl_label,  &
337            dofl_time_count, dofl_unit, domask_unit, dopr_unit, dopts_num,     &
338            dots_label, dots_max, dots_num, dots_rad, dots_soil, dots_unit,    &
339            do2d_unit, do3d_unit, fill_value, id_set_agt, id_set_fl,           &
340            id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp,         &
341            id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d, id_var_agt, &
342            id_var_domask, id_var_dofl, id_var_dopr, id_var_dopts,             &
343            id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d, id_var_do3d, &
344            id_var_norm_dopr, id_var_time_agt, id_var_time_fl,                 &
345            id_var_time_mask, id_var_time_pr, id_var_rnoa_agt, id_var_time_pts,&
346            id_var_time_sp, id_var_time_ts,                                    &
347            id_var_time_xy, id_var_time_xz, id_var_time_yz, id_var_time_3d,    &
348            id_var_x_fl, id_var_y_fl, id_var_z_fl,  nc_stat,                   &
349            netcdf_data_format, netcdf_data_format_string, netcdf_deflate,     &
350            netcdf_precision, output_for_t0, heatflux_output_unit,             &
351            waterflux_output_unit, momentumflux_output_unit
352
353    SAVE
354
355    INTERFACE netcdf_create_dim
356       MODULE PROCEDURE netcdf_create_dim
357    END INTERFACE netcdf_create_dim
358
359    INTERFACE netcdf_create_file
360       MODULE PROCEDURE netcdf_create_file
361    END INTERFACE netcdf_create_file
362
363    INTERFACE netcdf_create_global_atts
364       MODULE PROCEDURE netcdf_create_global_atts
365    END INTERFACE netcdf_create_global_atts
366
367    INTERFACE netcdf_create_var
368       MODULE PROCEDURE netcdf_create_var
369    END INTERFACE netcdf_create_var
370
371    INTERFACE netcdf_create_att
372       MODULE PROCEDURE netcdf_create_att_string
373    END INTERFACE netcdf_create_att
374
375    INTERFACE netcdf_define_header
376       MODULE PROCEDURE netcdf_define_header
377    END INTERFACE netcdf_define_header
378
379    INTERFACE netcdf_handle_error
380       MODULE PROCEDURE netcdf_handle_error
381    END INTERFACE netcdf_handle_error
382
383    INTERFACE netcdf_open_write_file
384       MODULE PROCEDURE netcdf_open_write_file
385    END INTERFACE netcdf_open_write_file
386
387    PUBLIC netcdf_create_att, netcdf_create_dim, netcdf_create_file,           &
388           netcdf_create_global_atts, netcdf_create_var, netcdf_define_header, &
389           netcdf_handle_error, netcdf_open_write_file
390
391 CONTAINS
392
393 SUBROUTINE netcdf_define_header( callmode, extend, av )
394
395#if defined( __netcdf )
396
397    USE arrays_3d,                                                             &
398        ONLY:  zu, zw
399
400    USE biometeorology_mod,                                                    &
401        ONLY:  bio_define_netcdf_grid
402
403    USE chemistry_model_mod,                                                   &
404        ONLY:  chem_define_netcdf_grid
405
406    USE basic_constants_and_equations_mod,                                     &
407        ONLY:  pi
408
409    USE control_parameters,                                                    &
410        ONLY:  agent_time_unlimited, air_chemistry, averaging_interval,        &
411               averaging_interval_pr, data_output_pr, domask, dopr_n,          &
412               dopr_time_count, dopts_time_count, dots_time_count,             &
413               do2d, do2d_at_begin, do2d_xz_time_count, do3d, do3d_at_begin,   &
414               do2d_yz_time_count, dt_data_output_av, dt_do2d_xy, dt_do2d_xz,  &
415               dt_do2d_yz, dt_do3d, dt_write_agent_data, mask_size,            &
416               do2d_xy_time_count, do3d_time_count, domask_time_count,         &
417               end_time, indoor_model, land_surface,                           &
418               mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global,      &
419               mask_k_global, mask_surface,                                    &
420               message_string, ntdim_2d_xy, ntdim_2d_xz,                       &
421               ntdim_2d_yz, ntdim_3d, nz_do3d, ocean_mode, plant_canopy,       &
422               run_description_header, salsa, section, simulated_time,         &
423               simulated_time_at_begin, skip_time_data_output_av,              &
424               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
425               skip_time_do3d, topography, num_leg, num_var_fl,                &
426               urban_surface
427
428    USE diagnostic_output_quantities_mod,                                      &
429        ONLY:  doq_define_netcdf_grid
430
431    USE grid_variables,                                                        &
432        ONLY:  dx, dy, zu_s_inner, zw_w_inner
433
434    USE gust_mod,                                                              &
435        ONLY: gust_define_netcdf_grid, gust_module_enabled
436
437    USE indices,                                                               &
438        ONLY:  nx, nxl, nxr, ny, nys, nyn, nz ,nzb, nzt
439
440    USE kinds
441
442    USE indoor_model_mod,                                                      &
443        ONLY: im_define_netcdf_grid
444
445    USE land_surface_model_mod,                                                &
446        ONLY: lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
447
448    USE ocean_mod,                                                             &
449        ONLY:  ocean_define_netcdf_grid
450
451    USE pegrid
452
453    USE particle_attributes,                                                   &
454        ONLY:  number_of_particle_groups
455
456    USE plant_canopy_model_mod,                                                &
457        ONLY:  pch_index, pcm_define_netcdf_grid
458
459    USE profil_parameter,                                                      &
460        ONLY:  crmax, cross_profiles, dopr_index, profile_columns, profile_rows
461
462    USE radiation_model_mod,                                                   &
463        ONLY: radiation, radiation_define_netcdf_grid
464
465    USE salsa_mod,                                                             &
466        ONLY:  salsa_define_netcdf_grid
467
468    USE spectra_mod,                                                           &
469        ONLY:  averaging_interval_sp, comp_spectra_level, data_output_sp, dosp_time_count, spectra_direction
470
471    USE statistics,                                                            &
472        ONLY:  hom, statistic_regions
473
474    USE turbulence_closure_mod,                                                &
475        ONLY:  tcm_define_netcdf_grid
476
477    USE urban_surface_mod,                                                     &
478        ONLY:  usm_define_netcdf_grid
479
480    USE user,                                                                  &
481        ONLY:  user_module_enabled, user_define_netcdf_grid
482
483
484
485    IMPLICIT NONE
486
487    CHARACTER (LEN=3)              ::  suffix                !<
488    CHARACTER (LEN=2), INTENT (IN) ::  callmode              !<
489    CHARACTER (LEN=4)              ::  grid_x                !<
490    CHARACTER (LEN=4)              ::  grid_y                !<
491    CHARACTER (LEN=4)              ::  grid_z                !<
492    CHARACTER (LEN=6)              ::  mode                  !<
493    CHARACTER (LEN=10)             ::  precision             !<
494    CHARACTER (LEN=10)             ::  var                   !<
495    CHARACTER (LEN=20)             ::  netcdf_var_name       !<
496    CHARACTER (LEN=varnamelength)  ::  trimvar               !< TRIM of output-variable string
497    CHARACTER (LEN=80)             ::  time_average_text     !<
498    CHARACTER (LEN=4000)           ::  char_cross_profiles   !<
499    CHARACTER (LEN=4000)           ::  var_list              !<
500    CHARACTER (LEN=4000)           ::  var_list_old          !<
501
502    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_adj   !<
503    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_char  !<
504
505    INTEGER(iwp) ::  av                                      !<
506    INTEGER(iwp) ::  cross_profiles_count                    !<
507    INTEGER(iwp) ::  cross_profiles_maxi                     !<
508    INTEGER(iwp) ::  delim                                   !<
509    INTEGER(iwp) ::  delim_old                               !<
510    INTEGER(iwp) ::  file_id                                 !<
511    INTEGER(iwp) ::  i                                       !<
512    INTEGER(iwp) ::  id_last                                 !<
513    INTEGER(iwp) ::  id_x                                    !<
514    INTEGER(iwp) ::  id_y                                    !<
515    INTEGER(iwp) ::  id_z                                    !<
516    INTEGER(iwp) ::  j                                       !<
517    INTEGER(iwp) ::  k                                       !<
518    INTEGER(iwp) ::  kk                                      !<
519    INTEGER(iwp) ::  mid                                     !< masked output running index
520    INTEGER(iwp) ::  ns                                      !<
521    INTEGER(iwp) ::  ns_do                                   !< actual value of ns for soil model data
522    INTEGER(iwp) ::  ns_old                                  !<
523    INTEGER(iwp) ::  ntime_count                             !< number of time levels found in file
524    INTEGER(iwp) ::  nz_old                                  !<
525    INTEGER(iwp) ::  l                                       !<
526
527    INTEGER(iwp), SAVE ::  oldmode                           !<
528
529    INTEGER(iwp), DIMENSION(1) ::  id_dim_time_old           !<
530    INTEGER(iwp), DIMENSION(1) ::  id_dim_x_yz_old           !<
531    INTEGER(iwp), DIMENSION(1) ::  id_dim_y_xz_old           !<
532    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_sp_old          !<
533    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_xy_old          !<
534    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_3d_old          !<
535    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_mask_old        !<
536
537
538    INTEGER(iwp), DIMENSION(1:crmax) ::  cross_profiles_numb !<
539
540    LOGICAL ::  found                                        !<
541
542    LOGICAL, INTENT (INOUT) ::  extend                       !<
543
544    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !<
545
546    REAL(wp) ::  cos_ra                                      !< cosine of rotation_angle
547    REAL(wp) ::  eutm                                        !< easting (UTM)
548    REAL(wp) ::  nutm                                        !< northing (UTM)
549    REAL(wp) ::  shift_x                                     !< shift of x coordinate
550    REAL(wp) ::  shift_y                                     !< shift of y coordinate
551    REAL(wp) ::  sin_ra                                      !< sine of rotation_angle
552
553    REAL(wp), DIMENSION(1) ::  last_time_coordinate          !< last time value in file
554    REAL(wp), DIMENSION(8) ::  crs_list                      !< list of coord_ref_sys values
555
556    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  netcdf_data    !<
557    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  netcdf_data_2d !<
558    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lat            !< latitude
559    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lon            !< longitude
560
561
562!
563!-- Initializing actions
564    IF ( .NOT. init_netcdf )  THEN
565!
566!--    Check and set accuracy for netCDF output. First set default value
567       nc_precision = NF90_REAL4
568
569       i = 1
570       DO  WHILE ( netcdf_precision(i) /= ' ' )
571          j = INDEX( netcdf_precision(i), '_' )
572          IF ( j == 0 )  THEN
573             WRITE ( message_string, * ) 'netcdf_precision must contain a ', &
574                                         '"_"netcdf_precision(', i, ')="',   &
575                                         TRIM( netcdf_precision(i) ),'"'
576             CALL message( 'netcdf_define_header', 'PA0241', 2, 2, 0, 6, 0 )
577          ENDIF
578
579          var       = netcdf_precision(i)(1:j-1)
580          precision = netcdf_precision(i)(j+1:)
581
582          IF ( precision == 'NF90_REAL4' )  THEN
583             j = NF90_REAL4
584          ELSEIF ( precision == 'NF90_REAL8' )  THEN
585             j = NF90_REAL8
586          ELSE
587             WRITE ( message_string, * ) 'illegal netcdf precision: ',  &
588                                         'netcdf_precision(', i, ')="', &
589                                         TRIM( netcdf_precision(i) ),'"'
590             CALL message( 'netcdf_define_header', 'PA0242', 1, 2, 0, 6, 0 )
591          ENDIF
592
593          SELECT CASE ( var )
594             CASE ( 'xy' )
595                nc_precision(1) = j
596             CASE ( 'xz' )
597                nc_precision(2) = j
598             CASE ( 'yz' )
599                nc_precision(3) = j
600             CASE ( '2d' )
601                nc_precision(1:3) = j
602             CASE ( '3d' )
603                nc_precision(4) = j
604             CASE ( 'pr' )
605                nc_precision(5) = j
606             CASE ( 'ts' )
607                nc_precision(6) = j
608             CASE ( 'sp' )
609                nc_precision(7) = j
610             CASE ( 'prt' )
611                nc_precision(8) = j
612             CASE ( 'masks' )
613                nc_precision(11) = j
614             CASE ( 'fl' )
615                nc_precision(9) = j
616             CASE ( 'all' )
617                nc_precision    = j
618
619             CASE DEFAULT
620                WRITE ( message_string, * ) 'unknown variable in ' //          &
621                                  'initialization_parameters ',                &
622                                  'assignment: netcdf_precision(', i, ')="',   &
623                                            TRIM( netcdf_precision(i) ),'"'
624                CALL message( 'netcdf_define_header', 'PA0243', 1, 2, 0, 6, 0 )
625
626          END SELECT
627
628          i = i + 1
629          IF ( i > 50 )  EXIT
630       ENDDO
631
632!
633!--    Check for allowed parameter range
634       IF ( netcdf_deflate < 0  .OR.  netcdf_deflate > 9 )  THEN
635          WRITE ( message_string, '(A,I3,A)' ) 'netcdf_deflate out of ' //     &
636                                      'range & given value: ', netcdf_deflate, &
637                                      ', allowed range: 0-9'
638          CALL message( 'netcdf_define_header', 'PA0355', 2, 2, 0, 6, 0 )
639       ENDIF
640!
641!--    Data compression does not work with parallel NetCDF/HDF5
642       IF ( netcdf_deflate > 0  .AND.  netcdf_data_format /= 3 )  THEN
643          message_string = 'netcdf_deflate reset to 0'
644          CALL message( 'netcdf_define_header', 'PA0356', 0, 1, 0, 6, 0 )
645
646          netcdf_deflate = 0
647       ENDIF
648
649       init_netcdf = .TRUE.
650
651    ENDIF
652!
653!-- Convert coord_ref_sys into vector (used for lat/lon calculation)
654    crs_list = (/ coord_ref_sys%semi_major_axis,                  &
655                  coord_ref_sys%inverse_flattening,               &
656                  coord_ref_sys%longitude_of_prime_meridian,      &
657                  coord_ref_sys%longitude_of_central_meridian,    &
658                  coord_ref_sys%scale_factor_at_central_meridian, &
659                  coord_ref_sys%latitude_of_projection_origin,    &
660                  coord_ref_sys%false_easting,                    &
661                  coord_ref_sys%false_northing /)
662
663!
664!-- Determine the mode to be processed
665    IF ( extend )  THEN
666       mode = callmode // '_ext'
667    ELSE
668       mode = callmode // '_new'
669    ENDIF
670
671!
672!-- Select the mode to be processed. Possibilities are 3d, ma (mask), xy, xz,
673!-- yz, pr (profiles), ps (particle timeseries), fl (flight data), ts
674!-- (timeseries) or sp (spectra)
675    SELECT CASE ( mode )
676
677       CASE ( 'ma_new' )
678
679!
680!--       decompose actual parameter file_id (=formal parameter av) into
681!--       mid and av
682          file_id = av
683          IF ( file_id <= 200+max_masks )  THEN
684             mid = file_id - 200
685             av = 0
686          ELSE
687             mid = file_id - (200+max_masks)
688             av = 1
689          ENDIF
690
691!
692!--       Define some global attributes of the dataset
693          IF ( av == 0 )  THEN
694             CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked', TRIM( run_description_header ), 464 )
695             time_average_text = ' '
696          ELSE
697             CALL netcdf_create_global_atts( id_set_mask(mid,av), 'podsmasked', TRIM( run_description_header ), 464 )
698             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
699             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'time_avg',   &
700                                     TRIM( time_average_text ) )
701             CALL netcdf_handle_error( 'netcdf_define_header', 466 )
702          ENDIF
703
704!
705!--       Define time coordinate for volume data (unlimited dimension)
706          CALL netcdf_create_dim( id_set_mask(mid,av), 'time', NF90_UNLIMITED, &
707                                  id_dim_time_mask(mid,av), 467 )
708          CALL netcdf_create_var( id_set_mask(mid,av),                         &
709                                  (/ id_dim_time_mask(mid,av) /), 'time',      &
710                                  NF90_DOUBLE, id_var_time_mask(mid,av),       &
711                                 'seconds', 'time', 468, 469, 000 )
712          CALL netcdf_create_att( id_set_mask(mid,av), id_var_time_mask(mid,av), 'standard_name', 'time', 000)
713          CALL netcdf_create_att( id_set_mask(mid,av), id_var_time_mask(mid,av), 'axis', 'T', 000)
714
715!
716!--       Define spatial dimensions and coordinates:
717          IF ( mask_surface(mid) )  THEN
718!
719!--          In case of terrain-following output, the vertical dimensions are
720!--          indices, not meters
721             CALL netcdf_create_dim( id_set_mask(mid,av), 'ku_above_surf',     &
722                                     mask_size(mid,3), id_dim_zu_mask(mid,av), &
723                                     470 )
724             CALL netcdf_create_var( id_set_mask(mid,av),                      &
725                                     (/ id_dim_zu_mask(mid,av) /),             &
726                                     'ku_above_surf',                          &
727                                     NF90_DOUBLE, id_var_zu_mask(mid,av),      &
728                                     '1', 'grid point above terrain',          &
729                                     471, 472, 000 )
730             CALL netcdf_create_dim( id_set_mask(mid,av), 'kw_above_surf',     &
731                                     mask_size(mid,3), id_dim_zw_mask(mid,av), &
732                                     473 )
733             CALL netcdf_create_var( id_set_mask(mid,av),                      &
734                                     (/ id_dim_zw_mask(mid,av) /),             &
735                                     'kw_above_surf',                          &
736                                     NF90_DOUBLE, id_var_zw_mask(mid,av),      &
737                                    '1', 'grid point above terrain',           &
738                                    474, 475, 000 )
739          ELSE
740!
741!--          Define vertical coordinate grid (zu grid)
742             CALL netcdf_create_dim( id_set_mask(mid,av), 'zu_3d',             &
743                                     mask_size(mid,3), id_dim_zu_mask(mid,av), &
744                                     470 )
745             CALL netcdf_create_var( id_set_mask(mid,av),                      &
746                                     (/ id_dim_zu_mask(mid,av) /), 'zu_3d',    &
747                                     NF90_DOUBLE, id_var_zu_mask(mid,av),      &
748                                     'meters', '', 471, 472, 000 )
749!
750!--          Define vertical coordinate grid (zw grid)
751             CALL netcdf_create_dim( id_set_mask(mid,av), 'zw_3d',             &
752                                     mask_size(mid,3), id_dim_zw_mask(mid,av), &
753                                     473 )
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),      &
757                                    'meters', '', 474, 475, 000 )
758          ENDIF
759!
760!--       Define x-axis (for scalar position)
761          CALL netcdf_create_dim( id_set_mask(mid,av), 'x', mask_size(mid,1),  &
762                                  id_dim_x_mask(mid,av), 476 )
763          CALL netcdf_create_var( id_set_mask(mid,av),                         &
764                                  (/ id_dim_x_mask(mid,av) /), 'x',            &
765                                  NF90_DOUBLE, id_var_x_mask(mid,av),          &
766                                  'meters', '', 477, 478, 000 )
767!
768!--       Define x-axis (for u position)
769          CALL netcdf_create_dim( id_set_mask(mid,av), 'xu', mask_size(mid,1), &
770                                  id_dim_xu_mask(mid,av), 479 )
771          CALL netcdf_create_var( id_set_mask(mid,av),                         &
772                                  (/ id_dim_xu_mask(mid,av) /), 'xu',          &
773                                  NF90_DOUBLE, id_var_xu_mask(mid,av),         &
774                                  'meters', '', 480, 481, 000 )
775!
776!--       Define y-axis (for scalar position)
777          CALL netcdf_create_dim( id_set_mask(mid,av), 'y', mask_size(mid,2),  &
778                                  id_dim_y_mask(mid,av), 482 )
779          CALL netcdf_create_var( id_set_mask(mid,av),                         &
780                                  (/ id_dim_y_mask(mid,av) /), 'y',            &
781                                  NF90_DOUBLE, id_var_y_mask(mid,av),          &
782                                  'meters', '', 483, 484, 000 )
783!
784!--       Define y-axis (for v position)
785          CALL netcdf_create_dim( id_set_mask(mid,av), 'yv', mask_size(mid,2), &
786                                  id_dim_yv_mask(mid,av), 485 )
787          CALL netcdf_create_var( id_set_mask(mid,av),                         &
788                                  (/ id_dim_yv_mask(mid,av) /),                &
789                                  'yv', NF90_DOUBLE, id_var_yv_mask(mid,av),   &
790                                  'meters', '', 486, 487, 000 )
791!
792!--       Define UTM and geographic coordinates
793          CALL define_geo_coordinates( id_set_mask(mid,av),               &
794                  (/ id_dim_x_mask(mid,av), id_dim_xu_mask(mid,av) /),    &
795                  (/ id_dim_y_mask(mid,av), id_dim_yv_mask(mid,av) /),    &
796                  id_var_eutm_mask(:,mid,av), id_var_nutm_mask(:,mid,av), &
797                  id_var_lat_mask(:,mid,av), id_var_lon_mask(:,mid,av)    )
798!
799!--       Define coordinate-reference system
800          CALL netcdf_create_crs( id_set_mask(mid,av), 000 )
801!
802!--       In case of non-flat topography define 2d-arrays containing the height
803!--       information. Only for parallel netcdf output.
804          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
805               netcdf_data_format > 4 )  THEN
806!
807!--          Define zusi = zu(nzb_s_inner)
808             CALL netcdf_create_var( id_set_mask(mid,av),                      &
809                                     (/ id_dim_x_mask(mid,av),                 &
810                                        id_dim_y_mask(mid,av) /), 'zusi',      &
811                                     NF90_DOUBLE, id_var_zusi_mask(mid,av),    &
812                                     'meters', 'zu(nzb_s_inner)', 488, 489,    &
813                                     490 )
814!
815!--          Define zwwi = zw(nzb_w_inner)
816             CALL netcdf_create_var( id_set_mask(mid,av),                      &
817                                     (/ id_dim_x_mask(mid,av),                 &
818                                        id_dim_y_mask(mid,av) /), 'zwwi',      &
819                                     NF90_DOUBLE, id_var_zwwi_mask(mid,av),    &
820                                     'meters', 'zw(nzb_w_inner)', 491, 492,    &
821                                     493 )
822          ENDIF
823
824          IF ( land_surface )  THEN
825!
826!--          Define vertical coordinate grid (zw grid)
827             CALL netcdf_create_dim( id_set_mask(mid,av), 'zs_3d',             &
828                                     mask_size(mid,3), id_dim_zs_mask(mid,av), &
829                                     536 )
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),      &
833                                     'meters', '', 537, 555, 000 )
834          ENDIF
835
836!
837!--       Define the variables
838          var_list = ';'
839          i = 1
840
841          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
842
843             trimvar = TRIM( domask(mid,av,i) )
844!
845!--          Check for the grid
846             found = .FALSE.
847             SELECT CASE ( trimvar )
848!
849!--             Most variables are defined on the scalar grid
850                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',                &
851                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
852                       's', 'theta', 'thetal', 'thetav' )
853
854                   grid_x = 'x'
855                   grid_y = 'y'
856                   grid_z = 'zu'
857!
858!--             u grid
859                CASE ( 'u' )
860
861                   grid_x = 'xu'
862                   grid_y = 'y'
863                   grid_z = 'zu'
864!
865!--             v grid
866                CASE ( 'v' )
867
868                   grid_x = 'x'
869                   grid_y = 'yv'
870                   grid_z = 'zu'
871!
872!--             w grid
873                CASE ( 'w' )
874
875                   grid_x = 'x'
876                   grid_y = 'y'
877                   grid_z = 'zw'
878
879
880                CASE DEFAULT
881!
882!--                Check for quantities defined in other modules
883                   CALL tcm_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
884
885                   IF ( .NOT. found  .AND.  air_chemistry )  THEN
886                      CALL chem_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
887                   ENDIF
888
889                   IF ( .NOT. found )                                          &
890                      CALL doq_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
891
892                   IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
893                      CALL gust_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
894                   ENDIF
895
896                   IF ( .NOT. found  .AND. land_surface )  THEN
897                      CALL lsm_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
898                   ENDIF
899
900                   IF ( .NOT. found  .AND.  ocean_mode )  THEN
901                      CALL ocean_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
902                   ENDIF
903
904                   IF ( .NOT. found  .AND.  plant_canopy )  THEN
905                      CALL pcm_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
906                   ENDIF
907
908                   IF ( .NOT. found  .AND.  radiation )  THEN
909                      CALL radiation_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
910                   ENDIF
911!
912!--                Check for SALSA quantities
913                   IF ( .NOT. found  .AND.  salsa )  THEN
914                      CALL salsa_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
915                   ENDIF
916
917                   IF ( .NOT. found  .AND.  urban_surface )  THEN
918                      CALL usm_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
919                   ENDIF
920!
921!--                Now check for user-defined quantities
922                   IF ( .NOT. found  .AND.  user_module_enabled )  THEN
923                      CALL user_define_netcdf_grid( trimvar, found, grid_x, grid_y, grid_z )
924                   ENDIF
925
926                   IF ( .NOT. found )  THEN
927                      WRITE ( message_string, * ) 'no grid defined for variable ', TRIM( trimvar )
928                      CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
929                   ENDIF
930
931             END SELECT
932
933!
934!--          Select the respective dimension ids
935             IF ( grid_x == 'x' )  THEN
936                id_x = id_dim_x_mask(mid,av)
937             ELSEIF ( grid_x == 'xu' )  THEN
938                id_x = id_dim_xu_mask(mid,av)
939             ENDIF
940
941             IF ( grid_y == 'y' )  THEN
942                id_y = id_dim_y_mask(mid,av)
943             ELSEIF ( grid_y == 'yv' )  THEN
944                id_y = id_dim_yv_mask(mid,av)
945             ENDIF
946
947             IF ( grid_z == 'zu' )  THEN
948                id_z = id_dim_zu_mask(mid,av)
949             ELSEIF ( grid_z == 'zw' )  THEN
950                id_z = id_dim_zw_mask(mid,av)
951             ELSEIF ( grid_z == "zs" )  THEN
952                id_z = id_dim_zs_mask(mid,av)
953             ENDIF
954
955!
956!--          Define the grid
957             CALL netcdf_create_var( id_set_mask(mid,av), (/ id_x, id_y, id_z, &
958                                     id_dim_time_mask(mid,av) /),              &
959                                     domask(mid,av,i), nc_precision(11),       &
960                                     id_var_domask(mid,av,i),                  &
961                                     TRIM( domask_unit(mid,av,i) ),            &
962                                     domask(mid,av,i), 494, 495, 496, .TRUE. )
963
964             var_list = TRIM( var_list ) // TRIM( domask(mid,av,i) ) // ';'
965
966             i = i + 1
967
968          ENDDO
969
970!
971!--       No arrays to output
972          IF ( i == 1 )  RETURN
973
974!
975!--       Write the list of variables as global attribute (this is used by
976!--       restart runs and by combine_plot_fields)
977          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
978                                  'VAR_LIST', var_list )
979          CALL netcdf_handle_error( 'netcdf_define_header', 497 )
980
981!
982!--       Leave netCDF define mode
983          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
984          CALL netcdf_handle_error( 'netcdf_define_header', 498 )
985
986!
987!--       Write data for x (shifted by +dx/2) and xu axis
988          ALLOCATE( netcdf_data(mask_size(mid,1)) )
989
990          netcdf_data = ( mask_i_global(mid,:mask_size(mid,1)) + 0.5_wp ) * dx
991
992          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_x_mask(mid,av), &
993                                  netcdf_data, start = (/ 1 /),               &
994                                  count = (/ mask_size(mid,1) /) )
995          CALL netcdf_handle_error( 'netcdf_define_header', 499 )
996
997          netcdf_data = mask_i_global(mid,:mask_size(mid,1)) * dx
998
999          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_xu_mask(mid,av),&
1000                                  netcdf_data, start = (/ 1 /),               &
1001                                  count = (/ mask_size(mid,1) /) )
1002          CALL netcdf_handle_error( 'netcdf_define_header', 500 )
1003
1004          DEALLOCATE( netcdf_data )
1005
1006!
1007!--       Write data for y (shifted by +dy/2) and yv axis
1008          ALLOCATE( netcdf_data(mask_size(mid,2)) )
1009
1010          netcdf_data = ( mask_j_global(mid,:mask_size(mid,2)) + 0.5_wp ) * dy
1011
1012          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_y_mask(mid,av), &
1013                                  netcdf_data, start = (/ 1 /),               &
1014                                  count = (/ mask_size(mid,2) /))
1015          CALL netcdf_handle_error( 'netcdf_define_header', 501 )
1016
1017          netcdf_data = mask_j_global(mid,:mask_size(mid,2)) * dy
1018
1019          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
1020                                  netcdf_data, start = (/ 1 /),    &
1021                                  count = (/ mask_size(mid,2) /))
1022          CALL netcdf_handle_error( 'netcdf_define_header', 502 )
1023
1024          DEALLOCATE( netcdf_data )
1025
1026!
1027!--       Write UTM coordinates
1028          IF ( init_model%rotation_angle == 0.0_wp )  THEN
1029!
1030!--          1D in case of no rotation
1031             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
1032!
1033!--          x coordinates
1034             ALLOCATE( netcdf_data(mask_size(mid,1)) )
1035             DO  k = 0, 2
1036!
1037!--             Scalar grid points
1038                IF ( k == 0 )  THEN
1039                   shift_x = 0.5
1040!
1041!--             u grid points
1042                ELSEIF ( k == 1 )  THEN
1043                   shift_x = 0.0
1044!
1045!--             v grid points
1046                ELSEIF ( k == 2 )  THEN
1047                   shift_x = 0.5
1048                ENDIF
1049
1050                netcdf_data = init_model%origin_x + cos_ra                     &
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 /), &
1056                                        count = (/ mask_size(mid,1) /) )
1057                CALL netcdf_handle_error( 'netcdf_define_header', 555 )
1058
1059             ENDDO
1060             DEALLOCATE( netcdf_data )
1061!
1062!--          y coordinates
1063             ALLOCATE( netcdf_data(mask_size(mid,2)) )
1064             DO  k = 0, 2
1065!
1066!--             Scalar grid points
1067                IF ( k == 0 )  THEN
1068                   shift_y = 0.5
1069!
1070!--             u grid points
1071                ELSEIF ( k == 1 )  THEN
1072                   shift_y = 0.5
1073!
1074!--             v grid points
1075                ELSEIF ( k == 2 )  THEN
1076                   shift_y = 0.0
1077                ENDIF
1078
1079                netcdf_data = init_model%origin_y + cos_ra                     &
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 /), &
1085                                        count = (/ mask_size(mid,2) /) )
1086                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1087
1088             ENDDO
1089             DEALLOCATE( netcdf_data )
1090
1091          ELSE
1092!
1093!--          2D in case of rotation
1094             ALLOCATE( netcdf_data_2d(mask_size(mid,1),mask_size(mid,2)) )
1095             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
1096             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
1097
1098             DO  k = 0, 2
1099!
1100!--            Scalar grid points
1101               IF ( k == 0 )  THEN
1102                  shift_x = 0.5 ; shift_y = 0.5
1103!
1104!--            u grid points
1105               ELSEIF ( k == 1 )  THEN
1106                  shift_x = 0.0 ; shift_y = 0.5
1107!
1108!--            v grid points
1109               ELSEIF ( k == 2 )  THEN
1110                  shift_x = 0.5 ; shift_y = 0.0
1111               ENDIF
1112
1113               DO  j = 1, mask_size(mid,2)
1114                  DO  i = 1, mask_size(mid,1)
1115                     netcdf_data_2d(i,j) = init_model%origin_x                 &
1116                           + cos_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
1117                           + sin_ra * ( mask_j_global(mid,j) + shift_y ) * dy
1118                  ENDDO
1119               ENDDO
1120
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), &
1125                                                  mask_size(mid,2) /) )
1126               CALL netcdf_handle_error( 'netcdf_define_header', 555 )
1127
1128               DO  j = 1, mask_size(mid,2)
1129                  DO  i = 1, mask_size(mid,1)
1130                     netcdf_data_2d(i,j) = init_model%origin_y                 &
1131                           - sin_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
1132                           + cos_ra * ( mask_j_global(mid,j) + shift_y ) * dy
1133                  ENDDO
1134               ENDDO
1135
1136               nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
1137                                       id_var_nutm_mask(k,mid,av), &
1138                                       netcdf_data_2d, start = (/ 1, 1 /), &
1139                                       count = (/ mask_size(mid,1), &
1140                                                  mask_size(mid,2) /) )
1141               CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1142
1143             ENDDO
1144             DEALLOCATE( netcdf_data_2d )
1145          ENDIF
1146!
1147!--       Write lon and lat data.
1148          ALLOCATE( lat(mask_size(mid,1),mask_size(mid,2)) )
1149          ALLOCATE( lon(mask_size(mid,1),mask_size(mid,2)) )
1150          cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
1151          sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
1152
1153          DO  k = 0, 2
1154!
1155!--          Scalar grid points
1156             IF ( k == 0 )  THEN
1157                shift_x = 0.5 ; shift_y = 0.5
1158!
1159!--          u grid points
1160             ELSEIF ( k == 1 )  THEN
1161                shift_x = 0.0 ; shift_y = 0.5
1162!
1163!--          v grid points
1164             ELSEIF ( k == 2 )  THEN
1165                shift_x = 0.5 ; shift_y = 0.0
1166             ENDIF
1167
1168             DO  j = 1, mask_size(mid,2)
1169                DO  i = 1, mask_size(mid,1)
1170                   eutm = init_model%origin_x                               &
1171                        + cos_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
1172                        + sin_ra * ( mask_j_global(mid,j) + shift_y ) * dy
1173                   nutm = init_model%origin_y                               &
1174                        - sin_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
1175                        + cos_ra * ( mask_j_global(mid,j) + shift_y ) * dy
1176
1177                   CALL  convert_utm_to_geographic( crs_list,          &
1178                                                    eutm, nutm,        &
1179                                                    lon(i,j), lat(i,j) )
1180                ENDDO
1181             ENDDO
1182
1183             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),           &
1184                                     id_var_lon_mask(k,mid,av),     &
1185                                     lon, start = (/ 1, 1 /),       &
1186                                     count = (/ mask_size(mid,1),   &
1187                                                mask_size(mid,2) /) )
1188             CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1189
1190             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),           &
1191                                     id_var_lat_mask(k,mid,av),     &
1192                                     lat, start = (/ 1, 1 /),       &
1193                                     count = (/ mask_size(mid,1),   &
1194                                                mask_size(mid,2) /) )
1195             CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1196          ENDDO
1197
1198          DEALLOCATE( lat )
1199          DEALLOCATE( lon )
1200!
1201!--       Write zu and zw data (vertical axes)
1202          ALLOCATE( netcdf_data(mask_size(mid,3)) )
1203
1204          IF ( mask_surface(mid) )  THEN
1205
1206             netcdf_data = mask_k_global(mid,:mask_size(mid,3))
1207
1208             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
1209                                     netcdf_data, start = (/ 1 /), &
1210                                     count = (/ mask_size(mid,3) /) )
1211             CALL netcdf_handle_error( 'netcdf_define_header', 503 )
1212
1213             netcdf_data = mask_k_global(mid,:mask_size(mid,3))
1214
1215             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
1216                                     netcdf_data, start = (/ 1 /), &
1217                                     count = (/ mask_size(mid,3) /) )
1218             CALL netcdf_handle_error( 'netcdf_define_header', 504 )
1219
1220          ELSE
1221
1222             netcdf_data = zu( mask_k_global(mid,:mask_size(mid,3)) )
1223
1224             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
1225                                     netcdf_data, start = (/ 1 /), &
1226                                     count = (/ mask_size(mid,3) /) )
1227             CALL netcdf_handle_error( 'netcdf_define_header', 503 )
1228
1229             netcdf_data = zw( mask_k_global(mid,:mask_size(mid,3)) )
1230
1231             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
1232                                     netcdf_data, start = (/ 1 /), &
1233                                     count = (/ mask_size(mid,3) /) )
1234             CALL netcdf_handle_error( 'netcdf_define_header', 504 )
1235
1236          ENDIF
1237
1238          DEALLOCATE( netcdf_data )
1239
1240!
1241!--       In case of non-flat topography write height information
1242          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
1243               netcdf_data_format > 4 )  THEN
1244
1245             ALLOCATE( netcdf_data_2d(mask_size_l(mid,1),mask_size_l(mid,2)) )
1246             netcdf_data_2d = zu_s_inner( mask_i(mid,:mask_size_l(mid,1)),     &
1247                                          mask_j(mid,:mask_size_l(mid,2)) )
1248
1249             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
1250                                     id_var_zusi_mask(mid,av),                 &
1251                                     netcdf_data_2d,                           &
1252                                     start = (/ 1, 1 /),                       &
1253                                     count = (/ mask_size_l(mid,1),            &
1254                                                mask_size_l(mid,2) /) )
1255             CALL netcdf_handle_error( 'netcdf_define_header', 505 )
1256
1257             netcdf_data_2d = zw_w_inner( mask_i(mid,:mask_size_l(mid,1)),     &
1258                                          mask_j(mid,:mask_size_l(mid,2)) )
1259
1260             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
1261                                     id_var_zwwi_mask(mid,av),                 &
1262                                     netcdf_data_2d,                           &
1263                                     start = (/ 1, 1 /),                       &
1264                                     count = (/ mask_size_l(mid,1),            &
1265                                                mask_size_l(mid,2) /) )
1266             CALL netcdf_handle_error( 'netcdf_define_header', 506 )
1267
1268             DEALLOCATE( netcdf_data_2d )
1269
1270          ENDIF
1271!
1272!--       soil is not in masked output for now - disable temporary this block
1273!          IF ( land_surface )  THEN
1274!
1275!--          Write zs data (vertical axes for soil model), use negative values
1276!--          to indicate soil depth
1277!             ALLOCATE( netcdf_data(mask_size(mid,3)) )
1278!
1279!             netcdf_data = zs( mask_k_global(mid,:mask_size(mid,3)) )
1280!
1281!             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zs_mask(mid,av), &
1282!                                     netcdf_data, start = (/ 1 /), &
1283!                                     count = (/ mask_size(mid,3) /) )
1284!             CALL netcdf_handle_error( 'netcdf_define_header', 538 )
1285!
1286!             DEALLOCATE( netcdf_data )
1287!
1288!          ENDIF
1289
1290!
1291!--       restore original parameter file_id (=formal parameter av) into av
1292          av = file_id
1293
1294
1295       CASE ( 'ma_ext' )
1296
1297!
1298!--       decompose actual parameter file_id (=formal parameter av) into
1299!--       mid and av
1300          file_id = av
1301          IF ( file_id <= 200+max_masks )  THEN
1302             mid = file_id - 200
1303             av = 0
1304          ELSE
1305             mid = file_id - (200+max_masks)
1306             av = 1
1307          ENDIF
1308
1309!
1310!--       Get the list of variables and compare with the actual run.
1311!--       First var_list_old has to be reset, since GET_ATT does not assign
1312!--       trailing blanks.
1313          var_list_old = ' '
1314          nc_stat = NF90_GET_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST',&
1315                                  var_list_old )
1316          CALL netcdf_handle_error( 'netcdf_define_header', 507 )
1317
1318          var_list = ';'
1319          i = 1
1320          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
1321             var_list = TRIM(var_list) // TRIM( domask(mid,av,i) ) // ';'
1322             i = i + 1
1323          ENDDO
1324
1325          IF ( av == 0 )  THEN
1326             var = '(mask)'
1327          ELSE
1328             var = '(mask_av)'
1329          ENDIF
1330
1331          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
1332             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),       &
1333                  ' data for mask', mid, ' from previous run found,',           &
1334                  '&but this file cannot be extended due to variable ',         &
1335                  'mismatch.&New file is created instead.'
1336             CALL message( 'define_netcdf_header', 'PA0335', 0, 1, 0, 6, 0 )
1337             extend = .FALSE.
1338             RETURN
1339          ENDIF
1340
1341!
1342!--       Get and compare the number of vertical gridpoints
1343          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'zu_3d', &
1344                                    id_var_zu_mask(mid,av) )
1345          CALL netcdf_handle_error( 'netcdf_define_header', 508 )
1346
1347          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),     &
1348                                           id_var_zu_mask(mid,av),  &
1349                                           dimids = id_dim_zu_mask_old )
1350          CALL netcdf_handle_error( 'netcdf_define_header', 509 )
1351          id_dim_zu_mask(mid,av) = id_dim_zu_mask_old(1)
1352
1353          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),               &
1354                                            id_dim_zu_mask(mid,av),            &
1355                                            len = nz_old )
1356          CALL netcdf_handle_error( 'netcdf_define_header', 510 )
1357
1358          IF ( mask_size(mid,3) /= nz_old )  THEN
1359             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),      &
1360                  '&data for mask', mid, ' from previous run found,',          &
1361                  ' but this file cannot be extended due to mismatch in ',     &
1362                  ' number of vertical grid points.',                          &
1363                  '&New file is created instead.'
1364             CALL message( 'define_netcdf_header', 'PA0336', 0, 1, 0, 6, 0 )
1365             extend = .FALSE.
1366             RETURN
1367          ENDIF
1368
1369!
1370!--       Get the id of the time coordinate (unlimited coordinate) and its
1371!--       last index on the file. The next time level is plmask..count+1.
1372!--       The current time must be larger than the last output time
1373!--       on the file.
1374          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'time',               &
1375                                    id_var_time_mask(mid,av) )
1376          CALL netcdf_handle_error( 'netcdf_define_header', 511 )
1377
1378          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),                &
1379                                           id_var_time_mask(mid,av),           &
1380                                           dimids = id_dim_time_old )
1381          CALL netcdf_handle_error( 'netcdf_define_header', 512 )
1382          id_dim_time_mask(mid,av) = id_dim_time_old(1)
1383
1384          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),               &
1385                                            id_dim_time_mask(mid,av),          &
1386                                            len = domask_time_count(mid,av) )
1387          CALL netcdf_handle_error( 'netcdf_define_header', 513 )
1388
1389          nc_stat = NF90_GET_VAR( id_set_mask(mid,av),                         &
1390                                  id_var_time_mask(mid,av),                    &
1391                                  last_time_coordinate,                        &
1392                                  start = (/ domask_time_count(mid,av) /),     &
1393                                  count = (/ 1 /) )
1394          CALL netcdf_handle_error( 'netcdf_define_header', 514 )
1395
1396          IF ( last_time_coordinate(1) >= simulated_time )  THEN
1397             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),      &
1398                  ' data for mask', mid, ' from previous run found,',          &
1399                  '&but this file cannot be extended because the current ',    &
1400                  'output time is less or equal than the last output time ',   &
1401                  'on this file.&New file is created instead.'
1402             CALL message( 'define_netcdf_header', 'PA0337', 0, 1, 0, 6, 0 )
1403             domask_time_count(mid,av) = 0
1404             extend = .FALSE.
1405             RETURN
1406          ENDIF
1407
1408!
1409!--       Dataset seems to be extendable.
1410!--       Now get the variable ids.
1411          i = 1
1412          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
1413             nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), &
1414                                       TRIM( domask(mid,av,i) ), &
1415                                       id_var_domask(mid,av,i) )
1416             CALL netcdf_handle_error( 'netcdf_define_header', 515 )
1417             i = i + 1
1418          ENDDO
1419
1420!
1421!--       Update the title attribute on file
1422!--       In order to avoid 'data mode' errors if updated attributes are larger
1423!--       than their original size, NF90_PUT_ATT is called in 'define mode'
1424!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
1425!--       performance loss due to data copying; an alternative strategy would be
1426!--       to ensure equal attribute size in a job chain. Maybe revise later.
1427          IF ( av == 0 )  THEN
1428             time_average_text = ' '
1429          ELSE
1430             WRITE (time_average_text, '('', '',F7.1,'' s average'')')         &
1431                                                            averaging_interval
1432          ENDIF
1433          nc_stat = NF90_REDEF( id_set_mask(mid,av) )
1434          CALL netcdf_handle_error( 'netcdf_define_header', 516 )
1435          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title',   &
1436                                  TRIM( run_description_header ) //            &
1437                                  TRIM( time_average_text ) )
1438          CALL netcdf_handle_error( 'netcdf_define_header', 517 )
1439          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
1440          CALL netcdf_handle_error( 'netcdf_define_header', 518 )
1441          WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ),         &
1442               ' data for mask', mid, ' from previous run found.',             &
1443               ' &This file will be extended.'
1444          CALL message( 'define_netcdf_header', 'PA0338', 0, 0, 0, 6, 0 )
1445!
1446!--       restore original parameter file_id (=formal parameter av) into av
1447          av = file_id
1448
1449
1450       CASE ( '3d_new' )
1451
1452!
1453!--       Define some global attributes of the dataset
1454          IF ( av == 0 )  THEN
1455             CALL netcdf_create_global_atts( id_set_3d(av), '3d', TRIM( run_description_header ), 62 )
1456             time_average_text = ' '
1457          ELSE
1458             CALL netcdf_create_global_atts( id_set_3d(av), '3d_av', TRIM( run_description_header ), 62 )
1459             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
1460             nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'time_avg',   &
1461                                     TRIM( time_average_text ) )
1462             CALL netcdf_handle_error( 'netcdf_define_header', 63 )
1463          ENDIF
1464
1465!
1466!--       Define time coordinate for volume data.
1467!--       For parallel output the time dimensions has to be limited, otherwise
1468!--       the performance drops significantly.
1469          IF ( netcdf_data_format < 5 )  THEN
1470             CALL netcdf_create_dim( id_set_3d(av), 'time', NF90_UNLIMITED,    &
1471                                     id_dim_time_3d(av), 64 )
1472          ELSE
1473             CALL netcdf_create_dim( id_set_3d(av), 'time', ntdim_3d(av),      &
1474                                     id_dim_time_3d(av), 523 )
1475          ENDIF
1476
1477          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_time_3d(av) /),     &
1478                                  'time', NF90_DOUBLE, id_var_time_3d(av),     &
1479                                  'seconds', 'time', 65, 66, 00 )
1480          CALL netcdf_create_att( id_set_3d(av), id_var_time_3d(av), 'standard_name', 'time', 000)
1481          CALL netcdf_create_att( id_set_3d(av), id_var_time_3d(av), 'axis', 'T', 000)
1482!
1483!--       Define spatial dimensions and coordinates:
1484!--       Define vertical coordinate grid (zu grid)
1485          CALL netcdf_create_dim( id_set_3d(av), 'zu_3d', nz_do3d-nzb+1,       &
1486                                  id_dim_zu_3d(av), 67 )
1487          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zu_3d(av) /),       &
1488                                  'zu_3d', NF90_DOUBLE, id_var_zu_3d(av),      &
1489                                  'meters', '', 68, 69, 00 )
1490!
1491!--       Define vertical coordinate grid (zw grid)
1492          CALL netcdf_create_dim( id_set_3d(av), 'zw_3d', nz_do3d-nzb+1,       &
1493                                  id_dim_zw_3d(av), 70 )
1494          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zw_3d(av) /),       &
1495                                  'zw_3d', NF90_DOUBLE, id_var_zw_3d(av),      &
1496                                  'meters', '', 71, 72, 00 )
1497!
1498!--       Define x-axis (for scalar position)
1499          CALL netcdf_create_dim( id_set_3d(av), 'x', nx+1, id_dim_x_3d(av),   &
1500                                  73 )
1501          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av) /), 'x',   &
1502                                  NF90_DOUBLE, id_var_x_3d(av), 'meters', '',  &
1503                                  74, 75, 00 )
1504!
1505!--       Define x-axis (for u position)
1506          CALL netcdf_create_dim( id_set_3d(av), 'xu', nx+1, id_dim_xu_3d(av), &
1507                                  358 )
1508          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_xu_3d(av) /), 'xu', &
1509                                  NF90_DOUBLE, id_var_xu_3d(av), 'meters', '', &
1510                                  359, 360, 000 )
1511!
1512!--       Define y-axis (for scalar position)
1513          CALL netcdf_create_dim( id_set_3d(av), 'y', ny+1, id_dim_y_3d(av),   &
1514                                  76 )
1515          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_y_3d(av) /), 'y',   &
1516                                  NF90_DOUBLE, id_var_y_3d(av), 'meters', '',  &
1517                                  77, 78, 00 )
1518!
1519!--       Define y-axis (for v position)
1520          CALL netcdf_create_dim( id_set_3d(av), 'yv', ny+1, id_dim_yv_3d(av), &
1521                                  361 )
1522          CALL netcdf_create_var( id_set_3d(av), (/ id_dim_yv_3d(av) /), 'yv', &
1523                                  NF90_DOUBLE, id_var_yv_3d(av), 'meters', '', &
1524                                  362, 363, 000 )
1525!
1526!--       Define UTM and geographic coordinates
1527          CALL define_geo_coordinates( id_set_3d(av),         &
1528                  (/ id_dim_x_3d(av), id_dim_xu_3d(av) /),    &
1529                  (/ id_dim_y_3d(av), id_dim_yv_3d(av) /),    &
1530                  id_var_eutm_3d(:,av), id_var_nutm_3d(:,av), &
1531                  id_var_lat_3d(:,av), id_var_lon_3d(:,av)    )
1532!
1533!--       Define coordinate-reference system
1534          CALL netcdf_create_crs( id_set_3d(av), 000 )
1535!
1536!--       In case of non-flat topography define 2d-arrays containing the height
1537!--       information. Only output 2d topography information in case of parallel
1538!--       output.
1539          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
1540               netcdf_data_format > 4 )  THEN
1541!
1542!--          Define zusi = zu(nzb_s_inner)
1543             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av),        &
1544                                     id_dim_y_3d(av) /), 'zusi', NF90_DOUBLE,  &
1545                                     id_var_zusi_3d(av), 'meters',             &
1546                                     'zu(nzb_s_inner)', 413, 414, 415 )
1547!
1548!--          Define zwwi = zw(nzb_w_inner)
1549             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_x_3d(av),        &
1550                                     id_dim_y_3d(av) /), 'zwwi', NF90_DOUBLE,  &
1551                                     id_var_zwwi_3d(av), 'meters',             &
1552                                     'zw(nzb_w_inner)', 416, 417, 418 )
1553
1554          ENDIF
1555
1556          IF ( land_surface )  THEN
1557!
1558!--          Define vertical coordinate grid (zs grid)
1559             CALL netcdf_create_dim( id_set_3d(av), 'zs_3d',                   &
1560                                     nzt_soil-nzb_soil+1, id_dim_zs_3d(av), 70 )
1561             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zs_3d(av) /),    &
1562                                     'zs_3d', NF90_DOUBLE, id_var_zs_3d(av),   &
1563                                     'meters', '', 71, 72, 00 )
1564
1565          ENDIF
1566
1567          IF ( plant_canopy )  THEN
1568!
1569!--          Define vertical coordinate grid (zpc grid)
1570             CALL netcdf_create_dim( id_set_3d(av), 'zpc_3d',                  &
1571                                     pch_index+1, id_dim_zpc_3d(av), 70 )
1572             !netcdf_create_dim(ncid, dim_name, ncdim_type, ncdim_id, error_no)
1573             CALL netcdf_create_var( id_set_3d(av), (/ id_dim_zpc_3d(av) /),    &
1574                                     'zpc_3d', NF90_DOUBLE, id_var_zpc_3d(av),   &
1575                                     'meters', '', 71, 72, 00 )
1576
1577          ENDIF
1578
1579!
1580!--       Define the variables
1581          var_list = ';'
1582          i = 1
1583
1584          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
1585!
1586!--          Temporary solution to account for data output within the new urban
1587!--          surface model (urban_surface_mod.f90), see also SELECT CASE ( trimvar )
1588             trimvar = TRIM( do3d(av,i) )
1589             IF ( urban_surface  .AND.  trimvar(1:4) == 'usm_' )  THEN
1590                trimvar = 'usm_output'
1591             ENDIF
1592!
1593!--          Check for the grid
1594             found = .FALSE.
1595             SELECT CASE ( trimvar )
1596!
1597!--             Most variables are defined on the scalar grid
1598                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',   &
1599                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
1600                       's', 'theta', 'thetal', 'thetav' )
1601
1602                   grid_x = 'x'
1603                   grid_y = 'y'
1604                   grid_z = 'zu'
1605!
1606!--             u grid
1607                CASE ( 'u' )
1608
1609                   grid_x = 'xu'
1610                   grid_y = 'y'
1611                   grid_z = 'zu'
1612!
1613!--             v grid
1614                CASE ( 'v' )
1615
1616                   grid_x = 'x'
1617                   grid_y = 'yv'
1618                   grid_z = 'zu'
1619!
1620!--             w grid
1621                CASE ( 'w' )
1622
1623                   grid_x = 'x'
1624                   grid_y = 'y'
1625                   grid_z = 'zw'
1626
1627!
1628!--             Block of urban surface model outputs
1629                CASE ( 'usm_output' )
1630                   CALL usm_define_netcdf_grid( do3d(av,i), found, &
1631                                                   grid_x, grid_y, grid_z )
1632
1633                CASE DEFAULT
1634
1635                   CALL tcm_define_netcdf_grid( do3d(av,i), found, &
1636                                                   grid_x, grid_y, grid_z )
1637
1638!
1639!--                Check for land surface quantities
1640                   IF ( .NOT. found .AND. land_surface )  THEN
1641                      CALL lsm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
1642                                                   grid_y, grid_z )
1643                   ENDIF
1644!
1645!--                Check for ocean quantities
1646                   IF ( .NOT. found  .AND.  ocean_mode )  THEN
1647                      CALL ocean_define_netcdf_grid( do3d(av,i), found,  &
1648                                                     grid_x, grid_y, grid_z )
1649                   ENDIF
1650
1651!
1652!--                Check for plant canopy quantities
1653                   IF ( .NOT. found  .AND.  plant_canopy )  THEN
1654                      CALL pcm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
1655                                                   grid_y, grid_z )
1656                   ENDIF
1657
1658!
1659!--                Check for radiation quantities
1660                   IF ( .NOT. found  .AND.  radiation )  THEN
1661                      CALL radiation_define_netcdf_grid( do3d(av,i), found,    &
1662                                                         grid_x, grid_y,       &
1663                                                         grid_z )
1664                   ENDIF
1665
1666!--                Check for gust module quantities
1667                   IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
1668                      CALL gust_define_netcdf_grid( do3d(av,i), found, grid_x, &
1669                                                    grid_y, grid_z )
1670                   ENDIF
1671!
1672!--                Check for indoor model quantities
1673                   IF ( .NOT. found .AND. indoor_model ) THEN
1674                      CALL im_define_netcdf_grid( do3d(av,i), found,           &
1675                                                  grid_x, grid_y, grid_z )
1676                   ENDIF
1677
1678!
1679!--                Check for biometeorology quantities
1680                   IF ( .NOT. found  .AND.  biometeorology )  THEN
1681                      CALL bio_define_netcdf_grid( do3d(av,i), found,          &
1682                                                   grid_x, grid_y, grid_z )
1683                   ENDIF
1684
1685!
1686!--                Check for chemistry quantities
1687                   IF ( .NOT. found  .AND.  air_chemistry )  THEN
1688                      CALL chem_define_netcdf_grid( do3d(av,i), found,         &
1689                                                    grid_x, grid_y, grid_z )
1690                   ENDIF
1691
1692!
1693!--                Check for SALSA quantities
1694                   IF ( .NOT. found  .AND.  salsa )  THEN
1695                      CALL salsa_define_netcdf_grid( do3d(av,i), found, grid_x,&
1696                                                     grid_y, grid_z )
1697                   ENDIF
1698!
1699!--                Check for user-defined quantities
1700                   IF ( .NOT. found  .AND.  user_module_enabled )  THEN
1701                      CALL user_define_netcdf_grid( do3d(av,i), found, grid_x, &
1702                                                    grid_y, grid_z )
1703                   ENDIF
1704
1705                   IF ( .NOT. found )                                          &
1706                      CALL doq_define_netcdf_grid( do3d(av,i), found, grid_x,  &
1707                                                   grid_y, grid_z        )
1708
1709                   IF ( .NOT. found )  THEN
1710                      WRITE ( message_string, * ) 'no grid defined for varia', &
1711                                                  'ble ', TRIM( do3d(av,i) )
1712                      CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, &
1713                                    6, 0 )
1714                   ENDIF
1715
1716             END SELECT
1717
1718!
1719!--          Select the respective dimension ids
1720             IF ( grid_x == 'x' )  THEN
1721                id_x = id_dim_x_3d(av)
1722             ELSEIF ( grid_x == 'xu' )  THEN
1723                id_x = id_dim_xu_3d(av)
1724             ENDIF
1725
1726             IF ( grid_y == 'y' )  THEN
1727                id_y = id_dim_y_3d(av)
1728             ELSEIF ( grid_y == 'yv' )  THEN
1729                id_y = id_dim_yv_3d(av)
1730             ENDIF
1731
1732             IF ( grid_z == 'zu' )  THEN
1733                id_z = id_dim_zu_3d(av)
1734             ELSEIF ( grid_z == 'zw' )  THEN
1735                id_z = id_dim_zw_3d(av)
1736             ELSEIF ( grid_z == 'zs' )  THEN
1737                id_z = id_dim_zs_3d(av)
1738             ELSEIF ( grid_z == 'zpc' )  THEN
1739                id_z = id_dim_zpc_3d(av)
1740             ENDIF
1741
1742!
1743!--          Define the grid
1744             CALL netcdf_create_var( id_set_3d(av),(/ id_x, id_y, id_z,        &
1745                                     id_dim_time_3d(av) /), do3d(av,i),        &
1746                                     nc_precision(4), id_var_do3d(av,i),       &
1747                                     TRIM( do3d_unit(av,i) ), do3d(av,i), 79,  &
1748                                     80, 357, .TRUE. )
1749#if defined( __netcdf4_parallel )
1750             IF ( netcdf_data_format > 4 )  THEN
1751!
1752!--             Set no fill for every variable to increase performance.
1753                nc_stat = NF90_DEF_VAR_FILL( id_set_3d(av),     &
1754                                             id_var_do3d(av,i), &
1755                                             NF90_NOFILL, 0 )
1756                CALL netcdf_handle_error( 'netcdf_define_header', 532 )
1757!
1758!--             Set collective io operations for parallel io
1759                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
1760                                               id_var_do3d(av,i), &
1761                                               NF90_COLLECTIVE )
1762                CALL netcdf_handle_error( 'netcdf_define_header', 445 )
1763             ENDIF
1764#endif
1765             var_list = TRIM( var_list ) // TRIM( do3d(av,i) ) // ';'
1766
1767             i = i + 1
1768
1769          ENDDO
1770
1771!
1772!--       No arrays to output
1773          IF ( i == 1 )  RETURN
1774
1775!
1776!--       Write the list of variables as global attribute (this is used by
1777!--       restart runs and by combine_plot_fields)
1778          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
1779                                  var_list )
1780          CALL netcdf_handle_error( 'netcdf_define_header', 81 )
1781
1782!
1783!--       Set general no fill, otherwise the performance drops significantly for
1784!--       parallel output.
1785          nc_stat = NF90_SET_FILL( id_set_3d(av), NF90_NOFILL, oldmode )
1786          CALL netcdf_handle_error( 'netcdf_define_header', 528 )
1787
1788!
1789!--       Leave netCDF define mode
1790          nc_stat = NF90_ENDDEF( id_set_3d(av) )
1791          CALL netcdf_handle_error( 'netcdf_define_header', 82 )
1792
1793!
1794!--       These data are only written by PE0 for parallel output to increase
1795!--       the performance.
1796          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
1797!
1798!--          Write data for x (shifted by +dx/2) and xu axis
1799             ALLOCATE( netcdf_data(0:nx) )
1800
1801             DO  i = 0, nx
1802                netcdf_data(i) = ( i + 0.5 ) * dx
1803             ENDDO
1804
1805             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av),  &
1806                                     netcdf_data, start = (/ 1 /),    &
1807                                     count = (/ nx+1 /) )
1808             CALL netcdf_handle_error( 'netcdf_define_header', 83 )
1809
1810             DO  i = 0, nx
1811                netcdf_data(i) = i * dx
1812             ENDDO
1813
1814             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_xu_3d(av), &
1815                                     netcdf_data, start = (/ 1 /),    &
1816                                     count = (/ nx+1 /) )
1817             CALL netcdf_handle_error( 'netcdf_define_header', 385 )
1818
1819             DEALLOCATE( netcdf_data )
1820
1821!
1822!--          Write data for y (shifted by +dy/2) and yv axis
1823             ALLOCATE( netcdf_data(0:ny) )
1824
1825             DO  i = 0, ny
1826                netcdf_data(i) = ( i + 0.5_wp ) * dy
1827             ENDDO
1828
1829             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av),  &
1830                                     netcdf_data, start = (/ 1 /),    &
1831                                     count = (/ ny+1 /) )
1832             CALL netcdf_handle_error( 'netcdf_define_header', 84 )
1833
1834             DO  i = 0, ny
1835                netcdf_data(i) = i * dy
1836             ENDDO
1837
1838             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_yv_3d(av), &
1839                                     netcdf_data, start = (/ 1 /),    &
1840                                     count = (/ ny+1 /))
1841             CALL netcdf_handle_error( 'netcdf_define_header', 387 )
1842
1843             DEALLOCATE( netcdf_data )
1844
1845!
1846!--          Write UTM coordinates
1847             IF ( init_model%rotation_angle == 0.0_wp )  THEN
1848!
1849!--             1D in case of no rotation
1850                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
1851!
1852!--             x coordinates
1853                ALLOCATE( netcdf_data(0:nx) )
1854                DO  k = 0, 2
1855!
1856!--                Scalar grid points
1857                   IF ( k == 0 )  THEN
1858                      shift_x = 0.5
1859!
1860!--                u grid points
1861                   ELSEIF ( k == 1 )  THEN
1862                      shift_x = 0.0
1863!
1864!--                v grid points
1865                   ELSEIF ( k == 2 )  THEN
1866                      shift_x = 0.5
1867                   ENDIF
1868
1869                   DO  i = 0, nx
1870                     netcdf_data(i) = init_model%origin_x            &
1871                                    + cos_ra * ( i + shift_x ) * dx
1872                   ENDDO
1873
1874                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),&
1875                                           netcdf_data, start = (/ 1 /),   &
1876                                           count = (/ nx+1 /) )
1877                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
1878
1879                ENDDO
1880                DEALLOCATE( netcdf_data )
1881!
1882!--             y coordinates
1883                ALLOCATE( netcdf_data(0:ny) )
1884                DO  k = 0, 2
1885!
1886!--                Scalar grid points
1887                   IF ( k == 0 )  THEN
1888                      shift_y = 0.5
1889!
1890!--                u grid points
1891                   ELSEIF ( k == 1 )  THEN
1892                      shift_y = 0.5
1893!
1894!--                v grid points
1895                   ELSEIF ( k == 2 )  THEN
1896                      shift_y = 0.0
1897                   ENDIF
1898
1899                   DO  j = 0, ny
1900                      netcdf_data(j) = init_model%origin_y            &
1901                                     + cos_ra * ( j + shift_y ) * dy
1902                   ENDDO
1903
1904                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),&
1905                                           netcdf_data, start = (/ 1 /),   &
1906                                           count = (/ ny+1 /) )
1907                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1908
1909                ENDDO
1910                DEALLOCATE( netcdf_data )
1911
1912             ELSE
1913!
1914!--             2D in case of rotation
1915                ALLOCATE( netcdf_data_2d(0:nx,0:ny) )
1916                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
1917                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
1918
1919                DO  k = 0, 2
1920!
1921!--               Scalar grid points
1922                  IF ( k == 0 )  THEN
1923                     shift_x = 0.5 ; shift_y = 0.5
1924!
1925!--               u grid points
1926                  ELSEIF ( k == 1 )  THEN
1927                     shift_x = 0.0 ; shift_y = 0.5
1928!
1929!--               v grid points
1930                  ELSEIF ( k == 2 )  THEN
1931                     shift_x = 0.5 ; shift_y = 0.0
1932                  ENDIF
1933
1934                  DO  j = 0, ny
1935                     DO  i = 0, nx
1936                        netcdf_data_2d(i,j) = init_model%origin_x            &
1937                                            + cos_ra * ( i + shift_x ) * dx  &
1938                                            + sin_ra * ( j + shift_y ) * dy
1939                     ENDDO
1940                  ENDDO
1941
1942                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),  &
1943                                          netcdf_data_2d, start = (/ 1, 1 /),   &
1944                                          count = (/ nx+1, ny+1 /) )
1945                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
1946
1947                  DO  j = 0, ny
1948                     DO  i = 0, nx
1949                        netcdf_data_2d(i,j) = init_model%origin_y            &
1950                                            - sin_ra * ( i + shift_x ) * dx  &
1951                                            + cos_ra * ( j + shift_y ) * dy
1952                     ENDDO
1953                  ENDDO
1954
1955                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),  &
1956                                          netcdf_data_2d, start = (/ 1, 1 /),   &
1957                                          count = (/ nx+1, ny+1 /) )
1958                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
1959
1960                ENDDO
1961                DEALLOCATE( netcdf_data_2d )
1962             ENDIF
1963!
1964!--          Write zu and zw data (vertical axes)
1965             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zu_3d(av),  &
1966                                     zu(nzb:nz_do3d), start = (/ 1 /), &
1967                                     count = (/ nz_do3d-nzb+1 /) )
1968             CALL netcdf_handle_error( 'netcdf_define_header', 85 )
1969
1970
1971             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zw_3d(av),  &
1972                                     zw(nzb:nz_do3d), start = (/ 1 /), &
1973                                     count = (/ nz_do3d-nzb+1 /) )
1974             CALL netcdf_handle_error( 'netcdf_define_header', 86 )
1975
1976             IF ( land_surface )  THEN
1977!
1978!--             Write zs grid
1979                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zs_3d(av),  &
1980                                        - zs(nzb_soil:nzt_soil), start = (/ 1 /), &
1981                                        count = (/ nzt_soil-nzb_soil+1 /) )
1982                CALL netcdf_handle_error( 'netcdf_define_header', 86 )
1983             ENDIF
1984
1985             IF ( plant_canopy )  THEN
1986!
1987!--             Write zpc grid
1988                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zpc_3d(av),  &
1989                                        zu(nzb:nzb+pch_index), start = (/ 1 /), &
1990                                        count = (/ pch_index+1 /) )
1991                CALL netcdf_handle_error( 'netcdf_define_header', 86 )
1992             ENDIF
1993
1994          ENDIF
1995!
1996!--       Write lon and lat data. Only for parallel output.
1997          IF ( netcdf_data_format > 4 )  THEN
1998
1999             ALLOCATE( lat(nxl:nxr,nys:nyn) )
2000             ALLOCATE( lon(nxl:nxr,nys:nyn) )
2001             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
2002             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
2003
2004             DO  k = 0, 2
2005!
2006!--             Scalar grid points
2007                IF ( k == 0 )  THEN
2008                   shift_x = 0.5 ; shift_y = 0.5
2009!
2010!--             u grid points
2011                ELSEIF ( k == 1 )  THEN
2012                   shift_x = 0.0 ; shift_y = 0.5
2013!
2014!--             v grid points
2015                ELSEIF ( k == 2 )  THEN
2016                   shift_x = 0.5 ; shift_y = 0.0
2017                ENDIF
2018
2019                DO  j = nys, nyn
2020                   DO  i = nxl, nxr
2021                      eutm = init_model%origin_x            &
2022                           + cos_ra * ( i + shift_x ) * dx  &
2023                           + sin_ra * ( j + shift_y ) * dy
2024                      nutm = init_model%origin_y            &
2025                           - sin_ra * ( i + shift_x ) * dx  &
2026                           + cos_ra * ( j + shift_y ) * dy
2027
2028                      CALL  convert_utm_to_geographic( crs_list,          &
2029                                                       eutm, nutm,        &
2030                                                       lon(i,j), lat(i,j) )
2031                   ENDDO
2032                ENDDO
2033
2034                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lon_3d(k,av), &
2035                                     lon, start = (/ nxl+1, nys+1 /),       &
2036                                     count = (/ nxr-nxl+1, nyn-nys+1 /) )
2037                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
2038
2039                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_lat_3d(k,av), &
2040                                     lat, start = (/ nxl+1, nys+1 /),       &
2041                                     count = (/ nxr-nxl+1, nyn-nys+1 /) )
2042                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
2043             ENDDO
2044
2045             DEALLOCATE( lat )
2046             DEALLOCATE( lon )
2047
2048          ENDIF
2049!
2050!--       In case of non-flat topography write height information. Only for
2051!--       parallel netcdf output.
2052          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
2053               netcdf_data_format > 4 )  THEN
2054
2055!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
2056!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
2057!                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
2058!                                        start = (/ nxl+1, nys+1 /),            &
2059!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
2060!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
2061!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
2062!                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
2063!                                        start = (/ nxl+1, nys+1 /),            &
2064!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
2065!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
2066!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
2067!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
2068!                                        start = (/ nxl+1, nys+1 /),            &
2069!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
2070!             ELSE
2071                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
2072                                        zu_s_inner(nxl:nxr,nys:nyn),           &
2073                                        start = (/ nxl+1, nys+1 /),            &
2074                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
2075!             ENDIF
2076             CALL netcdf_handle_error( 'netcdf_define_header', 419 )
2077
2078!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
2079!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
2080!                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
2081!                                        start = (/ nxl+1, nys+1 /),            &
2082!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
2083!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
2084!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
2085!                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
2086!                                        start = (/ nxl+1, nys+1 /),            &
2087!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
2088!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
2089!                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
2090!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
2091!                                        start = (/ nxl+1, nys+1 /),            &
2092!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
2093!             ELSE
2094                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
2095                                        zw_w_inner(nxl:nxr,nys:nyn),           &
2096                                        start = (/ nxl+1, nys+1 /),            &
2097                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
2098!             ENDIF
2099             CALL netcdf_handle_error( 'netcdf_define_header', 420 )
2100
2101          ENDIF
2102
2103       CASE ( '3d_ext' )
2104
2105!
2106!--       Get the list of variables and compare with the actual run.
2107!--       First var_list_old has to be reset, since GET_ATT does not assign
2108!--       trailing blanks.
2109          var_list_old = ' '
2110          nc_stat = NF90_GET_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
2111                                  var_list_old )
2112          CALL netcdf_handle_error( 'netcdf_define_header', 87 )
2113
2114          var_list = ';'
2115          i = 1
2116          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
2117             var_list = TRIM(var_list) // TRIM( do3d(av,i) ) // ';'
2118             i = i + 1
2119          ENDDO
2120
2121          IF ( av == 0 )  THEN
2122             var = '(3d)'
2123          ELSE
2124             var = '(3d_av)'
2125          ENDIF
2126
2127          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
2128             message_string = 'netCDF file for volume data ' //             &
2129                              TRIM( var ) // ' from previous run found,' // &
2130                              '&but this file cannot be extended due to' // &
2131                              ' variable mismatch.' //                      &
2132                              '&New file is created instead.'
2133             CALL message( 'define_netcdf_header', 'PA0245', 0, 1, 0, 6, 0 )
2134             extend = .FALSE.
2135             RETURN
2136          ENDIF
2137
2138!
2139!--       Get and compare the number of vertical gridpoints
2140          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'zu_3d', id_var_zu_3d(av) )
2141          CALL netcdf_handle_error( 'netcdf_define_header', 88 )
2142
2143          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_zu_3d(av), &
2144                                           dimids = id_dim_zu_3d_old )
2145          CALL netcdf_handle_error( 'netcdf_define_header', 89 )
2146          id_dim_zu_3d(av) = id_dim_zu_3d_old(1)
2147
2148          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_zu_3d(av), &
2149                                            len = nz_old )
2150          CALL netcdf_handle_error( 'netcdf_define_header', 90 )
2151
2152          IF ( nz_do3d-nzb+1 /= nz_old )  THEN
2153              message_string = 'netCDF file for volume data ' //             &
2154                               TRIM( var ) // ' from previous run found,' // &
2155                               '&but this file cannot be extended due to' // &
2156                               ' mismatch in number of' //                   &
2157                               ' vertical grid points (nz_do3d).' //         &
2158                               '&New file is created instead.'
2159             CALL message( 'define_netcdf_header', 'PA0246', 0, 1, 0, 6, 0 )
2160             extend = .FALSE.
2161             RETURN
2162          ENDIF
2163
2164!
2165!--       Get the id of the time coordinate (unlimited coordinate) and its
2166!--       last index on the file. The next time level is pl3d..count+1.
2167!--       The current time must be larger than the last output time
2168!--       on the file.
2169          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'time', id_var_time_3d(av) )
2170          CALL netcdf_handle_error( 'netcdf_define_header', 91 )
2171
2172          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_time_3d(av), &
2173                                           dimids = id_dim_time_old )
2174          CALL netcdf_handle_error( 'netcdf_define_header', 92 )
2175
2176          id_dim_time_3d(av) = id_dim_time_old(1)
2177
2178          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_time_3d(av), &
2179                                            len = ntime_count )
2180          CALL netcdf_handle_error( 'netcdf_define_header', 93 )
2181
2182!
2183!--       For non-parallel output use the last output time level of the netcdf
2184!--       file because the time dimension is unlimited. In case of parallel
2185!--       output the variable ntime_count could get the value of 9*10E36 because
2186!--       the time dimension is limited.
2187          IF ( netcdf_data_format < 5 ) do3d_time_count(av) = ntime_count
2188
2189          nc_stat = NF90_GET_VAR( id_set_3d(av), id_var_time_3d(av), &
2190                                  last_time_coordinate,              &
2191                                  start = (/ do3d_time_count(av) /), &
2192                                  count = (/ 1 /) )
2193          CALL netcdf_handle_error( 'netcdf_define_header', 94 )
2194
2195          IF ( last_time_coordinate(1) >= simulated_time )  THEN
2196             message_string = 'netCDF file for volume data ' //             &
2197                              TRIM( var ) // ' from previous run found,' // &
2198                              '&but this file cannot be extended becaus' // &
2199                              'e the current output time' //                &
2200                              '&is less or equal than the last output t' // &
2201                              'ime on this file.' //                        &
2202                              '&New file is created instead.'
2203             CALL message( 'define_netcdf_header', 'PA0247', 0, 1, 0, 6, 0 )
2204             do3d_time_count(av) = 0
2205             extend = .FALSE.
2206             RETURN
2207          ENDIF
2208
2209          IF ( netcdf_data_format > 4 )  THEN
2210!
2211!--          Check if the needed number of output time levels is increased
2212!--          compared to the number of time levels in the existing file.
2213             IF ( ntdim_3d(av) > ntime_count )  THEN
2214                message_string = 'netCDF file for volume data ' // &
2215                                 TRIM( var ) // ' from previous run found,' // &
2216                                 '&but this file cannot be extended becaus' // &
2217                                 'e the number of output time levels has b' // &
2218                                 'een increased compared to the previous s' // &
2219                                 'imulation.' //                               &
2220                                 '&New file is created instead.'
2221                CALL message( 'define_netcdf_header', 'PA0388', 0, 1, 0, 6, 0 )
2222                do3d_time_count(av) = 0
2223                extend = .FALSE.
2224!
2225!--             Recalculate the needed time levels for the new file.
2226                IF ( av == 0 )  THEN
2227                   ntdim_3d(0) = CEILING(                               &
2228                           ( end_time - MAX( skip_time_do3d,            &
2229                                             simulated_time_at_begin )  &
2230                           ) / dt_do3d )
2231                   IF ( do3d_at_begin )  ntdim_3d(0) = ntdim_3d(0) + 1
2232                ELSE
2233                   ntdim_3d(1) = CEILING(                               &
2234                           ( end_time - MAX( skip_time_data_output_av,  &
2235                                             simulated_time_at_begin )  &
2236                           ) / dt_data_output_av )
2237                ENDIF
2238                RETURN
2239             ENDIF
2240          ENDIF
2241
2242!
2243!--       Dataset seems to be extendable.
2244!--       Now get the variable ids.
2245          i = 1
2246          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
2247             nc_stat = NF90_INQ_VARID( id_set_3d(av), TRIM( do3d(av,i) ), &
2248                                       id_var_do3d(av,i) )
2249             CALL netcdf_handle_error( 'netcdf_define_header', 95 )
2250#if defined( __netcdf4_parallel )
2251!
2252!--          Set collective io operations for parallel io
2253             IF ( netcdf_data_format > 4 )  THEN
2254                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
2255                                               id_var_do3d(av,i), &
2256                                               NF90_COLLECTIVE )
2257                CALL netcdf_handle_error( 'netcdf_define_header', 453 )
2258             ENDIF
2259#endif
2260             i = i + 1
2261          ENDDO
2262
2263!
2264!--       Update the title attribute on file
2265!--       In order to avoid 'data mode' errors if updated attributes are larger
2266!--       than their original size, NF90_PUT_ATT is called in 'define mode'
2267!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
2268!--       performance loss due to data copying; an alternative strategy would be
2269!--       to ensure equal attribute size. Maybe revise later.
2270          IF ( av == 0 )  THEN
2271             time_average_text = ' '
2272          ELSE
2273             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
2274                                                            averaging_interval
2275          ENDIF
2276          nc_stat = NF90_REDEF( id_set_3d(av) )
2277          CALL netcdf_handle_error( 'netcdf_define_header', 429 )
2278          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title', &
2279                                  TRIM( run_description_header ) //    &
2280                                  TRIM( time_average_text ) )
2281          CALL netcdf_handle_error( 'netcdf_define_header', 96 )
2282          nc_stat = NF90_ENDDEF( id_set_3d(av) )
2283          CALL netcdf_handle_error( 'netcdf_define_header', 430 )
2284          message_string = 'netCDF file for volume data ' //             &
2285                           TRIM( var ) // ' from previous run found.' // &
2286                           '&This file will be extended.'
2287          CALL message( 'define_netcdf_header', 'PA0248', 0, 0, 0, 6, 0 )
2288
2289
2290       CASE ( 'ag_new' )
2291
2292!
2293!--       Define some global attributes of the dataset
2294          nc_stat = NF90_PUT_ATT( id_set_agt, NF90_GLOBAL, 'title', &
2295                                  TRIM( run_description_header ) )
2296          CALL netcdf_handle_error( 'netcdf_define_header', 330 )
2297!
2298!--       Switch for unlimited time dimension
2299          IF ( agent_time_unlimited ) THEN
2300             CALL netcdf_create_dim( id_set_agt, 'time', NF90_UNLIMITED,       &
2301                                     id_dim_time_agt, 331 )
2302          ELSE
2303             CALL netcdf_create_dim( id_set_agt, 'time',                       &
2304                                     INT( ( MIN( multi_agent_system_end,       &
2305                                                 end_time ) -                  &
2306                                            multi_agent_system_start ) /       &
2307                                            dt_write_agent_data * 1.1 ),       &
2308                                     id_dim_time_agt, 331 )
2309          ENDIF
2310
2311          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /), 'time',   &
2312                                  NF90_REAL4, id_var_time_agt, 'seconds', 'time',  &
2313                                  332, 333, 000 )
2314          CALL netcdf_create_att( id_set_agt, id_var_time_agt, 'standard_name', 'time', 000)
2315          CALL netcdf_create_att( id_set_agt, id_var_time_agt, 'axis', 'T', 000)
2316
2317          CALL netcdf_create_dim( id_set_agt, 'agent_number',                  &
2318                                  dim_size_agtnum, id_dim_agtnum, 334 )
2319
2320          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum /),             &
2321                                  'agent_number', NF90_REAL4,                  &
2322                                  id_var_agtnum, 'agent number', '', 335,      &
2323                                  336, 000 )
2324!
2325!--       Define variable which contains the real number of agents in use
2326          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /),           &
2327                                  'real_num_of_agt', NF90_REAL4,               &
2328                                  id_var_rnoa_agt, 'agent number', '', 337,    &
2329                                  338, 000 )
2330          i = 1
2331          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,                &
2332                                  id_dim_time_agt /), agt_var_names(i),        &
2333                                  NF90_DOUBLE, id_var_agt(i),                  &
2334                                  TRIM( agt_var_units(i) ),                    &
2335                                  TRIM( agt_var_names(i) ), 339, 340, 341 )
2336!
2337!--       Define the variables
2338          DO  i = 2, 6
2339             CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,             &
2340                                     id_dim_time_agt /), agt_var_names(i),     &
2341                                     NF90_REAL4, id_var_agt(i),                &
2342                                     TRIM( agt_var_units(i) ),                 &
2343                                     TRIM( agt_var_names(i) ), 339, 340, 341 )
2344
2345          ENDDO
2346!
2347!--       Define vars for biometeorology
2348          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,                &
2349                                  id_dim_time_agt /), agt_var_names(9),        &
2350                                  nc_precision(8), id_var_agt(9),              &
2351                                  TRIM( agt_var_units(9) ),                    &
2352                                  TRIM( agt_var_names(9) ), 339, 340, 341 )
2353
2354!
2355!--       Leave netCDF define mode
2356          nc_stat = NF90_ENDDEF( id_set_agt )
2357          CALL netcdf_handle_error( 'netcdf_define_header', 342 )
2358
2359
2360!        CASE ( 'ag_ext' )
2361! !+?agent extend output for restart runs has to be adapted
2362!
2363! !
2364! !--       Get the id of the time coordinate (unlimited coordinate) and its
2365! !--       last index on the file. The next time level is prt..count+1.
2366! !--       The current time must be larger than the last output time
2367! !--       on the file.
2368!           nc_stat = NF90_INQ_VARID( id_set_agt, 'time', id_var_time_agt )
2369!           CALL netcdf_handle_error( 'netcdf_define_header', 343 )
2370!
2371!           nc_stat = NF90_INQUIRE_VARIABLE( id_set_agt, id_var_time_agt, &
2372!                                            dimids = id_dim_time_old )
2373!           CALL netcdf_handle_error( 'netcdf_define_header', 344 )
2374!           id_dim_time_agt = id_dim_time_old(1)
2375!
2376!           nc_stat = NF90_INQUIRE_DIMENSION( id_set_agt, id_dim_time_agt, &
2377!                                             len = agt_time_count )
2378!           CALL netcdf_handle_error( 'netcdf_define_header', 345 )
2379!
2380!           nc_stat = NF90_GET_VAR( id_set_agt, id_var_time_agt,  &
2381!                                   last_time_coordinate,         &
2382!                                   start = (/ agt_time_count /), &
2383!                                   count = (/ 1 /) )
2384!           CALL netcdf_handle_error( 'netcdf_define_header', 346 )
2385!
2386!           IF ( last_time_coordinate(1) >= simulated_time )  THEN
2387!              message_string = 'netCDF file for agents ' //                  &
2388!                               'from previous run found,' //                 &
2389!                               '&but this file cannot be extended becaus' // &
2390!                               'e the current output time' //                &
2391!                               '&is less or equal than the last output t' // &
2392!                               'ime on this file.' //                        &
2393!                               '&New file is created instead.'
2394!              CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
2395!              agt_time_count = 0
2396!              extend = .FALSE.
2397!              RETURN
2398!           ENDIF
2399!
2400! !
2401! !--       Dataset seems to be extendable.
2402! !--       Now get the variable ids.
2403!           nc_stat = NF90_INQ_VARID( id_set_agt, 'real_num_of_agt', &
2404!                                     id_var_rnoa_agt )
2405!           CALL netcdf_handle_error( 'netcdf_define_header', 347 )
2406!
2407!           DO  i = 1, 17
2408!
2409!              nc_stat = NF90_INQ_VARID( id_set_agt, agt_var_names(i), &
2410!                                        id_var_prt(i) )
2411!              CALL netcdf_handle_error( 'netcdf_define_header', 348 )
2412!
2413!           ENDDO
2414!
2415!           message_string = 'netCDF file for particles ' // &
2416!                            'from previous run found.' //   &
2417!                            '&This file will be extended.'
2418!           CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
2419
2420
2421       CASE ( 'xy_new' )
2422
2423!
2424!--       Define some global attributes of the dataset
2425          IF ( av == 0 )  THEN
2426             CALL netcdf_create_global_atts( id_set_xy(av), 'xy', TRIM( run_description_header ), 97 )
2427             time_average_text = ' '
2428          ELSE
2429             CALL netcdf_create_global_atts( id_set_xy(av), 'xy_av', TRIM( run_description_header ), 97 )
2430             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
2431             nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'time_avg',   &
2432                                     TRIM( time_average_text ) )
2433             CALL netcdf_handle_error( 'netcdf_define_header', 98 )
2434          ENDIF
2435
2436!
2437!--       Define time coordinate for xy sections.
2438!--       For parallel output the time dimensions has to be limited, otherwise
2439!--       the performance drops significantly.
2440          IF ( netcdf_data_format < 5 )  THEN
2441             CALL netcdf_create_dim( id_set_xy(av), 'time', NF90_UNLIMITED,    &
2442                                     id_dim_time_xy(av), 99 )
2443          ELSE
2444             CALL netcdf_create_dim( id_set_xy(av), 'time', ntdim_2d_xy(av),   &
2445                                     id_dim_time_xy(av), 524 )
2446          ENDIF
2447
2448          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_time_xy(av) /),     &
2449                                  'time', NF90_DOUBLE, id_var_time_xy(av),     &
2450                                  'seconds', 'time', 100, 101, 000 )
2451          CALL netcdf_create_att( id_set_xy(av), id_var_time_xy(av), 'standard_name', 'time', 000)
2452          CALL netcdf_create_att( id_set_xy(av), id_var_time_xy(av), 'axis', 'T', 000)
2453!
2454!--       Define the spatial dimensions and coordinates for xy-sections.
2455!--       First, determine the number of horizontal sections to be written.
2456          IF ( section(1,1) == -9999 )  THEN
2457             RETURN
2458          ELSE
2459             ns = 1
2460             DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
2461                ns = ns + 1
2462             ENDDO
2463             ns = ns - 1
2464          ENDIF
2465
2466!
2467!--       Define vertical coordinate grid (zu grid)
2468          CALL netcdf_create_dim( id_set_xy(av), 'zu_xy', ns,                  &
2469                                  id_dim_zu_xy(av), 102 )
2470          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /),       &
2471                                  'zu_xy', NF90_DOUBLE, id_var_zu_xy(av),      &
2472                                  'meters', '', 103, 104, 000 )
2473!
2474!--       Define vertical coordinate grid (zw grid)
2475          CALL netcdf_create_dim( id_set_xy(av), 'zw_xy', ns,                  &
2476                                  id_dim_zw_xy(av), 105 )
2477          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zw_xy(av) /),       &
2478                                  'zw_xy', NF90_DOUBLE, id_var_zw_xy(av),      &
2479                                  'meters', '', 106, 107, 000 )
2480
2481          IF ( land_surface )  THEN
2482
2483             ns_do = 1
2484             DO WHILE ( section(ns_do,1) /= -9999  .AND.  ns_do < nzs )
2485                ns_do = ns_do + 1
2486             ENDDO
2487!
2488!--          Define vertical coordinate grid (zs grid)
2489             CALL netcdf_create_dim( id_set_xy(av), 'zs_xy', ns_do,            &
2490                                     id_dim_zs_xy(av), 539 )
2491             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zs_xy(av) /),    &
2492                                     'zs_xy', NF90_DOUBLE, id_var_zs_xy(av),   &
2493                                     'meters', '', 540, 541, 000 )
2494
2495          ENDIF
2496
2497!
2498!--       Define a pseudo vertical coordinate grid for the surface variables
2499!--       u* and t* to store their height level
2500          CALL netcdf_create_dim( id_set_xy(av), 'zu1_xy', 1,                  &
2501                                  id_dim_zu1_xy(av), 108 )
2502          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu1_xy(av) /),      &
2503                                  'zu1_xy', NF90_DOUBLE, id_var_zu1_xy(av),    &
2504                                  'meters', '', 109, 110, 000 )
2505!
2506!--       Define a variable to store the layer indices of the horizontal cross
2507!--       sections, too
2508          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_zu_xy(av) /),       &
2509                                  'ind_z_xy', NF90_DOUBLE,                     &
2510                                  id_var_ind_z_xy(av), 'gridpoints', '', 111,  &
2511                                  112, 000 )
2512!
2513!--       Define x-axis (for scalar position)
2514          CALL netcdf_create_dim( id_set_xy(av), 'x', nx+1, id_dim_x_xy(av),   &
2515                                  113 )
2516          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av) /), 'x',   &
2517                                  NF90_DOUBLE, id_var_x_xy(av), 'meters', '',  &
2518                                  114, 115, 000 )
2519!
2520!--       Define x-axis (for u position)
2521          CALL netcdf_create_dim( id_set_xy(av), 'xu', nx+1,                   &
2522                                  id_dim_xu_xy(av), 388 )
2523          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_xu_xy(av) /), 'xu', &
2524                                  NF90_DOUBLE, id_var_xu_xy(av), 'meters', '', &
2525                                  389, 390, 000 )
2526!
2527!--       Define y-axis (for scalar position)
2528          CALL netcdf_create_dim( id_set_xy(av), 'y', ny+1, id_dim_y_xy(av),   &
2529                                  116 )
2530          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_y_xy(av) /), 'y',   &
2531                                  NF90_DOUBLE, id_var_y_xy(av), 'meters', '',  &
2532                                  117, 118, 000 )
2533!
2534!--       Define y-axis (for scalar position)
2535          CALL netcdf_create_dim( id_set_xy(av), 'yv', ny+1,                   &
2536                                  id_dim_yv_xy(av), 364 )
2537          CALL netcdf_create_var( id_set_xy(av), (/ id_dim_yv_xy(av) /), 'yv', &
2538                                  NF90_DOUBLE, id_var_yv_xy(av), 'meters', '', &
2539                                  365, 366, 000 )
2540!
2541!--       Define UTM and geographic coordinates
2542          CALL define_geo_coordinates( id_set_xy(av),         &
2543                  (/ id_dim_x_xy(av), id_dim_xu_xy(av) /),    &
2544                  (/ id_dim_y_xy(av), id_dim_yv_xy(av) /),    &
2545                  id_var_eutm_xy(:,av), id_var_nutm_xy(:,av), &
2546                  id_var_lat_xy(:,av), id_var_lon_xy(:,av)    )
2547!
2548!--       Define coordinate-reference system
2549          CALL netcdf_create_crs( id_set_xy(av), 000 )
2550!
2551!--       In case of non-flat topography define 2d-arrays containing the height
2552!--       information. Only for parallel netcdf output.
2553          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
2554               netcdf_data_format > 4  )  THEN
2555!
2556!--          Define zusi = zu(nzb_s_inner)
2557             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),        &
2558                                     id_dim_y_xy(av) /), 'zusi', NF90_DOUBLE,  &
2559                                     id_var_zusi_xy(av), 'meters',             &
2560                                     'zu(nzb_s_inner)', 421, 422, 423 )
2561!
2562!--          Define zwwi = zw(nzb_w_inner)
2563             CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),        &
2564                                     id_dim_y_xy(av) /), 'zwwi', NF90_DOUBLE,  &
2565                                     id_var_zwwi_xy(av), 'meters',             &
2566                                     'zw(nzb_w_inner)', 424, 425, 426 )
2567
2568          ENDIF
2569
2570!
2571!--       Define the variables
2572          var_list = ';'
2573          i = 1
2574
2575          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2576
2577             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
2578!
2579!--             If there is a star in the variable name (u* or t*), it is a
2580!--             surface variable. Define it with id_dim_zu1_xy.
2581                IF ( INDEX( do2d(av,i), '*' ) /= 0 )  THEN
2582
2583                   CALL netcdf_create_var( id_set_xy(av), (/ id_dim_x_xy(av),  &
2584                                           id_dim_y_xy(av), id_dim_zu1_xy(av), &
2585                                           id_dim_time_xy(av) /), do2d(av,i),  &
2586                                           nc_precision(1), id_var_do2d(av,i), &
2587                                           TRIM( do2d_unit(av,i) ),            &
2588                                           do2d(av,i), 119, 120, 354, .TRUE. )
2589
2590                ELSE
2591
2592!
2593!--                Check for the grid
2594                   found = .FALSE.
2595                   SELECT CASE ( do2d(av,i) )
2596!
2597!--                   Most variables are defined on the zu grid
2598                      CASE ( 'e_xy', 'nc_xy', 'nr_xy', 'p_xy',                 &
2599                             'pc_xy', 'pr_xy', 'prr_xy', 'q_xy',               &
2600                             'qc_xy', 'ql_xy', 'ql_c_xy', 'ql_v_xy',           &
2601                             'ql_vp_xy', 'qr_xy', 'qv_xy',                     &
2602                             's_xy',                                           &
2603                             'theta_xy', 'thetal_xy', 'thetav_xy' )
2604
2605                         grid_x = 'x'
2606                         grid_y = 'y'
2607                         grid_z = 'zu'
2608!
2609!--                   u grid
2610                      CASE ( 'u_xy' )
2611
2612                         grid_x = 'xu'
2613                         grid_y = 'y'
2614                         grid_z = 'zu'
2615!
2616!--                   v grid
2617                      CASE ( 'v_xy' )
2618
2619                         grid_x = 'x'
2620                         grid_y = 'yv'
2621                         grid_z = 'zu'
2622!
2623!--                   w grid
2624                      CASE ( 'w_xy' )
2625
2626                         grid_x = 'x'
2627                         grid_y = 'y'
2628                         grid_z = 'zw'
2629
2630
2631                      CASE DEFAULT
2632!
2633!--                      Check for land surface quantities
2634                         IF ( land_surface )  THEN
2635                            CALL lsm_define_netcdf_grid( do2d(av,i), found,    &
2636                                                   grid_x, grid_y, grid_z )
2637                         ENDIF
2638
2639                         IF ( .NOT. found )  THEN
2640                            CALL tcm_define_netcdf_grid( do2d(av,i), found,    &
2641                                                         grid_x, grid_y,       &
2642                                                         grid_z )
2643                         ENDIF
2644
2645!
2646!--                      Check for ocean quantities
2647                         IF ( .NOT. found  .AND.  ocean_mode )  THEN
2648                            CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
2649                                                           grid_x, grid_y,     &
2650                                                           grid_z )
2651                         ENDIF
2652!
2653!--                      Check for radiation quantities
2654                         IF ( .NOT. found  .AND.  radiation )  THEN
2655                            CALL radiation_define_netcdf_grid( do2d(av,i),     &
2656                                                         found, grid_x, grid_y,&
2657                                                         grid_z )
2658                         ENDIF
2659
2660!
2661!--                      Check for SALSA quantities
2662                         IF ( .NOT. found  .AND.  salsa )  THEN
2663                            CALL salsa_define_netcdf_grid( do2d(av,i), found,  &
2664                                                           grid_x, grid_y,     &
2665                                                           grid_z )
2666                         ENDIF
2667
2668!
2669!--                      Check for gust module quantities
2670                         IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
2671                            CALL gust_define_netcdf_grid( do2d(av,i), found,   &
2672                                                          grid_x, grid_y,      &
2673                                                          grid_z )
2674                         ENDIF
2675!
2676!--                      Check for biometeorology quantities
2677                         IF ( .NOT. found  .AND.  biometeorology )  THEN
2678                            CALL bio_define_netcdf_grid( do2d( av, i), found,  &
2679                                                         grid_x, grid_y,       &
2680                                                         grid_z )
2681                         ENDIF
2682!
2683!--                      Check for chemistry quantities
2684                         IF ( .NOT. found  .AND.  air_chemistry )  THEN
2685                            CALL chem_define_netcdf_grid( do2d(av,i), found,   &
2686                                                          grid_x, grid_y,      &
2687                                                          grid_z )
2688                         ENDIF
2689
2690                         IF ( .NOT. found )                                    &
2691                            CALL doq_define_netcdf_grid(                       &
2692                                                    do2d(av,i), found, grid_x, &
2693                                                    grid_y, grid_z              )
2694!
2695!--                      Check for user-defined quantities
2696                         IF ( .NOT. found  .AND.  user_module_enabled )  THEN
2697                            CALL user_define_netcdf_grid( do2d(av,i), found,   &
2698                                                          grid_x, grid_y,      &
2699                                                          grid_z )
2700                         ENDIF
2701
2702                         IF ( .NOT. found )  THEN
2703                            WRITE ( message_string, * ) 'no grid defined for', &
2704                                                ' variable ', TRIM( do2d(av,i) )
2705                            CALL message( 'define_netcdf_header', 'PA0244',    &
2706                                          0, 1, 0, 6, 0 )
2707                         ENDIF
2708
2709                   END SELECT
2710
2711!
2712!--                Select the respective dimension ids
2713                   IF ( grid_x == 'x' )  THEN
2714                      id_x = id_dim_x_xy(av)
2715                   ELSEIF ( grid_x == 'xu' )  THEN
2716                      id_x = id_dim_xu_xy(av)
2717                   ENDIF
2718
2719                   IF ( grid_y == 'y' )  THEN
2720                      id_y = id_dim_y_xy(av)
2721                   ELSEIF ( grid_y == 'yv' )  THEN
2722                      id_y = id_dim_yv_xy(av)
2723                   ENDIF
2724
2725                   IF ( grid_z == 'zu' )  THEN
2726                      id_z = id_dim_zu_xy(av)
2727                   ELSEIF ( grid_z == 'zw' )  THEN
2728                      id_z = id_dim_zw_xy(av)
2729                   ELSEIF ( grid_z == 'zs' )  THEN
2730                      id_z = id_dim_zs_xy(av)
2731                   ELSEIF ( grid_z == 'zu1' )  THEN
2732                      id_z = id_dim_zu1_xy(av)
2733                   ENDIF
2734
2735!
2736!--                Define the grid
2737                   CALL netcdf_create_var( id_set_xy(av), (/ id_x, id_y, id_z, &
2738                                           id_dim_time_xy(av) /), do2d(av,i),  &
2739                                           nc_precision(1), id_var_do2d(av,i), &
2740                                           TRIM( do2d_unit(av,i) ),            &
2741                                           do2d(av,i), 119, 120, 354, .TRUE. )
2742
2743                ENDIF
2744
2745#if defined( __netcdf4_parallel )
2746                IF ( netcdf_data_format > 4 )  THEN
2747!
2748!--                Set no fill for every variable to increase performance.
2749                   nc_stat = NF90_DEF_VAR_FILL( id_set_xy(av),     &
2750                                                id_var_do2d(av,i), &
2751                                                NF90_NOFILL, 0 )
2752                   CALL netcdf_handle_error( 'netcdf_define_header', 533 )
2753!
2754!--                Set collective io operations for parallel io
2755                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
2756                                                  id_var_do2d(av,i), &
2757                                                  NF90_COLLECTIVE )
2758                   CALL netcdf_handle_error( 'netcdf_define_header', 448 )
2759                ENDIF
2760#endif
2761                var_list = TRIM( var_list) // TRIM( do2d(av,i) ) // ';'
2762
2763             ENDIF
2764
2765             i = i + 1
2766
2767          ENDDO
2768
2769!
2770!--       No arrays to output. Close the netcdf file and return.
2771          IF ( i == 1 )  RETURN
2772
2773!
2774!--       Write the list of variables as global attribute (this is used by
2775!--       restart runs and by combine_plot_fields)
2776          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
2777                                  var_list )
2778          CALL netcdf_handle_error( 'netcdf_define_header', 121 )
2779
2780!
2781!--       Set general no fill, otherwise the performance drops significantly for
2782!--       parallel output.
2783          nc_stat = NF90_SET_FILL( id_set_xy(av), NF90_NOFILL, oldmode )
2784          CALL netcdf_handle_error( 'netcdf_define_header', 529 )
2785
2786!
2787!--       Leave netCDF define mode
2788          nc_stat = NF90_ENDDEF( id_set_xy(av) )
2789          CALL netcdf_handle_error( 'netcdf_define_header', 122 )
2790
2791!
2792!--       These data are only written by PE0 for parallel output to increase
2793!--       the performance.
2794          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
2795
2796!
2797!--          Write axis data: z_xy, x, y
2798             ALLOCATE( netcdf_data(1:ns) )
2799
2800!
2801!--          Write zu data
2802             DO  i = 1, ns
2803                IF( section(i,1) == -1 )  THEN
2804                   netcdf_data(i) = -1.0_wp  ! section averaged along z
2805                ELSE
2806                   netcdf_data(i) = zu( section(i,1) )
2807                ENDIF
2808             ENDDO
2809             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu_xy(av), &
2810                                     netcdf_data, start = (/ 1 /),    &
2811                                     count = (/ ns /) )
2812             CALL netcdf_handle_error( 'netcdf_define_header', 123 )
2813
2814!
2815!--          Write zw data
2816             DO  i = 1, ns
2817                IF( section(i,1) == -1 )  THEN
2818                   netcdf_data(i) = -1.0_wp  ! section averaged along z
2819                ELSE
2820                   netcdf_data(i) = zw( section(i,1) )
2821                ENDIF
2822             ENDDO
2823             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zw_xy(av), &
2824                                     netcdf_data, start = (/ 1 /),    &
2825                                     count = (/ ns /) )
2826             CALL netcdf_handle_error( 'netcdf_define_header', 124 )
2827
2828!
2829!--          Write zs data
2830             IF ( land_surface )  THEN
2831                ns_do = 0
2832                DO  i = 1, ns
2833                   IF( section(i,1) == -1 )  THEN
2834                      netcdf_data(i) = 1.0_wp  ! section averaged along z
2835                      ns_do = ns_do + 1
2836                   ELSEIF ( section(i,1) < nzs )  THEN
2837                      netcdf_data(i) = - zs( section(i,1) )
2838                      ns_do = ns_do + 1
2839                   ENDIF
2840                ENDDO
2841
2842                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zs_xy(av), &
2843                                        netcdf_data(1:ns_do), start = (/ 1 /),    &
2844                                        count = (/ ns_do /) )
2845                CALL netcdf_handle_error( 'netcdf_define_header', 124 )
2846
2847             ENDIF
2848
2849!
2850!--          Write gridpoint number data
2851             netcdf_data(1:ns) = section(1:ns,1)
2852             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_ind_z_xy(av), &
2853                                     netcdf_data, start = (/ 1 /),       &
2854                                     count = (/ ns /) )
2855             CALL netcdf_handle_error( 'netcdf_define_header', 125 )
2856
2857             DEALLOCATE( netcdf_data )
2858
2859!
2860!--          Write the cross section height u*, t*
2861             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu1_xy(av), &
2862                                     (/ zu(nzb+1) /), start = (/ 1 /), &
2863                                     count = (/ 1 /) )
2864             CALL netcdf_handle_error( 'netcdf_define_header', 126 )
2865
2866!
2867!--          Write data for x (shifted by +dx/2) and xu axis
2868             ALLOCATE( netcdf_data(0:nx) )
2869
2870             DO  i = 0, nx
2871                netcdf_data(i) = ( i + 0.5_wp ) * dx
2872             ENDDO
2873
2874             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av), &
2875                                     netcdf_data, start = (/ 1 /),   &
2876                                     count = (/ nx+1 /) )
2877             CALL netcdf_handle_error( 'netcdf_define_header', 127 )
2878
2879             DO  i = 0, nx
2880                netcdf_data(i) = i * dx
2881             ENDDO
2882
2883             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_xu_xy(av), &
2884                                     netcdf_data, start = (/ 1 /),    &
2885                                     count = (/ nx+1 /) )
2886             CALL netcdf_handle_error( 'netcdf_define_header', 367 )
2887
2888             DEALLOCATE( netcdf_data )
2889
2890!
2891!--          Write data for y (shifted by +dy/2) and yv axis
2892             ALLOCATE( netcdf_data(0:ny+1) )
2893
2894             DO  i = 0, ny
2895                netcdf_data(i) = ( i + 0.5_wp ) * dy
2896             ENDDO
2897
2898             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av), &
2899                                     netcdf_data, start = (/ 1 /),   &
2900                                     count = (/ ny+1 /))
2901             CALL netcdf_handle_error( 'netcdf_define_header', 128 )
2902
2903             DO  i = 0, ny
2904                netcdf_data(i) = i * dy
2905             ENDDO
2906
2907             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_yv_xy(av), &
2908                                     netcdf_data, start = (/ 1 /),    &
2909                                     count = (/ ny+1 /))
2910             CALL netcdf_handle_error( 'netcdf_define_header', 368 )
2911
2912             DEALLOCATE( netcdf_data )
2913!
2914!--          Write UTM coordinates
2915             IF ( init_model%rotation_angle == 0.0_wp )  THEN
2916!
2917!--             1D in case of no rotation
2918                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
2919!
2920!--             x coordinates
2921                ALLOCATE( netcdf_data(0:nx) )
2922                DO  k = 0, 2
2923!
2924!--                Scalar grid points
2925                   IF ( k == 0 )  THEN
2926                      shift_x = 0.5
2927!
2928!--                u grid points
2929                   ELSEIF ( k == 1 )  THEN
2930                      shift_x = 0.0
2931!
2932!--                v grid points
2933                   ELSEIF ( k == 2 )  THEN
2934                      shift_x = 0.5
2935                   ENDIF
2936
2937                   DO  i = 0, nx
2938                     netcdf_data(i) = init_model%origin_x            &
2939                                    + cos_ra * ( i + shift_x ) * dx
2940                   ENDDO
2941
2942                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),&
2943                                           netcdf_data, start = (/ 1 /),   &
2944                                           count = (/ nx+1 /) )
2945                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
2946
2947                ENDDO
2948                DEALLOCATE( netcdf_data )
2949!
2950!--             y coordinates
2951                ALLOCATE( netcdf_data(0:ny) )
2952                DO  k = 0, 2
2953!
2954!--                Scalar grid points
2955                   IF ( k == 0 )  THEN
2956                      shift_y = 0.5
2957!
2958!--                u grid points
2959                   ELSEIF ( k == 1 )  THEN
2960                      shift_y = 0.5
2961!
2962!--                v grid points
2963                   ELSEIF ( k == 2 )  THEN
2964                      shift_y = 0.0
2965                   ENDIF
2966
2967                   DO  j = 0, ny
2968                      netcdf_data(j) = init_model%origin_y            &
2969                                     + cos_ra * ( j + shift_y ) * dy
2970                   ENDDO
2971
2972                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),&
2973                                           netcdf_data, start = (/ 1 /),   &
2974                                           count = (/ ny+1 /) )
2975                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
2976
2977                ENDDO
2978                DEALLOCATE( netcdf_data )
2979
2980             ELSE
2981!
2982!--             2D in case of rotation
2983                ALLOCATE( netcdf_data_2d(0:nx,0:ny) )
2984                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
2985                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
2986
2987                DO  k = 0, 2
2988!
2989!--               Scalar grid points
2990                  IF ( k == 0 )  THEN
2991                     shift_x = 0.5 ; shift_y = 0.5
2992!
2993!--               u grid points
2994                  ELSEIF ( k == 1 )  THEN
2995                     shift_x = 0.0 ; shift_y = 0.5
2996!
2997!--               v grid points
2998                  ELSEIF ( k == 2 )  THEN
2999                     shift_x = 0.5 ; shift_y = 0.0
3000                  ENDIF
3001
3002                  DO  j = 0, ny
3003                     DO  i = 0, nx
3004                        netcdf_data_2d(i,j) = init_model%origin_x            &
3005                                            + cos_ra * ( i + shift_x ) * dx  &
3006                                            + sin_ra * ( j + shift_y ) * dy
3007                     ENDDO
3008                  ENDDO
3009
3010                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),  &
3011                                          netcdf_data_2d, start = (/ 1, 1 /),   &
3012                                          count = (/ nx+1, ny+1 /) )
3013                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
3014
3015                  DO  j = 0, ny
3016                     DO  i = 0, nx
3017                        netcdf_data_2d(i,j) = init_model%origin_y            &
3018                                            - sin_ra * ( i + shift_x ) * dx  &
3019                                            + cos_ra * ( j + shift_y ) * dy
3020                     ENDDO
3021                  ENDDO
3022
3023                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),  &
3024                                          netcdf_data_2d, start = (/ 1, 1 /),   &
3025                                          count = (/ nx+1, ny+1 /) )
3026                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3027
3028                ENDDO
3029                DEALLOCATE( netcdf_data_2d )
3030             ENDIF
3031
3032          ENDIF
3033!
3034!--       Write lon and lat data. Only for parallel output.
3035          IF ( netcdf_data_format > 4 )  THEN
3036
3037             ALLOCATE( lat(nxl:nxr,nys:nyn) )
3038             ALLOCATE( lon(nxl:nxr,nys:nyn) )
3039             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
3040             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
3041
3042             DO  k = 0, 2
3043!
3044!--             Scalar grid points
3045                IF ( k == 0 )  THEN
3046                   shift_x = 0.5 ; shift_y = 0.5
3047!
3048!--             u grid points
3049                ELSEIF ( k == 1 )  THEN
3050                   shift_x = 0.0 ; shift_y = 0.5
3051!
3052!--             v grid points
3053                ELSEIF ( k == 2 )  THEN
3054                   shift_x = 0.5 ; shift_y = 0.0
3055                ENDIF
3056
3057                DO  j = nys, nyn
3058                   DO  i = nxl, nxr
3059                      eutm = init_model%origin_x            &
3060                           + cos_ra * ( i + shift_x ) * dx  &
3061                           + sin_ra * ( j + shift_y ) * dy
3062                      nutm = init_model%origin_y            &
3063                           - sin_ra * ( i + shift_x ) * dx  &
3064                           + cos_ra * ( j + shift_y ) * dy
3065
3066                      CALL  convert_utm_to_geographic( crs_list,          &
3067                                                       eutm, nutm,        &
3068                                                       lon(i,j), lat(i,j) )
3069                   ENDDO
3070                ENDDO
3071
3072                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lon_xy(k,av), &
3073                                     lon, start = (/ nxl+1, nys+1 /),       &
3074                                     count = (/ nxr-nxl+1, nyn-nys+1 /) )
3075                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3076
3077                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_lat_xy(k,av), &
3078                                     lat, start = (/ nxl+1, nys+1 /),       &
3079                                     count = (/ nxr-nxl+1, nyn-nys+1 /) )
3080                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3081             ENDDO
3082
3083             DEALLOCATE( lat )
3084             DEALLOCATE( lon )
3085
3086          ENDIF
3087!
3088!--       In case of non-flat topography write height information. Only for
3089!--       parallel netcdf output.
3090          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
3091               netcdf_data_format > 4  )  THEN
3092
3093!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
3094!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
3095!                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
3096!                                        start = (/ nxl+1, nys+1 /),            &
3097!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
3098!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
3099!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
3100!                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
3101!                                        start = (/ nxl+1, nys+1 /),            &
3102!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
3103!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
3104!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
3105!                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
3106!                                        start = (/ nxl+1, nys+1 /),            &
3107!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
3108!             ELSE
3109                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
3110                                        zu_s_inner(nxl:nxr,nys:nyn),           &
3111                                        start = (/ nxl+1, nys+1 /),            &
3112                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
3113!             ENDIF
3114             CALL netcdf_handle_error( 'netcdf_define_header', 427 )
3115
3116!             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
3117!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
3118!                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
3119!                                        start = (/ nxl+1, nys+1 /),            &
3120!                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
3121!             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
3122!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
3123!                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
3124!                                        start = (/ nxl+1, nys+1 /),            &
3125!                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
3126!             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
3127!                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
3128!                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
3129!                                        start = (/ nxl+1, nys+1 /),            &
3130!                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
3131!             ELSE
3132                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
3133                                        zw_w_inner(nxl:nxr,nys:nyn),           &
3134                                        start = (/ nxl+1, nys+1 /),            &
3135                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
3136!             ENDIF
3137             CALL netcdf_handle_error( 'netcdf_define_header', 428 )
3138
3139          ENDIF
3140
3141       CASE ( 'xy_ext' )
3142
3143!
3144!--       Get the list of variables and compare with the actual run.
3145!--       First var_list_old has to be reset, since GET_ATT does not assign
3146!--       trailing blanks.
3147          var_list_old = ' '
3148          nc_stat = NF90_GET_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
3149                                  var_list_old )
3150          CALL netcdf_handle_error( 'netcdf_define_header', 129 )
3151
3152          var_list = ';'
3153          i = 1
3154          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
3155             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
3156                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
3157             ENDIF
3158             i = i + 1
3159          ENDDO
3160
3161          IF ( av == 0 )  THEN
3162             var = '(xy)'
3163          ELSE
3164             var = '(xy_av)'
3165          ENDIF
3166
3167          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
3168             message_string = 'netCDF file for cross-sections ' //           &
3169                              TRIM( var ) // ' from previous run found,' //  &
3170                              '&but this file cannot be extended due to' //  &
3171                              ' variable mismatch.' //                       &
3172                              '&New file is created instead.'
3173             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
3174             extend = .FALSE.
3175             RETURN
3176          ENDIF
3177
3178!
3179!--       Calculate the number of current sections
3180          ns = 1
3181          DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
3182             ns = ns + 1
3183          ENDDO
3184          ns = ns - 1
3185
3186!
3187!--       Get and compare the number of horizontal cross sections
3188          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'zu_xy', id_var_zu_xy(av) )
3189          CALL netcdf_handle_error( 'netcdf_define_header', 130 )
3190
3191          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_zu_xy(av), &
3192                                           dimids = id_dim_zu_xy_old )
3193          CALL netcdf_handle_error( 'netcdf_define_header', 131 )
3194          id_dim_zu_xy(av) = id_dim_zu_xy_old(1)
3195
3196          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_zu_xy(av), &
3197                                            len = ns_old )
3198          CALL netcdf_handle_error( 'netcdf_define_header', 132 )
3199
3200          IF ( ns /= ns_old )  THEN
3201             message_string = 'netCDF file for cross-sections ' //          &
3202                              TRIM( var ) // ' from previous run found,' // &
3203                              '&but this file cannot be extended due to' // &
3204                              ' mismatch in number of' //                   &
3205                              ' cross sections.' //                         &
3206                              '&New file is created instead.'
3207             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
3208             extend = .FALSE.
3209             RETURN
3210          ENDIF
3211
3212!
3213!--       Get and compare the heights of the cross sections
3214          ALLOCATE( netcdf_data(1:ns_old) )
3215
3216          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_zu_xy(av), netcdf_data )
3217          CALL netcdf_handle_error( 'netcdf_define_header', 133 )
3218
3219          DO  i = 1, ns
3220             IF ( section(i,1) /= -1 )  THEN
3221                IF ( zu(section(i,1)) /= netcdf_data(i) )  THEN
3222                   message_string = 'netCDF file for cross-sections ' //       &
3223                               TRIM( var ) // ' from previous run found,' //   &
3224                               ' but this file cannot be extended' //          &
3225                               ' due to mismatch in cross' //                  &
3226                               ' section levels.' //                           &
3227                               ' New file is created instead.'
3228                   CALL message( 'define_netcdf_header', 'PA0251',             &
3229                                                                 0, 1, 0, 6, 0 )
3230                   extend = .FALSE.
3231                   RETURN
3232                ENDIF
3233             ELSE
3234                IF ( -1.0_wp /= netcdf_data(i) )  THEN
3235                   message_string = 'netCDF file for cross-sections ' //       &
3236                               TRIM( var ) // ' from previous run found,' //   &
3237                               ' but this file cannot be extended' //          &
3238                               ' due to mismatch in cross' //                  &
3239                               ' section levels.' //                           &
3240                               ' New file is created instead.'
3241                   CALL message( 'define_netcdf_header', 'PA0251',             &
3242                                                                 0, 1, 0, 6, 0 )
3243                   extend = .FALSE.
3244                   RETURN
3245                ENDIF
3246             ENDIF
3247          ENDDO
3248
3249          DEALLOCATE( netcdf_data )
3250
3251!
3252!--       Get the id of the time coordinate (unlimited coordinate) and its
3253!--       last index on the file. The next time level is do2d..count+1.
3254!--       The current time must be larger than the last output time
3255!--       on the file.
3256          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'time', id_var_time_xy(av) )
3257          CALL netcdf_handle_error( 'netcdf_define_header', 134 )
3258
3259          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_time_xy(av), &
3260                                           dimids = id_dim_time_old )
3261          CALL netcdf_handle_error( 'netcdf_define_header', 135 )
3262          id_dim_time_xy(av) = id_dim_time_old(1)
3263
3264          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_time_xy(av), &
3265                                            len = ntime_count )
3266          CALL netcdf_handle_error( 'netcdf_define_header', 136 )
3267
3268!
3269!--       For non-parallel output use the last output time level of the netcdf
3270!--       file because the time dimension is unlimited. In case of parallel
3271!--       output the variable ntime_count could get the value of 9*10E36 because
3272!--       the time dimension is limited.
3273          IF ( netcdf_data_format < 5 ) do2d_xy_time_count(av) = ntime_count
3274
3275          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_time_xy(av),           &
3276                                  last_time_coordinate,                        &
3277                                  start = (/ do2d_xy_time_count(av) /),        &
3278                                  count = (/ 1 /) )
3279          CALL netcdf_handle_error( 'netcdf_define_header', 137 )
3280
3281          IF ( last_time_coordinate(1) >= simulated_time )  THEN
3282             message_string = 'netCDF file for cross sections ' //             &
3283                              TRIM( var ) // ' from previous run found,' //    &
3284                              '&but this file cannot be extended becaus' //    &
3285                              'e the current output time' //                   &
3286                              '&is less or equal than the last output t' //    &
3287                              'ime on this file.' //                           &
3288                              '&New file is created instead.'
3289             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
3290             do2d_xy_time_count(av) = 0
3291             extend = .FALSE.
3292             RETURN
3293          ENDIF
3294
3295          IF ( netcdf_data_format > 4 )  THEN
3296!
3297!--          Check if the needed number of output time levels is increased
3298!--          compared to the number of time levels in the existing file.
3299             IF ( ntdim_2d_xy(av) > ntime_count )  THEN
3300                message_string = 'netCDF file for cross sections ' //          &
3301                                 TRIM( var ) // ' from previous run found,' // &
3302                                 '&but this file cannot be extended becaus' // &
3303                                 'e the number of output time levels has b' // &
3304                                 'een increased compared to the previous s' // &
3305                                 'imulation.' //                               &
3306                                 '&New file is created instead.'
3307                CALL message( 'define_netcdf_header', 'PA0389', 0, 1, 0, 6, 0 )
3308                do2d_xy_time_count(av) = 0
3309                extend = .FALSE.
3310!
3311!--             Recalculate the needed time levels for the new file.
3312                IF ( av == 0 )  THEN
3313                   ntdim_2d_xy(0) = CEILING(                            &
3314                           ( end_time - MAX( skip_time_do2d_xy,         &
3315                                             simulated_time_at_begin )  &
3316                           ) / dt_do2d_xy )
3317                   IF ( do2d_at_begin )  ntdim_2d_xy(0) = ntdim_2d_xy(0) + 1
3318                ELSE
3319                   ntdim_2d_xy(1) = CEILING(                            &
3320                           ( end_time - MAX( skip_time_data_output_av,  &
3321                                             simulated_time_at_begin )  &
3322                           ) / dt_data_output_av )
3323                ENDIF
3324                RETURN
3325             ENDIF
3326          ENDIF
3327
3328!
3329!--       Dataset seems to be extendable.
3330!--       Now get the variable ids.
3331          i = 1
3332          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
3333             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
3334                nc_stat = NF90_INQ_VARID( id_set_xy(av), do2d(av,i), &
3335                                          id_var_do2d(av,i) )
3336                CALL netcdf_handle_error( 'netcdf_define_header', 138 )
3337#if defined( __netcdf4_parallel )
3338!
3339!--             Set collective io operations for parallel io
3340                IF ( netcdf_data_format > 4 )  THEN
3341                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
3342                                                  id_var_do2d(av,i), &
3343                                                  NF90_COLLECTIVE )
3344                   CALL netcdf_handle_error( 'netcdf_define_header', 454 )
3345                ENDIF
3346#endif
3347             ENDIF
3348             i = i + 1
3349          ENDDO
3350
3351!
3352!--       Update the title attribute on file
3353!--       In order to avoid 'data mode' errors if updated attributes are larger
3354!--       than their original size, NF90_PUT_ATT is called in 'define mode'
3355!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
3356!--       performance loss due to data copying; an alternative strategy would be
3357!--       to ensure equal attribute size in a job chain. Maybe revise later.
3358          IF ( av == 0 )  THEN
3359             time_average_text = ' '
3360          ELSE
3361             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
3362                                                            averaging_interval
3363          ENDIF
3364          nc_stat = NF90_REDEF( id_set_xy(av) )
3365          CALL netcdf_handle_error( 'netcdf_define_header', 431 )
3366          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title',         &
3367                                  TRIM( run_description_header ) //            &
3368                                  TRIM( time_average_text ) )
3369          CALL netcdf_handle_error( 'netcdf_define_header', 139 )
3370          nc_stat = NF90_ENDDEF( id_set_xy(av) )
3371          CALL netcdf_handle_error( 'netcdf_define_header', 432 )
3372          message_string = 'netCDF file for cross-sections ' //                &
3373                            TRIM( var ) // ' from previous run found.' //      &
3374                           '&This file will be extended.'
3375          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
3376
3377
3378       CASE ( 'xz_new' )
3379
3380!
3381!--       Define some global attributes of the dataset
3382          IF ( av == 0 )  THEN
3383             CALL netcdf_create_global_atts( id_set_xz(av), 'xz', TRIM( run_description_header ), 140 )
3384             time_average_text = ' '
3385          ELSE
3386             CALL netcdf_create_global_atts( id_set_xz(av), 'xz_av', TRIM( run_description_header ), 140 )
3387             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
3388             nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'time_avg',   &
3389                                     TRIM( time_average_text ) )
3390             CALL netcdf_handle_error( 'netcdf_define_header', 141 )
3391          ENDIF
3392
3393!
3394!--       Define time coordinate for xz sections.
3395!--       For parallel output the time dimensions has to be limited, otherwise
3396!--       the performance drops significantly.
3397          IF ( netcdf_data_format < 5 )  THEN
3398             CALL netcdf_create_dim( id_set_xz(av), 'time', NF90_UNLIMITED,    &
3399                                     id_dim_time_xz(av), 142 )
3400          ELSE
3401             CALL netcdf_create_dim( id_set_xz(av), 'time', ntdim_2d_xz(av),   &
3402                                     id_dim_time_xz(av), 525 )
3403          ENDIF
3404
3405          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_time_xz(av) /),     &
3406                                  'time', NF90_DOUBLE, id_var_time_xz(av),     &
3407                                  'seconds', 'time', 143, 144, 000 )
3408          CALL netcdf_create_att( id_set_xz(av), id_var_time_xz(av), 'standard_name', 'time', 000)
3409          CALL netcdf_create_att( id_set_xz(av), id_var_time_xz(av), 'axis', 'T', 000)
3410!
3411!--       Define the spatial dimensions and coordinates for xz-sections.
3412!--       First, determine the number of vertical sections to be written.
3413          IF ( section(1,2) == -9999 )  THEN
3414             RETURN
3415          ELSE
3416             ns = 1
3417             DO WHILE ( section(ns,2) /= -9999  .AND.  ns <= 100 )
3418                ns = ns + 1
3419             ENDDO
3420             ns = ns - 1
3421          ENDIF
3422
3423!
3424!--       Define y-axis (for scalar position)
3425          CALL netcdf_create_dim( id_set_xz(av), 'y_xz', ns, id_dim_y_xz(av),  &
3426                                  145 )
3427          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /),        &
3428                                  'y_xz', NF90_DOUBLE, id_var_y_xz(av),        &
3429                                  'meters', '', 146, 147, 000 )
3430!
3431!--       Define y-axis (for v position)
3432          CALL netcdf_create_dim( id_set_xz(av), 'yv_xz', ns,                  &
3433                                  id_dim_yv_xz(av), 369 )
3434          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_yv_xz(av) /),       &
3435                                  'yv_xz', NF90_DOUBLE, id_var_yv_xz(av),      &
3436                                  'meters', '', 370, 371, 000 )
3437!
3438!--       Define a variable to store the layer indices of the vertical cross
3439!--       sections
3440          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_y_xz(av) /),        &
3441                                  'ind_y_xz', NF90_DOUBLE,                     &
3442                                  id_var_ind_y_xz(av), 'gridpoints', '', 148,  &
3443                                  149, 000 )
3444!
3445!--       Define x-axis (for scalar position)
3446          CALL netcdf_create_dim( id_set_xz(av), 'x', nx+1, id_dim_x_xz(av),   &
3447                                  150 )
3448          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_x_xz(av) /), 'x',   &
3449                                  NF90_DOUBLE, id_var_x_xz(av), 'meters', '',  &
3450                                  151, 152, 000 )
3451!
3452!--       Define x-axis (for u position)
3453          CALL netcdf_create_dim( id_set_xz(av), 'xu', nx+1, id_dim_xu_xz(av), &
3454                                  372 )
3455          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_xu_xz(av) /), 'xu', &
3456                                  NF90_DOUBLE, id_var_xu_xz(av), 'meters', '', &
3457                                  373, 374, 000 )
3458!
3459!--       Define the three z-axes (zu, zw, and zs)
3460          CALL netcdf_create_dim( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av), &
3461                                  153 )
3462          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zu_xz(av) /), 'zu', &
3463                                  NF90_DOUBLE, id_var_zu_xz(av), 'meters', '', &
3464                                  154, 155, 000 )
3465          CALL netcdf_create_dim( id_set_xz(av), 'zw', nz+2, id_dim_zw_xz(av), &
3466                                  156 )
3467          CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zw_xz(av) /), 'zw', &
3468                                  NF90_DOUBLE, id_var_zw_xz(av), 'meters', '', &
3469                                  157, 158, 000 )
3470!
3471!--       Define UTM and geographic coordinates
3472          CALL define_geo_coordinates( id_set_xz(av),         &
3473                  (/ id_dim_x_xz(av), id_dim_xu_xz(av) /),    &
3474                  (/ id_dim_y_xz(av), id_dim_yv_xz(av) /),    &
3475                  id_var_eutm_xz(:,av), id_var_nutm_xz(:,av), &
3476                  id_var_lat_xz(:,av), id_var_lon_xz(:,av)    )
3477!
3478!--       Define coordinate-reference system
3479          CALL netcdf_create_crs( id_set_xz(av), 000 )
3480
3481          IF ( land_surface )  THEN
3482
3483             CALL netcdf_create_dim( id_set_xz(av), 'zs', nzs,                 &
3484                                     id_dim_zs_xz(av), 542 )
3485             CALL netcdf_create_var( id_set_xz(av), (/ id_dim_zs_xz(av) /),    &
3486                                     'zs', NF90_DOUBLE, id_var_zs_xz(av),      &
3487                                     'meters', '', 543, 544, 000 )
3488
3489          ENDIF
3490
3491!
3492!--       Define the variables
3493          var_list = ';'
3494          i = 1
3495
3496          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
3497
3498             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
3499
3500!
3501!--             Check for the grid
3502                found = .FALSE.
3503                SELECT CASE ( do2d(av,i) )
3504!
3505!--                Most variables are defined on the zu grid
3506                   CASE ( 'e_xz', 'nc_xz', 'nr_xz', 'p_xz', 'pc_xz',           &
3507                          'pr_xz', 'prr_xz', 'q_xz', 'qc_xz',                  &
3508                          'ql_xz', 'ql_c_xz', 'ql_v_xz', 'ql_vp_xz', 'qr_xz',  &
3509                          'qv_xz', 's_xz',                                     &
3510                          'theta_xz', 'thetal_xz', 'thetav_xz' )
3511
3512                      grid_x = 'x'
3513                      grid_y = 'y'
3514                      grid_z = 'zu'
3515!
3516!--                u grid
3517                   CASE ( 'u_xz' )
3518
3519                      grid_x = 'xu'
3520                      grid_y = 'y'
3521                      grid_z = 'zu'
3522!
3523!--                v grid
3524                   CASE ( 'v_xz' )
3525
3526                      grid_x = 'x'
3527                      grid_y = 'yv'
3528                      grid_z = 'zu'
3529!
3530!--                w grid
3531                   CASE ( 'w_xz' )
3532
3533                      grid_x = 'x'
3534                      grid_y = 'y'
3535                      grid_z = 'zw'
3536
3537                   CASE DEFAULT
3538
3539!
3540!--                   Check for land surface quantities
3541                      IF ( land_surface )  THEN
3542                         CALL lsm_define_netcdf_grid( do2d(av,i), found,       &
3543                                                      grid_x, grid_y, grid_z )
3544                      ENDIF
3545
3546                      IF ( .NOT. found )  THEN
3547                         CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
3548                                                      grid_x, grid_y, grid_z )
3549                      ENDIF
3550
3551!
3552!--                   Check for ocean quantities
3553                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
3554                         CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
3555                                                        grid_x, grid_y, grid_z )
3556                      ENDIF
3557!
3558!--                   Check for radiation quantities
3559                      IF ( .NOT. found  .AND.  radiation )  THEN
3560                         CALL radiation_define_netcdf_grid( do2d(av,i), found, &
3561                                                            grid_x, grid_y,    &
3562                                                            grid_z )
3563                      ENDIF
3564!
3565!--                   Check for SALSA quantities
3566                      IF ( .NOT. found  .AND.  salsa )  THEN
3567                         CALL salsa_define_netcdf_grid( do2d(av,i), found,     &
3568                                                        grid_x, grid_y, grid_z )
3569                      ENDIF
3570
3571!
3572!--                   Check for gust module quantities
3573                      IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
3574                         CALL gust_define_netcdf_grid( do2d(av,i), found,      &
3575                                                       grid_x, grid_y, grid_z )
3576                      ENDIF
3577
3578!
3579!--                   Check for chemistry quantities
3580                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
3581                         CALL chem_define_netcdf_grid( do2d(av,i), found,      &
3582                                                       grid_x, grid_y,         &
3583                                                       grid_z )
3584                      ENDIF
3585
3586                      IF ( .NOT. found )                                       &
3587                         CALL doq_define_netcdf_grid( do2d(av,i), found,       &
3588                                                      grid_x, grid_y, grid_z )
3589
3590!
3591!--                   Check for user-defined quantities
3592                      IF ( .NOT. found  .AND.  user_module_enabled )  THEN
3593                         CALL user_define_netcdf_grid( do2d(av,i), found,      &
3594                                                       grid_x, grid_y, grid_z )
3595                      ENDIF
3596
3597                      IF ( .NOT. found )  THEN
3598                         WRITE ( message_string, * ) 'no grid defined for',    &
3599                                                ' variable ', TRIM( do2d(av,i) )
3600                         CALL message( 'define_netcdf_header', 'PA0244',       &
3601                                       0, 1, 0, 6, 0 )
3602                      ENDIF
3603
3604                END SELECT
3605
3606!
3607!--             Select the respective dimension ids
3608                IF ( grid_x == 'x' )  THEN
3609                   id_x = id_dim_x_xz(av)
3610                ELSEIF ( grid_x == 'xu' )  THEN
3611                   id_x = id_dim_xu_xz(av)
3612                ENDIF
3613
3614                IF ( grid_y == 'y' )  THEN
3615                   id_y = id_dim_y_xz(av)
3616                ELSEIF ( grid_y == 'yv' )  THEN
3617                   id_y = id_dim_yv_xz(av)
3618                ENDIF
3619
3620                IF ( grid_z == 'zu' )  THEN
3621                   id_z = id_dim_zu_xz(av)
3622                ELSEIF ( grid_z == 'zw' )  THEN
3623                   id_z = id_dim_zw_xz(av)
3624                ELSEIF ( grid_z == 'zs' )  THEN
3625                   id_z = id_dim_zs_xz(av)
3626                ENDIF
3627
3628!
3629!--             Define the grid
3630                CALL netcdf_create_var( id_set_xz(av), (/ id_x, id_y, id_z,    &
3631                                        id_dim_time_xz(av) /), do2d(av,i),     &
3632                                        nc_precision(2), id_var_do2d(av,i),    &
3633                                        TRIM( do2d_unit(av,i) ), do2d(av,i),   &
3634                                        159, 160, 355, .TRUE. )
3635
3636#if defined( __netcdf4_parallel )
3637
3638                IF ( netcdf_data_format > 4 )  THEN
3639!
3640!--                Set no fill for every variable to increase performance.
3641                   nc_stat = NF90_DEF_VAR_FILL( id_set_xz(av),     &
3642                                                id_var_do2d(av,i), &
3643                                                NF90_NOFILL, 0 )
3644                   CALL netcdf_handle_error( 'netcdf_define_header', 534 )
3645!
3646!--                Set independent io operations for parallel io. Collective io
3647!--                is only allowed in case of a 1d-decomposition along x,
3648!--                because otherwise, not all PEs have output data.
3649                   IF ( npey == 1 )  THEN
3650                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
3651                                                     id_var_do2d(av,i), &
3652                                                     NF90_COLLECTIVE )
3653                   ELSE
3654!
3655!--                   Test simulations showed that the output of cross sections
3656!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
3657!--                   faster than the output by the first row of PEs in
3658!--                   x-direction using NF90_INDEPENDENT.
3659                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),    &
3660                                                    id_var_do2d(av,i), &
3661                                                    NF90_COLLECTIVE )
3662!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
3663!                                                     id_var_do2d(av,i), &
3664!                                                     NF90_INDEPENDENT )
3665                   ENDIF
3666                   CALL netcdf_handle_error( 'netcdf_define_header', 449 )
3667                ENDIF
3668#endif
3669                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
3670
3671             ENDIF
3672
3673             i = i + 1
3674
3675          ENDDO
3676
3677!
3678!--       No arrays to output. Close the netcdf file and return.
3679          IF ( i == 1 )  RETURN
3680
3681!
3682!--       Write the list of variables as global attribute (this is used by
3683!--       restart runs and by combine_plot_fields)
3684          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
3685                                  var_list )
3686          CALL netcdf_handle_error( 'netcdf_define_header', 161 )
3687
3688!
3689!--       Set general no fill, otherwise the performance drops significantly for
3690!--       parallel output.
3691          nc_stat = NF90_SET_FILL( id_set_xz(av), NF90_NOFILL, oldmode )
3692          CALL netcdf_handle_error( 'netcdf_define_header', 530 )
3693
3694!
3695!--       Leave netCDF define mode
3696          nc_stat = NF90_ENDDEF( id_set_xz(av) )
3697          CALL netcdf_handle_error( 'netcdf_define_header', 162 )
3698
3699!
3700!--       These data are only written by PE0 for parallel output to increase
3701!--       the performance.
3702          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
3703
3704!
3705!--          Write axis data: y_xz, x, zu, zw
3706             ALLOCATE( netcdf_data(1:ns) )
3707
3708!
3709!--          Write y_xz data (shifted by +dy/2)
3710             DO  i = 1, ns
3711                IF( section(i,2) == -1 )  THEN
3712                   netcdf_data(i) = -1.0_wp  ! section averaged along y
3713                ELSE
3714                   netcdf_data(i) = ( section(i,2) + 0.5_wp ) * dy
3715                ENDIF
3716             ENDDO
3717             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), &
3718                                     netcdf_data, start = (/ 1 /),   &
3719                                     count = (/ ns /) )
3720             CALL netcdf_handle_error( 'netcdf_define_header', 163 )
3721
3722!
3723!--          Write yv_xz data
3724             DO  i = 1, ns
3725                IF( section(i,2) == -1 )  THEN
3726                   netcdf_data(i) = -1.0_wp  ! section averaged along y
3727                ELSE
3728                   netcdf_data(i) = section(i,2) * dy
3729                ENDIF
3730             ENDDO
3731             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_yv_xz(av), &
3732                                     netcdf_data, start = (/ 1 /),    &
3733                                     count = (/ ns /) )
3734             CALL netcdf_handle_error( 'netcdf_define_header', 375 )
3735
3736!
3737!--          Write gridpoint number data
3738             netcdf_data(1:ns) = section(1:ns,2)
3739             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_ind_y_xz(av), &
3740                                     netcdf_data, start = (/ 1 /),       &
3741                                     count = (/ ns /) )
3742             CALL netcdf_handle_error( 'netcdf_define_header', 164 )
3743
3744
3745             DEALLOCATE( netcdf_data )
3746
3747!
3748!--          Write data for x (shifted by +dx/2) and xu axis
3749             ALLOCATE( netcdf_data(0:nx) )
3750
3751             DO  i = 0, nx
3752                netcdf_data(i) = ( i + 0.5_wp ) * dx
3753             ENDDO
3754
3755             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av), &
3756                                     netcdf_data, start = (/ 1 /),   &
3757                                     count = (/ nx+1 /) )
3758             CALL netcdf_handle_error( 'netcdf_define_header', 165 )
3759
3760             DO  i = 0, nx
3761                netcdf_data(i) = i * dx
3762             ENDDO
3763
3764             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_xu_xz(av), &
3765                                     netcdf_data, start = (/ 1 /),    &
3766                                     count = (/ nx+1 /) )
3767             CALL netcdf_handle_error( 'netcdf_define_header', 377 )
3768
3769             DEALLOCATE( netcdf_data )
3770
3771!
3772!--          Write zu and zw data (vertical axes)
3773             ALLOCATE( netcdf_data(0:nz+1) )
3774
3775             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
3776             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zu_xz(av), &
3777                                     netcdf_data, start = (/ 1 /),    &
3778                                     count = (/ nz+2 /) )
3779             CALL netcdf_handle_error( 'netcdf_define_header', 166 )
3780
3781             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
3782             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zw_xz(av), &
3783                                     netcdf_data, start = (/ 1 /),    &
3784                                     count = (/ nz+2 /) )
3785             CALL netcdf_handle_error( 'netcdf_define_header', 167 )
3786
3787!
3788!--          Write zs data
3789             IF ( land_surface )  THEN
3790                netcdf_data(0:nzs-1) = - zs(nzb_soil:nzt_soil)
3791                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zs_xz(av), &
3792                                        netcdf_data(0:nzs), start = (/ 1 /),    &
3793                                        count = (/ nzt_soil-nzb_soil+1 /) )
3794               CALL netcdf_handle_error( 'netcdf_define_header', 548 )
3795             ENDIF
3796
3797             DEALLOCATE( netcdf_data )
3798!
3799!--          Write UTM coordinates
3800             IF ( init_model%rotation_angle == 0.0_wp )  THEN
3801!
3802!--             1D in case of no rotation
3803                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
3804!
3805!--             x coordinates
3806                ALLOCATE( netcdf_data(0:nx) )
3807                DO  k = 0, 2
3808!
3809!--                Scalar grid points
3810                   IF ( k == 0 )  THEN
3811                      shift_x = 0.5
3812!
3813!--                u grid points
3814                   ELSEIF ( k == 1 )  THEN
3815                      shift_x = 0.0
3816!
3817!--                v grid points
3818                   ELSEIF ( k == 2 )  THEN
3819                      shift_x = 0.5
3820                   ENDIF
3821
3822                   DO  i = 0, nx
3823                     netcdf_data(i) = init_model%origin_x            &
3824                                    + cos_ra * ( i + shift_x ) * dx
3825                   ENDDO
3826
3827                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),&
3828                                           netcdf_data, start = (/ 1 /),   &
3829                                           count = (/ nx+1 /) )
3830                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
3831
3832                ENDDO
3833                DEALLOCATE( netcdf_data )
3834!
3835!--             y coordinates
3836                ALLOCATE( netcdf_data(1:ns) )
3837                DO  k = 0, 2
3838!
3839!--                Scalar grid points
3840                   IF ( k == 0 )  THEN
3841                      shift_y = 0.5
3842!
3843!--                u grid points
3844                   ELSEIF ( k == 1 )  THEN
3845                      shift_y = 0.5
3846!
3847!--                v grid points
3848                   ELSEIF ( k == 2 )  THEN
3849                      shift_y = 0.0
3850                   ENDIF
3851
3852                   DO  i = 1, ns
3853                      IF( section(i,2) == -1 )  THEN
3854                         netcdf_data(i) = -1.0_wp  ! section averaged along y
3855                      ELSE
3856                         netcdf_data(i) = init_model%origin_y &
3857                                     + cos_ra * ( section(i,2) + shift_y ) * dy
3858                      ENDIF
3859                   ENDDO
3860
3861                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),&
3862                                           netcdf_data, start = (/ 1 /),   &
3863                                           count = (/ ns /) )
3864                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3865
3866                ENDDO
3867                DEALLOCATE( netcdf_data )
3868
3869             ELSE
3870!
3871!--             2D in case of rotation
3872                ALLOCATE( netcdf_data_2d(0:nx,1:ns) )
3873                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
3874                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
3875
3876                DO  k = 0, 2
3877!
3878!--                Scalar grid points
3879                   IF ( k == 0 )  THEN
3880                      shift_x = 0.5 ; shift_y = 0.5
3881!
3882!--                u grid points
3883                   ELSEIF ( k == 1 )  THEN
3884                      shift_x = 0.0 ; shift_y = 0.5
3885!
3886!--                v grid points
3887                   ELSEIF ( k == 2 )  THEN
3888                      shift_x = 0.5 ; shift_y = 0.0
3889                   ENDIF
3890
3891                   DO  j = 1, ns
3892                      IF( section(j,2) == -1 )  THEN
3893                         netcdf_data_2d(:,j) = -1.0_wp  ! section averaged along y
3894                      ELSE
3895                         DO  i = 0, nx
3896                            netcdf_data_2d(i,j) = init_model%origin_x          &
3897                                    + cos_ra * ( i + shift_x ) * dx            &
3898                                    + sin_ra * ( section(j,2) + shift_y ) * dy
3899                         ENDDO
3900                      ENDIF
3901                   ENDDO
3902
3903                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),  &
3904                                           netcdf_data_2d, start = (/ 1, 1 /),   &
3905                                           count = (/ nx+1, ns /) )
3906                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
3907
3908                   DO  j = 1, ns
3909                      IF( section(j,2) == -1 )  THEN
3910                         netcdf_data_2d(:,j) = -1.0_wp  ! section averaged along y
3911                      ELSE
3912                         DO  i = 0, nx
3913                            netcdf_data_2d(i,j) = init_model%origin_y          &
3914                                    - sin_ra * ( i + shift_x ) * dx            &
3915                                    + cos_ra * ( section(j,2) + shift_y ) * dy
3916                         ENDDO
3917                      ENDIF
3918                   ENDDO
3919
3920                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(k,av),  &
3921                                           netcdf_data_2d, start = (/ 1, 1 /),   &
3922                                           count = (/ nx+1, ns /) )
3923                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3924
3925                ENDDO
3926                DEALLOCATE( netcdf_data_2d )
3927             ENDIF
3928!
3929!--          Write lon and lat data
3930             ALLOCATE( lat(0:nx,1:ns) )
3931             ALLOCATE( lon(0:nx,1:ns) )
3932             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
3933             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
3934
3935             DO  k = 0, 2
3936!
3937!--             Scalar grid points
3938                IF ( k == 0 )  THEN
3939                   shift_x = 0.5 ; shift_y = 0.5
3940!
3941!--             u grid points
3942                ELSEIF ( k == 1 )  THEN
3943                   shift_x = 0.0 ; shift_y = 0.5
3944!
3945!--             v grid points
3946                ELSEIF ( k == 2 )  THEN
3947                   shift_x = 0.5 ; shift_y = 0.0
3948                ENDIF
3949
3950                DO  j = 1, ns
3951                   IF( section(j,2) == -1 )  THEN
3952                      lat(:,j) = -90.0_wp  ! section averaged along y
3953                      lon(:,j) = -180.0_wp  ! section averaged along y
3954                   ELSE
3955                      DO  i = 0, nx
3956                         eutm = init_model%origin_x            &
3957                              + cos_ra * ( i + shift_x ) * dx  &
3958                              + sin_ra * ( section(j,2) + shift_y ) * dy
3959                         nutm = init_model%origin_y            &
3960                              - sin_ra * ( i + shift_x ) * dx  &
3961                              + cos_ra * ( section(j,2) + shift_y ) * dy
3962
3963                         CALL  convert_utm_to_geographic( crs_list,          &
3964                                                          eutm, nutm,        &
3965                                                          lon(i,j), lat(i,j) )
3966                      ENDDO
3967                   ENDIF
3968                ENDDO
3969
3970                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lon_xz(k,av), &
3971                                     lon, start = (/ 1, 1 /),       &
3972                                     count = (/ nx+1, ns /) )
3973                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3974
3975                nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_lat_xz(k,av), &
3976                                     lat, start = (/ 1, 1 /),       &
3977                                     count = (/ nx+1, ns /) )
3978                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
3979             ENDDO
3980
3981             DEALLOCATE( lat )
3982             DEALLOCATE( lon )
3983
3984          ENDIF
3985
3986
3987       CASE ( 'xz_ext' )
3988
3989!
3990!--       Get the list of variables and compare with the actual run.
3991!--       First var_list_old has to be reset, since GET_ATT does not assign
3992!--       trailing blanks.
3993          var_list_old = ' '
3994          nc_stat = NF90_GET_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
3995                                  var_list_old )
3996          CALL netcdf_handle_error( 'netcdf_define_header', 168 )
3997
3998          var_list = ';'
3999          i = 1
4000          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
4001             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
4002                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
4003             ENDIF
4004             i = i + 1
4005          ENDDO
4006
4007          IF ( av == 0 )  THEN
4008             var = '(xz)'
4009          ELSE
4010             var = '(xz_av)'
4011          ENDIF
4012
4013          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
4014             message_string = 'netCDF file for cross-sections ' //           &
4015                              TRIM( var ) // ' from previous run found,' //  &
4016                              '&but this file cannot be extended due to' //  &
4017                              ' variable mismatch.' //                       &
4018                              '&New file is created instead.'
4019             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
4020             extend = .FALSE.
4021             RETURN
4022          ENDIF
4023
4024!
4025!--       Calculate the number of current sections
4026          ns = 1
4027          DO WHILE ( section(ns,2) /= -9999  .AND.  ns <= 100 )
4028             ns = ns + 1
4029          ENDDO
4030          ns = ns - 1
4031
4032!
4033!--       Get and compare the number of vertical cross sections
4034          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'y_xz', id_var_y_xz(av) )
4035          CALL netcdf_handle_error( 'netcdf_define_header', 169 )
4036
4037          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_y_xz(av), &
4038                                           dimids = id_dim_y_xz_old )
4039          CALL netcdf_handle_error( 'netcdf_define_header', 170 )
4040          id_dim_y_xz(av) = id_dim_y_xz_old(1)
4041
4042          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_y_xz(av), &
4043                                            len = ns_old )
4044          CALL netcdf_handle_error( 'netcdf_define_header', 171 )
4045
4046          IF ( ns /= ns_old )  THEN
4047             message_string = 'netCDF file for cross-sections ' //          &
4048                              TRIM( var ) // ' from previous run found,' // &
4049                              '&but this file cannot be extended due to' // &
4050                              ' mismatch in number of' //                   &
4051                              ' cross sections.' //                         &
4052                              '&New file is created instead.'
4053             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
4054             extend = .FALSE.
4055             RETURN
4056          ENDIF
4057
4058!
4059!--       Get and compare the heights of the cross sections
4060          ALLOCATE( netcdf_data(1:ns_old) )
4061
4062          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data )
4063          CALL netcdf_handle_error( 'netcdf_define_header', 172 )
4064
4065          DO  i = 1, ns
4066             IF ( section(i,2) /= -1 )  THEN
4067                IF ( ( ( section(i,2) + 0.5 ) * dy ) /= netcdf_data(i) )  THEN
4068                   message_string = 'netCDF file for cross-sections ' //       &
4069                               TRIM( var ) // ' from previous run found,' //   &
4070                               ' but this file cannot be extended' //          &
4071                               ' due to mismatch in cross' //                  &
4072                               ' section levels.' //                           &
4073                               ' New file is created instead.'
4074                   CALL message( 'define_netcdf_header', 'PA0251',             &
4075                                                                 0, 1, 0, 6, 0 )
4076                   extend = .FALSE.
4077                   RETURN
4078                ENDIF
4079             ELSE
4080                IF ( -1.0_wp /= netcdf_data(i) )  THEN
4081                   message_string = 'netCDF file for cross-sections ' //       &
4082                               TRIM( var ) // ' from previous run found,' //   &
4083                               ' but this file cannot be extended' //          &
4084                               ' due to mismatch in cross' //                  &
4085                               ' section levels.' //                           &
4086                               ' New file is created instead.'
4087                   CALL message( 'define_netcdf_header', 'PA0251',             &
4088                                                                 0, 1, 0, 6, 0 )
4089                   extend = .FALSE.
4090                   RETURN
4091                ENDIF
4092             ENDIF
4093          ENDDO
4094
4095          DEALLOCATE( netcdf_data )
4096
4097!
4098!--       Get the id of the time coordinate (unlimited coordinate) and its
4099!--       last index on the file. The next time level is do2d..count+1.
4100!--       The current time must be larger than the last output time
4101!--       on the file.
4102          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'time', id_var_time_xz(av) )
4103          CALL netcdf_handle_error( 'netcdf_define_header', 173 )
4104
4105          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_time_xz(av), &
4106                                           dimids = id_dim_time_old )
4107          CALL netcdf_handle_error( 'netcdf_define_header', 174 )
4108          id_dim_time_xz(av) = id_dim_time_old(1)
4109
4110          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_time_xz(av), &
4111                                            len = ntime_count )
4112          CALL netcdf_handle_error( 'netcdf_define_header', 175 )
4113
4114!
4115!--       For non-parallel output use the last output time level of the netcdf
4116!--       file because the time dimension is unlimited. In case of parallel
4117!--       output the variable ntime_count could get the value of 9*10E36 because
4118!--       the time dimension is limited.
4119          IF ( netcdf_data_format < 5 ) do2d_xz_time_count(av) = ntime_count
4120
4121          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_time_xz(av),           &
4122                                  last_time_coordinate,                        &
4123                                  start = (/ do2d_xz_time_count(av) /),        &
4124                                  count = (/ 1 /) )
4125          CALL netcdf_handle_error( 'netcdf_define_header', 176 )
4126
4127          IF ( last_time_coordinate(1) >= simulated_time )  THEN
4128             message_string = 'netCDF file for cross sections ' //             &
4129                              TRIM( var ) // ' from previous run found,' //    &
4130                              '&but this file cannot be extended becaus' //    &
4131                              'e the current output time' //                   &
4132                              '&is less or equal than the last output t' //    &
4133                              'ime on this file.' //                           &
4134                              '&New file is created instead.'
4135             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
4136             do2d_xz_time_count(av) = 0
4137             extend = .FALSE.
4138             RETURN
4139          ENDIF
4140
4141          IF ( netcdf_data_format > 4 )  THEN
4142!
4143!--          Check if the needed number of output time levels is increased
4144!--          compared to the number of time levels in the existing file.
4145             IF ( ntdim_2d_xz(av) > ntime_count )  THEN
4146                message_string = 'netCDF file for cross sections ' // &
4147                                 TRIM( var ) // ' from previous run found,' // &
4148                                 '&but this file cannot be extended becaus' // &
4149                                 'e the number of output time levels has b' // &
4150                                 'een increased compared to the previous s' // &
4151                                 'imulation.' //                               &
4152                                 '&New file is created instead.'
4153                CALL message( 'define_netcdf_header', 'PA0390', 0, 1, 0, 6, 0 )
4154                do2d_xz_time_count(av) = 0
4155                extend = .FALSE.
4156!
4157!--             Recalculate the needed time levels for the new file.
4158                IF ( av == 0 )  THEN
4159                   ntdim_2d_xz(0) = CEILING(                            &
4160                           ( end_time - MAX( skip_time_do2d_xz,         &
4161                                             simulated_time_at_begin )  &
4162                           ) / dt_do2d_xz )
4163                   IF ( do2d_at_begin )  ntdim_2d_xz(0) = ntdim_2d_xz(0) + 1
4164                ELSE
4165                   ntdim_2d_xz(1) = CEILING(                            &
4166                           ( end_time - MAX( skip_time_data_output_av,  &
4167                                             simulated_time_at_begin )  &
4168                           ) / dt_data_output_av )
4169                ENDIF
4170                RETURN
4171             ENDIF
4172          ENDIF
4173
4174!
4175!--       Dataset seems to be extendable.
4176!--       Now get the variable ids.
4177          i = 1
4178          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
4179             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
4180                nc_stat = NF90_INQ_VARID( id_set_xz(av), do2d(av,i), &
4181                                          id_var_do2d(av,i) )
4182                CALL netcdf_handle_error( 'netcdf_define_header', 177 )
4183#if defined( __netcdf4_parallel )
4184!
4185!--             Set independent io operations for parallel io. Collective io
4186!--             is only allowed in case of a 1d-decomposition along x, because
4187!--             otherwise, not all PEs have output data.
4188                IF ( netcdf_data_format > 4 )  THEN
4189                   IF ( npey == 1 )  THEN
4190                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
4191                                                     id_var_do2d(av,i), &
4192                                                     NF90_COLLECTIVE )
4193                   ELSE
4194!
4195!--                   Test simulations showed that the output of cross sections
4196!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
4197!--                   faster than the output by the first row of PEs in
4198!--                   x-direction using NF90_INDEPENDENT.
4199                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
4200                                                     id_var_do2d(av,i), &
4201                                                     NF90_COLLECTIVE )
4202!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
4203!                                                     id_var_do2d(av,i), &
4204!                                                     NF90_INDEPENDENT )
4205                   ENDIF
4206                   CALL netcdf_handle_error( 'netcdf_define_header', 455 )
4207                ENDIF
4208#endif
4209             ENDIF
4210             i = i + 1
4211          ENDDO
4212
4213!
4214!--       Update the title attribute on file
4215!--       In order to avoid 'data mode' errors if updated attributes are larger
4216!--       than their original size, NF90_PUT_ATT is called in 'define mode'
4217!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
4218!--       performance loss due to data copying; an alternative strategy would be
4219!--       to ensure equal attribute size in a job chain. Maybe revise later.
4220          IF ( av == 0 )  THEN
4221             time_average_text = ' '
4222          ELSE
4223             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
4224                                                            averaging_interval
4225          ENDIF
4226          nc_stat = NF90_REDEF( id_set_xz(av) )
4227          CALL netcdf_handle_error( 'netcdf_define_header', 433 )
4228          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title',         &
4229                                  TRIM( run_description_header ) //            &
4230                                  TRIM( time_average_text ) )
4231          CALL netcdf_handle_error( 'netcdf_define_header', 178 )
4232          nc_stat = NF90_ENDDEF( id_set_xz(av) )
4233          CALL netcdf_handle_error( 'netcdf_define_header', 434 )
4234          message_string = 'netCDF file for cross-sections ' //                &
4235                            TRIM( var ) // ' from previous run found.' //      &
4236                           '&This file will be extended.'
4237          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
4238
4239
4240       CASE ( 'yz_new' )
4241
4242!
4243!--       Define some global attributes of the dataset
4244          IF ( av == 0 )  THEN
4245             CALL netcdf_create_global_atts( id_set_yz(av), 'yz', TRIM( run_description_header ), 179 )
4246             time_average_text = ' '
4247          ELSE
4248             CALL netcdf_create_global_atts( id_set_yz(av), 'yz_av', TRIM( run_description_header ), 179 )
4249             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
4250             nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'time_avg',   &
4251                                     TRIM( time_average_text ) )
4252             CALL netcdf_handle_error( 'netcdf_define_header', 180 )
4253          ENDIF
4254
4255!
4256!--       Define time coordinate for yz sections.
4257!--       For parallel output the time dimensions has to be limited, otherwise
4258!--       the performance drops significantly.
4259          IF ( netcdf_data_format < 5 )  THEN
4260             CALL netcdf_create_dim( id_set_yz(av), 'time', NF90_UNLIMITED,    &
4261                                     id_dim_time_yz(av), 181 )
4262          ELSE
4263             CALL netcdf_create_dim( id_set_yz(av), 'time', ntdim_2d_yz(av),   &
4264                                     id_dim_time_yz(av), 526 )
4265          ENDIF
4266
4267          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_time_yz(av) /),     &
4268                                  'time', NF90_DOUBLE, id_var_time_yz(av),     &
4269                                  'seconds', 'time', 182, 183, 000 )
4270          CALL netcdf_create_att( id_set_yz(av), id_var_time_yz(av), 'standard_name', 'time', 000)
4271          CALL netcdf_create_att( id_set_yz(av), id_var_time_yz(av), 'axis', 'T', 000)
4272!
4273!--       Define the spatial dimensions and coordinates for yz-sections.
4274!--       First, determine the number of vertical sections to be written.
4275          IF ( section(1,3) == -9999 )  THEN
4276             RETURN
4277          ELSE
4278             ns = 1
4279             DO WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
4280                ns = ns + 1
4281             ENDDO
4282             ns = ns - 1
4283          ENDIF
4284
4285!
4286!--       Define x axis (for scalar position)
4287          CALL netcdf_create_dim( id_set_yz(av), 'x_yz', ns, id_dim_x_yz(av),  &
4288                                  184 )
4289          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /),        &
4290                                  'x_yz', NF90_DOUBLE, id_var_x_yz(av),        &
4291                                  'meters', '', 185, 186, 000 )
4292!
4293!--       Define x axis (for u position)
4294          CALL netcdf_create_dim( id_set_yz(av), 'xu_yz', ns,                  &
4295                                  id_dim_xu_yz(av), 377 )
4296          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_xu_yz(av) /),       &
4297                                  'xu_yz', NF90_DOUBLE, id_var_xu_yz(av),      &
4298                                  'meters', '', 378, 379, 000 )
4299!
4300!--       Define a variable to store the layer indices of the vertical cross
4301!--       sections
4302          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_x_yz(av) /),        &
4303                                  'ind_x_yz', NF90_DOUBLE,                     &
4304                                  id_var_ind_x_yz(av), 'gridpoints', '', 187,  &
4305                                  188, 000 )
4306!
4307!--       Define y-axis (for scalar position)
4308          CALL netcdf_create_dim( id_set_yz(av), 'y', ny+1, id_dim_y_yz(av),   &
4309                                  189 )
4310          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_y_yz(av) /), 'y',   &
4311                                  NF90_DOUBLE, id_var_y_yz(av), 'meters', '',  &
4312                                  190, 191, 000 )
4313!
4314!--       Define y-axis (for v position)
4315          CALL netcdf_create_dim( id_set_yz(av), 'yv', ny+1, id_dim_yv_yz(av), &
4316                                  380 )
4317          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_yv_yz(av) /), 'yv', &
4318                                  NF90_DOUBLE, id_var_yv_yz(av), 'meters', '', &
4319                                  381, 382, 000 )
4320!
4321!--       Define the two z-axes (zu and zw)
4322          CALL netcdf_create_dim( id_set_yz(av), 'zu', nz+2, id_dim_zu_yz(av), &
4323                                  192 )
4324          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zu_yz(av) /), 'zu', &
4325                                  NF90_DOUBLE, id_var_zu_yz(av), 'meters', '', &
4326                                  193, 194, 000 )
4327
4328          CALL netcdf_create_dim( id_set_yz(av), 'zw', nz+2, id_dim_zw_yz(av), &
4329                                  195 )
4330          CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zw_yz(av) /), 'zw', &
4331                                  NF90_DOUBLE, id_var_zw_yz(av), 'meters', '', &
4332                                  196, 197, 000 )
4333!
4334!--       Define UTM and geographic coordinates
4335          CALL define_geo_coordinates( id_set_yz(av),         &
4336                  (/ id_dim_x_yz(av), id_dim_xu_yz(av) /),    &
4337                  (/ id_dim_y_yz(av), id_dim_yv_yz(av) /),    &
4338                  id_var_eutm_yz(:,av), id_var_nutm_yz(:,av), &
4339                  id_var_lat_yz(:,av), id_var_lon_yz(:,av)    )
4340!
4341!--       Define coordinate-reference system
4342          CALL netcdf_create_crs( id_set_yz(av), 000 )
4343
4344          IF ( land_surface )  THEN
4345
4346             CALL netcdf_create_dim( id_set_yz(av), 'zs', nzs,                 &
4347                                     id_dim_zs_yz(av), 545 )
4348             CALL netcdf_create_var( id_set_yz(av), (/ id_dim_zs_yz(av) /),    &
4349                                     'zs', NF90_DOUBLE, id_var_zs_yz(av),      &
4350                                     'meters', '', 546, 547, 000 )
4351
4352          ENDIF
4353
4354!
4355!--       Define the variables
4356          var_list = ';'
4357          i = 1
4358
4359          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
4360
4361             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
4362
4363!
4364!--             Check for the grid
4365                found = .FALSE.
4366                SELECT CASE ( do2d(av,i) )
4367!
4368!--                Most variables are defined on the zu grid
4369                   CASE ( 'e_yz', 'nc_yz', 'nr_yz', 'p_yz', 'pc_yz',           &
4370                          'pr_yz','prr_yz', 'q_yz', 'qc_yz', 'ql_yz',          &
4371                          'ql_c_yz', 'ql_v_yz', 'ql_vp_yz', 'qr_yz', 'qv_yz',  &
4372                          's_yz',                                              &
4373                          'theta_yz', 'thetal_yz', 'thetav_yz', 'ti_yz' )
4374
4375                      grid_x = 'x'
4376                      grid_y = 'y'
4377                      grid_z = 'zu'
4378!
4379!--                u grid
4380                   CASE ( 'u_yz' )
4381
4382                      grid_x = 'xu'
4383                      grid_y = 'y'
4384                      grid_z = 'zu'
4385!
4386!--                v grid
4387                   CASE ( 'v_yz' )
4388
4389                      grid_x = 'x'
4390                      grid_y = 'yv'
4391                      grid_z = 'zu'
4392!
4393!--                w grid
4394                   CASE ( 'w_yz' )
4395
4396                      grid_x = 'x'
4397                      grid_y = 'y'
4398                      grid_z = 'zw'
4399
4400
4401                   CASE DEFAULT
4402!
4403!--                   Check for land surface quantities
4404                      IF ( land_surface )  THEN
4405                         CALL lsm_define_netcdf_grid( do2d(av,i), found,       &
4406                                                      grid_x, grid_y, grid_z )
4407                      ENDIF
4408
4409                      IF ( .NOT. found )  THEN
4410                         CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
4411                                                      grid_x, grid_y, grid_z )
4412                      ENDIF
4413
4414!
4415!--                   Check for ocean quantities
4416                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
4417                         CALL ocean_define_netcdf_grid( do2d(av,i), found,     &
4418                                                       grid_x, grid_y, grid_z )
4419                      ENDIF
4420!
4421!--                   Check for radiation quantities
4422                      IF ( .NOT. found  .AND.  radiation )  THEN
4423                         CALL radiation_define_netcdf_grid( do2d(av,i), found, &
4424                                                            grid_x, grid_y,    &
4425                                                            grid_z )
4426                      ENDIF
4427!
4428!--                   Check for SALSA quantities
4429                      IF ( .NOT. found  .AND.  salsa )  THEN
4430                         CALL salsa_define_netcdf_grid( do2d(av,i), found,     &
4431                                                        grid_x, grid_y, grid_z )
4432                      ENDIF
4433!
4434!--                   Check for gust module quantities
4435                      IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
4436                         CALL gust_define_netcdf_grid( do2d(av,i), found,      &
4437                                                       grid_x, grid_y, grid_z )
4438                      ENDIF
4439
4440!
4441!--                   Check for chemistry quantities
4442                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
4443                         CALL chem_define_netcdf_grid( do2d(av,i), found,      &
4444                                                       grid_x, grid_y,         &
4445                                                       grid_z )
4446                      ENDIF
4447
4448                      IF ( .NOT. found )                                       &
4449                         CALL doq_define_netcdf_grid(                          &
4450                                                    do2d(av,i), found, grid_x, &
4451                                                    grid_y, grid_z           )
4452!
4453!--                   Check for user-defined quantities
4454                      IF ( .NOT. found  .AND.  user_module_enabled )  THEN
4455                         CALL user_define_netcdf_grid( do2d(av,i), found,      &
4456                                                       grid_x, grid_y, grid_z )
4457                      ENDIF
4458
4459                      IF ( .NOT. found )  THEN
4460                         WRITE ( message_string, * ) 'no grid defined for',    &
4461                                                ' variable ', TRIM( do2d(av,i) )
4462                         CALL message( 'define_netcdf_header', 'PA0244',       &
4463                                       0, 1, 0, 6, 0 )
4464                      ENDIF
4465
4466                END SELECT
4467
4468!
4469!--             Select the respective dimension ids
4470                IF ( grid_x == 'x' )  THEN
4471                   id_x = id_dim_x_yz(av)
4472                ELSEIF ( grid_x == 'xu' )  THEN
4473                   id_x = id_dim_xu_yz(av)
4474                ENDIF
4475
4476                IF ( grid_y == 'y' )  THEN
4477                   id_y = id_dim_y_yz(av)
4478                ELSEIF ( grid_y == 'yv' )  THEN
4479                   id_y = id_dim_yv_yz(av)
4480                ENDIF
4481
4482                IF ( grid_z == 'zu' )  THEN
4483                   id_z = id_dim_zu_yz(av)
4484                ELSEIF ( grid_z == 'zw' )  THEN
4485                   id_z = id_dim_zw_yz(av)
4486                ELSEIF ( grid_z == 'zs' )  THEN
4487                   id_z = id_dim_zs_yz(av)
4488                ENDIF
4489
4490!
4491!--             Define the grid
4492                CALL netcdf_create_var( id_set_yz(av),  (/ id_x, id_y, id_z,   &
4493                                        id_dim_time_yz(av) /), do2d(av,i),     &
4494                                        nc_precision(3), id_var_do2d(av,i),    &
4495                                        TRIM( do2d_unit(av,i) ), do2d(av,i),   &
4496                                        198, 199, 356, .TRUE. )
4497
4498#if defined( __netcdf4_parallel )
4499                IF ( netcdf_data_format > 4 )  THEN
4500!
4501!--                Set no fill for every variable to increase performance.
4502                   nc_stat = NF90_DEF_VAR_FILL( id_set_yz(av),     &
4503                                                id_var_do2d(av,i), &
4504                                                NF90_NOFILL, 0 )
4505                   CALL netcdf_handle_error( 'netcdf_define_header', 535 )
4506!
4507!--                Set independent io operations for parallel io. Collective io
4508!--                is only allowed in case of a 1d-decomposition along y,
4509!--                because otherwise, not all PEs have output data.
4510                   IF ( npex == 1 )  THEN
4511                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
4512                                                     id_var_do2d(av,i), &
4513                                                     NF90_COLLECTIVE )
4514                   ELSE
4515!
4516!--                   Test simulations showed that the output of cross sections
4517!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
4518!--                   faster than the output by the first row of PEs in
4519!--                   y-direction using NF90_INDEPENDENT.
4520                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
4521                                                     id_var_do2d(av,i), &
4522                                                     NF90_COLLECTIVE )
4523!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
4524!                                                     id_var_do2d(av,i), &
4525!                                                     NF90_INDEPENDENT )
4526                   ENDIF
4527                   CALL netcdf_handle_error( 'netcdf_define_header', 450 )
4528                ENDIF
4529#endif
4530                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
4531
4532             ENDIF
4533
4534             i = i + 1
4535
4536          ENDDO
4537
4538!
4539!--       No arrays to output. Close the netcdf file and return.
4540          IF ( i == 1 )  RETURN
4541
4542!
4543!--       Write the list of variables as global attribute (this is used by
4544!--       restart runs and by combine_plot_fields)
4545          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
4546                                  var_list )
4547          CALL netcdf_handle_error( 'netcdf_define_header', 200 )
4548
4549!
4550!--       Set general no fill, otherwise the performance drops significantly for
4551!--       parallel output.
4552          nc_stat = NF90_SET_FILL( id_set_yz(av), NF90_NOFILL, oldmode )
4553          CALL netcdf_handle_error( 'netcdf_define_header', 531 )
4554
4555!
4556!--       Leave netCDF define mode
4557          nc_stat = NF90_ENDDEF( id_set_yz(av) )
4558          CALL netcdf_handle_error( 'netcdf_define_header', 201 )
4559
4560!
4561!--       These data are only written by PE0 for parallel output to increase
4562!--       the performance.
4563          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
4564
4565!
4566!--          Write axis data: x_yz, y, zu, zw
4567             ALLOCATE( netcdf_data(1:ns) )
4568
4569!
4570!--          Write x_yz data (shifted by +dx/2)
4571             DO  i = 1, ns
4572                IF( section(i,3) == -1 )  THEN
4573                   netcdf_data(i) = -1.0_wp  ! section averaged along x
4574                ELSE
4575                   netcdf_data(i) = ( section(i,3) + 0.5_wp ) * dx
4576                ENDIF
4577             ENDDO
4578             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), &
4579                                     netcdf_data, start = (/ 1 /),   &
4580                                     count = (/ ns /) )
4581             CALL netcdf_handle_error( 'netcdf_define_header', 202 )
4582
4583!
4584!--          Write x_yz data (xu grid)
4585             DO  i = 1, ns
4586                IF( section(i,3) == -1 )  THEN
4587                   netcdf_data(i) = -1.0_wp  ! section averaged along x
4588                ELSE
4589                   netcdf_data(i) = section(i,3) * dx
4590                ENDIF
4591             ENDDO
4592             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av), &
4593                                     netcdf_data, start = (/ 1 /),    &
4594                                     count = (/ ns /) )
4595             CALL netcdf_handle_error( 'netcdf_define_header', 383 )
4596
4597!
4598!--          Write gridpoint number data
4599             netcdf_data(1:ns) = section(1:ns,3)
4600             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_ind_x_yz(av), &
4601                                     netcdf_data, start = (/ 1 /),       &
4602                                     count = (/ ns /) )
4603             CALL netcdf_handle_error( 'netcdf_define_header', 203 )
4604
4605             DEALLOCATE( netcdf_data )
4606
4607!
4608!--          Write data for y (shifted by +dy/2) and yv axis
4609             ALLOCATE( netcdf_data(0:ny) )
4610
4611             DO  j = 0, ny
4612                netcdf_data(j) = ( j + 0.5_wp ) * dy
4613             ENDDO
4614
4615             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av), &
4616                                     netcdf_data, start = (/ 1 /),   &
4617                                     count = (/ ny+1 /) )
4618             CALL netcdf_handle_error( 'netcdf_define_header', 204 )
4619
4620             DO  j = 0, ny
4621                netcdf_data(j) = j * dy
4622             ENDDO
4623
4624             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_yv_yz(av), &
4625                                     netcdf_data, start = (/ 1 /),    &
4626                                     count = (/ ny+1 /) )
4627             CALL netcdf_handle_error( 'netcdf_define_header', 384 )
4628
4629             DEALLOCATE( netcdf_data )
4630
4631!
4632!--          Write zu and zw data (vertical axes)
4633             ALLOCATE( netcdf_data(0:nz+1) )
4634
4635             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
4636             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zu_yz(av), &
4637                                     netcdf_data, start = (/ 1 /),    &
4638                                     count = (/ nz+2 /) )
4639             CALL netcdf_handle_error( 'netcdf_define_header', 205 )
4640
4641             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
4642             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zw_yz(av), &
4643                                     netcdf_data, start = (/ 1 /),    &
4644                                     count = (/ nz+2 /) )
4645             CALL netcdf_handle_error( 'netcdf_define_header', 206 )
4646
4647             DEALLOCATE( netcdf_data )
4648!
4649!--          Write UTM coordinates
4650             IF ( init_model%rotation_angle == 0.0_wp )  THEN
4651!
4652!--             1D in case of no rotation
4653                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
4654!
4655!--             x coordinates
4656                ALLOCATE( netcdf_data(1:ns) )
4657                DO  k = 0, 2
4658!
4659!--                Scalar grid points
4660                   IF ( k == 0 )  THEN
4661                      shift_x = 0.5
4662!
4663!--                u grid points
4664                   ELSEIF ( k == 1 )  THEN
4665                      shift_x = 0.0
4666!
4667!--                v grid points
4668                   ELSEIF ( k == 2 )  THEN
4669                      shift_x = 0.5
4670                   ENDIF
4671
4672                   DO  i = 1, ns
4673                      IF( section(i,3) == -1 )  THEN
4674                         netcdf_data(i) = -1.0_wp  ! section averaged along x
4675                      ELSE
4676                         netcdf_data(i) = init_model%origin_x &
4677                                     + cos_ra * ( section(i,3) + shift_x ) * dx
4678                      ENDIF
4679                   ENDDO
4680
4681                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),&
4682                                           netcdf_data, start = (/ 1 /),   &
4683                                           count = (/ ns /) )
4684                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
4685
4686                ENDDO
4687                DEALLOCATE( netcdf_data )
4688!
4689!--             y coordinates
4690                ALLOCATE( netcdf_data(0:ny) )
4691                DO  k = 0, 2
4692!
4693!--                Scalar grid points
4694                   IF ( k == 0 )  THEN
4695                      shift_y = 0.5
4696!
4697!--                u grid points
4698                   ELSEIF ( k == 1 )  THEN
4699                      shift_y = 0.5
4700!
4701!--                v grid points
4702                   ELSEIF ( k == 2 )  THEN
4703                      shift_y = 0.0
4704                   ENDIF
4705
4706                   DO  i = 0, ny
4707                     netcdf_data(i) = init_model%origin_y            &
4708                                    + cos_ra * ( i + shift_y ) * dy
4709                   ENDDO
4710
4711                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),&
4712                                           netcdf_data, start = (/ 1 /),   &
4713                                           count = (/ ny+1 /) )
4714                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
4715
4716                ENDDO
4717                DEALLOCATE( netcdf_data )
4718
4719             ELSE
4720!
4721!--             2D in case of rotation
4722                ALLOCATE( netcdf_data_2d(1:ns,0:ny) )
4723                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
4724                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
4725
4726                DO  k = 0, 2
4727!
4728!--                Scalar grid points
4729                   IF ( k == 0 )  THEN
4730                      shift_x = 0.5 ; shift_y = 0.5
4731!
4732!--                u grid points
4733                   ELSEIF ( k == 1 )  THEN
4734                      shift_x = 0.0 ; shift_y = 0.5
4735!
4736!--                v grid points
4737                   ELSEIF ( k == 2 )  THEN
4738                      shift_x = 0.5 ; shift_y = 0.0
4739                   ENDIF
4740
4741                   DO  j = 0, ny
4742                      DO  i = 1, ns
4743                         IF( section(i,3) == -1 )  THEN
4744                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
4745                         ELSE
4746                            netcdf_data_2d(i,j) = init_model%origin_x          &
4747                                    + cos_ra * ( section(i,3) + shift_x ) * dx &
4748                                    + sin_ra * ( j + shift_y ) * dy
4749                         ENDIF
4750                      ENDDO
4751                   ENDDO
4752
4753                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(k,av),  &
4754                                           netcdf_data_2d, start = (/ 1, 1 /),   &
4755                                           count = (/ ns, ny+1 /) )
4756                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
4757
4758                   DO  j = 0, ny
4759                      DO  i = 1, ns
4760                         IF( section(i,3) == -1 )  THEN
4761                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
4762                         ELSE
4763                            netcdf_data_2d(i,j) = init_model%origin_y          &
4764                                    - sin_ra * ( section(i,3) + shift_x ) * dx &
4765                                    + cos_ra * ( j + shift_y ) * dy
4766                         ENDIF
4767                      ENDDO
4768                   ENDDO
4769
4770                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(k,av),  &
4771                                           netcdf_data_2d, start = (/ 1, 1 /),   &
4772                                           count = (/ ns, ny+1 /) )
4773                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
4774
4775                ENDDO
4776                DEALLOCATE( netcdf_data_2d )
4777             ENDIF
4778!
4779!--          Write lon and lat data
4780             ALLOCATE( lat(1:ns,0:ny) )
4781             ALLOCATE( lon(1:ns,0:ny) )
4782             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
4783             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
4784
4785             DO  k = 0, 2
4786!
4787!--             Scalar grid points
4788                IF ( k == 0 )  THEN
4789                   shift_x = 0.5 ; shift_y = 0.5
4790!
4791!--             u grid points
4792                ELSEIF ( k == 1 )  THEN
4793                   shift_x = 0.0 ; shift_y = 0.5
4794!
4795!--             v grid points
4796                ELSEIF ( k == 2 )  THEN
4797                   shift_x = 0.5 ; shift_y = 0.0
4798                ENDIF
4799
4800                DO  j = 0, ny
4801                   DO  i = 1, ns
4802                      IF( section(i,3) == -1 )  THEN
4803                         lat(i,:) = -90.0_wp   ! section averaged along x
4804                         lon(i,:) = -180.0_wp  ! section averaged along x
4805                      ELSE
4806                         eutm = init_model%origin_x            &
4807                              + cos_ra * ( section(i,3) + shift_x ) * dx  &
4808                              + sin_ra * ( j + shift_y ) * dy
4809                         nutm = init_model%origin_y            &
4810                              - sin_ra * ( section(i,3) + shift_x ) * dx  &
4811                              + cos_ra * ( j + shift_y ) * dy
4812
4813                         CALL  convert_utm_to_geographic( crs_list,          &
4814                                                          eutm, nutm,        &
4815                                                          lon(i,j), lat(i,j) )
4816                      ENDIF
4817                   ENDDO
4818                ENDDO
4819
4820                nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lon_yz(k,av), &
4821                                     lon, start = (/ 1, 1 /),       &
4822                                     count = (/ ns, ny+1 /) )
4823                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
4824
4825                nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_lat_yz(k,av), &
4826                                     lat, start = (/ 1, 1 /),       &
4827                                     count = (/ ns, ny+1 /) )
4828                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
4829             ENDDO
4830
4831             DEALLOCATE( lat )
4832             DEALLOCATE( lon )
4833
4834          ENDIF
4835
4836
4837       CASE ( 'yz_ext' )
4838
4839!
4840!--       Get the list of variables and compare with the actual run.
4841!--       First var_list_old has to be reset, since GET_ATT does not assign
4842!--       trailing blanks.
4843          var_list_old = ' '
4844          nc_stat = NF90_GET_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
4845                                  var_list_old )
4846          CALL netcdf_handle_error( 'netcdf_define_header', 207 )
4847
4848          var_list = ';'
4849          i = 1
4850          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
4851             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
4852                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
4853             ENDIF
4854             i = i + 1
4855          ENDDO
4856
4857          IF ( av == 0 )  THEN
4858             var = '(yz)'
4859          ELSE
4860             var = '(yz_av)'
4861          ENDIF
4862
4863          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
4864             message_string = 'netCDF file for cross-sections ' //           &
4865                              TRIM( var ) // ' from previous run found,' //  &
4866                              '&but this file cannot be extended due to' //  &
4867                              ' variable mismatch.' //                       &
4868                              '&New file is created instead.'
4869             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
4870             extend = .FALSE.
4871             RETURN
4872          ENDIF
4873
4874!
4875!--       Calculate the number of current sections
4876          ns = 1
4877          DO WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
4878             ns = ns + 1
4879          ENDDO
4880          ns = ns - 1
4881
4882!
4883!--       Get and compare the number of vertical cross sections
4884          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'x_yz', id_var_x_yz(av) )
4885          CALL netcdf_handle_error( 'netcdf_define_header', 208 )
4886
4887          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_x_yz(av), &
4888                                           dimids = id_dim_x_yz_old )
4889          CALL netcdf_handle_error( 'netcdf_define_header', 209 )
4890          id_dim_x_yz(av) = id_dim_x_yz_old(1)
4891
4892          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_x_yz(av), &
4893                                            len = ns_old )
4894          CALL netcdf_handle_error( 'netcdf_define_header', 210 )
4895
4896          IF ( ns /= ns_old )  THEN
4897             message_string = 'netCDF file for cross-sections ' //          &
4898                              TRIM( var ) // ' from previous run found,' // &
4899                              '&but this file cannot be extended due to' // &
4900                              ' mismatch in number of' //                   &
4901                              ' cross sections.' //                         &
4902                              '&New file is created instead.'
4903             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
4904             extend = .FALSE.
4905             RETURN
4906          ENDIF
4907
4908!
4909!--       Get and compare the heights of the cross sections
4910          ALLOCATE( netcdf_data(1:ns_old) )
4911
4912          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data )
4913          CALL netcdf_handle_error( 'netcdf_define_header', 211 )
4914
4915          DO  i = 1, ns
4916             IF ( section(i,3) /= -1 )  THEN
4917                IF ( ( ( section(i,3) + 0.5 ) * dx ) /= netcdf_data(i) )  THEN
4918                   message_string = 'netCDF file for cross-sections ' //       &
4919                              TRIM( var ) // ' from previous run found,' //    &
4920                              ' but this file cannot be extended' //           &
4921                              ' due to mismatch in cross' //                   &
4922                              ' section levels.' //                            &
4923                              ' New file is created instead.'
4924                   CALL message( 'define_netcdf_header', 'PA0251',             &
4925                                                                 0, 1, 0, 6, 0 )
4926                   extend = .FALSE.
4927                   RETURN
4928                ENDIF
4929             ELSE
4930                IF ( -1.0_wp /= netcdf_data(i) )  THEN
4931                   message_string = 'netCDF file for cross-sections ' //       &
4932                              TRIM( var ) // ' from previous run found,' //    &
4933                              ' but this file cannot be extended' //           &
4934                              ' due to mismatch in cross' //                   &
4935                              ' section levels.' //                            &
4936                              ' New file is created instead.'
4937                   CALL message( 'define_netcdf_header', 'PA0251',             &
4938                                                                 0, 1, 0, 6, 0 )
4939                   extend = .FALSE.
4940                   RETURN
4941                ENDIF
4942             ENDIF
4943          ENDDO
4944
4945          DEALLOCATE( netcdf_data )
4946
4947!
4948!--       Get the id of the time coordinate (unlimited coordinate) and its
4949!--       last index on the file. The next time level is pl2d..count+1.
4950!--       The current time must be larger than the last output time
4951!--       on the file.
4952          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'time', id_var_time_yz(av) )
4953          CALL netcdf_handle_error( 'netcdf_define_header', 212 )
4954
4955          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_time_yz(av), &
4956                                           dimids = id_dim_time_old )
4957          CALL netcdf_handle_error( 'netcdf_define_header', 213 )
4958          id_dim_time_yz(av) = id_dim_time_old(1)
4959
4960          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_time_yz(av), &
4961                                            len = ntime_count )
4962          CALL netcdf_handle_error( 'netcdf_define_header', 214 )
4963
4964!
4965!--       For non-parallel output use the last output time level of the netcdf
4966!--       file because the time dimension is unlimited. In case of parallel
4967!--       output the variable ntime_count could get the value of 9*10E36 because
4968!--       the time dimension is limited.
4969          IF ( netcdf_data_format < 5 ) do2d_yz_time_count(av) = ntime_count
4970
4971          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_time_yz(av),           &
4972                                  last_time_coordinate,                        &
4973                                  start = (/ do2d_yz_time_count(av) /),        &
4974                                  count = (/ 1 /) )
4975          CALL netcdf_handle_error( 'netcdf_define_header', 215 )
4976
4977          IF ( last_time_coordinate(1) >= simulated_time )  THEN
4978             message_string = 'netCDF file for cross sections ' //             &
4979                              TRIM( var ) // ' from previous run found,' //    &
4980                              '&but this file cannot be extended becaus' //    &
4981                              'e the current output time' //                   &
4982                              '&is less or equal than the last output t' //    &
4983                              'ime on this file.' //                           &
4984                              '&New file is created instead.'
4985             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
4986             do2d_yz_time_count(av) = 0
4987             extend = .FALSE.
4988             RETURN
4989          ENDIF
4990
4991          IF ( netcdf_data_format > 4 )  THEN
4992!
4993!--          Check if the needed number of output time levels is increased
4994!--          compared to the number of time levels in the existing file.
4995             IF ( ntdim_2d_yz(av) > ntime_count )  THEN
4996                message_string = 'netCDF file for cross sections ' //          &
4997                                 TRIM( var ) // ' from previous run found,' // &
4998                                 '&but this file cannot be extended becaus' // &
4999                                 'e the number of output time levels has b' // &
5000                                 'een increased compared to the previous s' // &
5001                                 'imulation.' //                               &
5002                                 '&New file is created instead.'
5003                CALL message( 'define_netcdf_header', 'PA0391', 0, 1, 0, 6, 0 )
5004                do2d_yz_time_count(av) = 0
5005                extend = .FALSE.
5006!
5007!--             Recalculate the needed time levels for the new file.
5008                IF ( av == 0 )  THEN
5009                   ntdim_2d_yz(0) = CEILING(                            &
5010                           ( end_time - MAX( skip_time_do2d_yz,         &
5011                                             simulated_time_at_begin )  &
5012                           ) / dt_do2d_yz )
5013                   IF ( do2d_at_begin )  ntdim_2d_yz(0) = ntdim_2d_yz(0) + 1
5014                ELSE
5015                   ntdim_2d_yz(1) = CEILING(                            &
5016                           ( end_time - MAX( skip_time_data_output_av,  &
5017                                             simulated_time_at_begin )  &
5018                           ) / dt_data_output_av )
5019                ENDIF
5020                RETURN
5021             ENDIF
5022          ENDIF
5023
5024!
5025!--       Dataset seems to be extendable.
5026!--       Now get the variable ids.
5027          i = 1
5028          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
5029             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
5030                nc_stat = NF90_INQ_VARID( id_set_yz(av), do2d(av,i), &
5031                                          id_var_do2d(av,i) )
5032                CALL netcdf_handle_error( 'netcdf_define_header', 216 )
5033#if defined( __netcdf4_parallel )
5034!
5035!--             Set independent io operations for parallel io. Collective io
5036!--             is only allowed in case of a 1d-decomposition along y, because
5037!--             otherwise, not all PEs have output data.
5038                IF ( netcdf_data_format > 4 )  THEN
5039                   IF ( npex == 1 )  THEN
5040                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
5041                                                     id_var_do2d(av,i), &
5042                                                     NF90_COLLECTIVE )
5043                   ELSE
5044!
5045!--                   Test simulations showed that the output of cross sections
5046!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
5047!--                   faster than the output by the first row of PEs in
5048!--                   y-direction using NF90_INDEPENDENT.
5049                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
5050                                                     id_var_do2d(av,i), &
5051                                                     NF90_COLLECTIVE )
5052!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
5053!                                                     id_var_do2d(av,i), &
5054!                                                     NF90_INDEPENDENT )
5055                   ENDIF
5056                   CALL netcdf_handle_error( 'netcdf_define_header', 450 )
5057                ENDIF
5058#endif
5059             ENDIF
5060             i = i + 1
5061          ENDDO
5062
5063!
5064!--       Update the title attribute on file
5065!--       In order to avoid 'data mode' errors if updated attributes are larger
5066!--       than their original size, NF90_PUT_ATT is called in 'define mode'
5067!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
5068!--       performance loss due to data copying; an alternative strategy would be
5069!--       to ensure equal attribute size in a job chain. Maybe revise later.
5070          IF ( av == 0 )  THEN
5071             time_average_text = ' '
5072          ELSE
5073             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
5074                                                            averaging_interval
5075          ENDIF
5076          nc_stat = NF90_REDEF( id_set_yz(av) )
5077          CALL netcdf_handle_error( 'netcdf_define_header', 435 )
5078          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title',         &
5079                                  TRIM( run_description_header ) //            &
5080                                  TRIM( time_average_text ) )
5081          CALL netcdf_handle_error( 'netcdf_define_header', 217 )
5082          nc_stat = NF90_ENDDEF( id_set_yz(av) )
5083          CALL netcdf_handle_error( 'netcdf_define_header', 436 )
5084          message_string = 'netCDF file for cross-sections ' //                &
5085                            TRIM( var ) // ' from previous run found.' //      &
5086                           '&This file will be extended.'
5087          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
5088
5089
5090       CASE ( 'pr_new' )
5091
5092!
5093!--       Define some global attributes of the dataset
5094
5095          IF ( averaging_interval_pr /= 0.0_wp )  THEN
5096             CALL netcdf_create_global_atts( id_set_pr, 'podsprav', TRIM( run_description_header ), 451 )
5097             WRITE ( time_average_text,'(F7.1,'' s avg'')' ) averaging_interval_pr
5098             nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'time_avg',       &
5099                                     TRIM( time_average_text ) )
5100          ELSE
5101             CALL netcdf_create_global_atts( id_set_pr, 'podspr', TRIM( run_description_header ), 451 )
5102          ENDIF
5103          CALL netcdf_handle_error( 'netcdf_define_header', 219 )
5104!
5105!--       Write number of columns and rows of coordinate systems to be plotted
5106!--       on one page to the netcdf header.
5107!--       This information can be used by palmplot.
5108          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
5109                                  'no_rows',                                  &
5110                                  profile_rows )
5111          CALL netcdf_handle_error( 'netcdf_define_header', 519 )
5112
5113          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
5114                                  'no_columns',                               &
5115                                  profile_columns )
5116          CALL netcdf_handle_error( 'netcdf_define_header', 520 )
5117
5118
5119          cross_profiles_adj  = ADJUSTL( cross_profiles )
5120          cross_profiles_numb = 999999
5121          cross_profiles_char = ''
5122
5123!
5124!--       Each profile defined in cross_profiles is written to an array
5125!--       (cross_profiles_char). The number of the respective coordinate
5126!--       system is assigned in a second array (cross_profiles_numb).
5127          k = 1
5128
5129          DO  i = 1, crmax
5130
5131             IF ( TRIM( cross_profiles_adj(i) ) == ' ' )  EXIT
5132             delim_old = 0
5133
5134             DO   j = 1, crmax
5135                delim = INDEX( cross_profiles_adj(i)(delim_old+1:), ' ' )
5136                IF ( delim == 1 )  EXIT
5137                kk = MIN( crmax, k )
5138                cross_profiles_char(kk) = cross_profiles_adj(i)(delim_old+1: &
5139                                                              delim_old+delim-1)
5140                cross_profiles_numb(kk) = i
5141                k = k + 1
5142                cross_profiles_maxi  = i
5143                delim_old = delim_old + delim
5144             ENDDO
5145
5146          ENDDO
5147
5148          cross_profiles_count = MIN( crmax, k-1 )
5149!
5150!--       Check if all profiles defined in cross_profiles are defined in
5151!--       data_output_pr. If not, they will be skipped.
5152          DO  i = 1, cross_profiles_count
5153             DO  j = 1, dopr_n
5154
5155                IF ( TRIM(cross_profiles_char(i)) == TRIM(data_output_pr(j)) ) &
5156                THEN
5157                   EXIT
5158                ENDIF
5159
5160                IF ( j == dopr_n )  THEN
5161                   cross_profiles_numb(i) = 999999
5162                ENDIF
5163
5164             ENDDO
5165          ENDDO
5166
5167          DO i = 1, crmax
5168             IF ( cross_profiles_numb(i) == 999999 ) THEN
5169                DO j = i + 1, crmax
5170                   IF ( cross_profiles_numb(j) /= 999999 ) THEN
5171                      cross_profiles_char(i) = cross_profiles_char(j)
5172                      cross_profiles_numb(i) = cross_profiles_numb(j)
5173                      cross_profiles_numb(j) = 999999
5174                      EXIT
5175                   ENDIF
5176                ENDDO
5177             ENDIF
5178          ENDDO
5179
5180          DO i = 1, crmax-1
5181             IF ( cross_profiles_numb(i + 1) == 999999 ) THEN
5182                cross_profiles_count = i
5183                EXIT
5184             ENDIF
5185          ENDDO
5186!
5187!--       Check if all profiles defined in data_output_pr are defined in
5188!--       cross_profiles. If not, they will be added to cross_profiles.
5189          DO  i = 1, dopr_n
5190             DO  j = 1, cross_profiles_count
5191
5192                IF ( TRIM(cross_profiles_char(j)) == TRIM(data_output_pr(i)))  &
5193                THEN
5194                   EXIT
5195                ENDIF
5196
5197                IF (( j == cross_profiles_count ) .AND.                        &
5198                    ( cross_profiles_count <= crmax - 1))  THEN
5199                   cross_profiles_count = cross_profiles_count + 1
5200                   cross_profiles_maxi  = cross_profiles_maxi  + 1
5201                   cross_profiles_char(MIN( crmax, cross_profiles_count )) =   &
5202                                                      TRIM( data_output_pr(i) )
5203                   cross_profiles_numb(MIN( crmax, cross_profiles_count )) =   &
5204                                                      cross_profiles_maxi
5205                ENDIF
5206
5207             ENDDO
5208          ENDDO
5209
5210          IF ( cross_profiles_count >= crmax )  THEN
5211             message_string = 'It is not allowed to arrange more than '        &
5212                              // '100 profiles with & cross_profiles. Apart'   &
5213                              // ' from that, all profiles are saved & to '    &
5214                              // 'the netCDF file.'
5215             CALL message( 'define_netcdf_header', 'PA0354', 0, 0, 0, 6, 0 )
5216          ENDIF
5217
5218!
5219!--       Writing cross_profiles to netcdf header. This information can be
5220!--       used by palmplot. Each profile is separated by ",", each cross is
5221!--       separated by ";".
5222          char_cross_profiles = ';'
5223          id_last = 1
5224          cross_profiles_count = MIN( cross_profiles_count, crmax )
5225
5226          DO  i = 1, cross_profiles_count
5227
5228             IF ( cross_profiles_numb(i) /= 999999 )  THEN
5229                IF ( TRIM( char_cross_profiles ) == ';' )  THEN
5230                   char_cross_profiles = TRIM( char_cross_profiles ) // &
5231                                         TRIM( cross_profiles_char(i) )
5232                ELSEIF ( id_last == cross_profiles_numb(i) )  THEN
5233                   char_cross_profiles = TRIM( char_cross_profiles ) // &
5234                                         ',' // TRIM( cross_profiles_char(i) )
5235                ELSE
5236                   char_cross_profiles = TRIM( char_cross_profiles ) // &
5237                                         ';' // TRIM( cross_profiles_char(i) )
5238                ENDIF
5239                id_last = cross_profiles_numb(i)
5240             ENDIF
5241
5242          ENDDO
5243
5244          char_cross_profiles = TRIM( char_cross_profiles ) // ';'
5245
5246          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',   &
5247                                  TRIM( char_cross_profiles ) )
5248          CALL netcdf_handle_error( 'netcdf_define_header', 521 )
5249
5250!
5251!--       Define time coordinate for profiles (unlimited dimension)
5252          CALL netcdf_create_dim( id_set_pr, 'time', NF90_UNLIMITED,           &
5253                                  id_dim_time_pr, 220 )
5254          CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /), 'time',     &
5255                                  NF90_DOUBLE, id_var_time_pr, 'seconds', 'time',  &
5256                                  221, 222, 000 )
5257          CALL netcdf_create_att( id_set_pr, id_var_time_pr, 'standard_name', 'time', 000)
5258          CALL netcdf_create_att( id_set_pr, id_var_time_pr, 'axis', 'T', 000)
5259!
5260!--       Define the variables
5261          var_list = ';'
5262          DO  i = 1, dopr_n
5263
5264             IF ( statistic_regions == 0 )  THEN
5265
5266!
5267!--             Define the z-axes (each variable gets its own z-axis)
5268                CALL netcdf_create_dim( id_set_pr,                             &
5269                                        'z' // TRIM( data_output_pr(i) ),      &
5270                                        nzt+2-nzb, id_dim_z_pr(i,0), 223 )
5271                CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0) /),     &
5272                                        'z' // TRIM( data_output_pr(i) ),      &
5273                                       NF90_DOUBLE, id_var_z_pr(i,0),          &
5274                                       'meters', '', 224, 225, 000 )
5275!
5276!--             Define the variable
5277                CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,0),        &
5278                                        id_dim_time_pr /), data_output_pr(i),  &
5279                                        nc_precision(5), id_var_dopr(i,0),     &
5280                                        TRIM( dopr_unit(i) ),                  &
5281                                        TRIM( data_output_pr(i) ), 226, 227,   &
5282                                        228 )
5283
5284                var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) //  ';'
5285
5286             ELSE
5287!
5288!--             If statistic regions are defined, add suffix _SR+#SR to the
5289!--             names
5290                DO  j = 0, statistic_regions
5291                   WRITE ( suffix, '(''_'',I2.2)' )  j
5292
5293!
5294!--                Define the z-axes (each variable gets it own z-axis)
5295                   CALL netcdf_create_dim( id_set_pr, 'z' //                   &
5296                                           TRIM(data_output_pr(i)) // suffix,  &
5297                                           nzt+2-nzb, id_dim_z_pr(i,j), 229 )
5298                   CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j) /),  &
5299                                           'z' // TRIM(data_output_pr(i)) //   &
5300                                           suffix, NF90_DOUBLE,                &
5301                                           id_var_z_pr(i,j), 'meters', '',     &
5302                                           230, 231, 000 )
5303!
5304!--                Define the variable
5305                   CALL netcdf_create_var( id_set_pr, (/ id_dim_z_pr(i,j),     &
5306                                           id_dim_time_pr /),                  &
5307                                           TRIM(data_output_pr(i)) // suffix,  &
5308                                           nc_precision(5), id_var_dopr(i,j),  &
5309                                           TRIM( dopr_unit(i) ),               &
5310                                           TRIM( data_output_pr(i) ) //        &
5311                                           ' SR ', 232, 233, 234 )
5312
5313                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
5314                              suffix // ';'
5315
5316                ENDDO
5317
5318             ENDIF
5319
5320          ENDDO
5321
5322!
5323!--       Write the list of variables as global attribute (this is used by
5324!--       restart runs)
5325          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', var_list )
5326          CALL netcdf_handle_error( 'netcdf_define_header', 235 )
5327
5328!
5329!--       Define normalization variables (as time series)
5330          DO  i = 1, dopr_norm_num
5331
5332             CALL netcdf_create_var( id_set_pr, (/ id_dim_time_pr /),          &
5333                                     'NORM_' // TRIM( dopr_norm_names(i) ),    &
5334                                     nc_precision(5), id_var_norm_dopr(i),     &
5335                                     '', TRIM( dopr_norm_longnames(i) ), 236,  &
5336                                     000, 237 )
5337
5338          ENDDO
5339
5340!
5341!--       Leave netCDF define mode
5342          nc_stat = NF90_ENDDEF( id_set_pr )
5343          CALL netcdf_handle_error( 'netcdf_define_header', 238 )
5344
5345!
5346!--       Write z-axes data
5347          DO  i = 1, dopr_n
5348             DO  j = 0, statistic_regions
5349
5350                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_z_pr(i,j),      &
5351                                        hom(nzb:nzt+1,2,dopr_index(i),0), &
5352                                        start = (/ 1 /),                  &
5353                                        count = (/ nzt-nzb+2 /) )
5354                CALL netcdf_handle_error( 'netcdf_define_header', 239 )
5355
5356             ENDDO
5357          ENDDO
5358
5359
5360       CASE ( 'pr_ext' )
5361
5362!
5363!--       Get the list of variables and compare with the actual run.
5364!--       First var_list_old has to be reset, since GET_ATT does not assign
5365!--       trailing blanks.
5366          var_list_old = ' '
5367          nc_stat = NF90_GET_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', &
5368                                  var_list_old )
5369          CALL netcdf_handle_error( 'netcdf_define_header', 240 )
5370
5371          var_list = ';'
5372          DO  i = 1, dopr_n
5373
5374             IF ( statistic_regions == 0 )  THEN
5375                var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // ';'
5376             ELSE
5377                DO  j = 0, statistic_regions
5378                   WRITE ( suffix, '(''_'',I2.2)' )  j
5379                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
5380                              suffix // ';'
5381                ENDDO
5382             ENDIF
5383
5384          ENDDO
5385
5386          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
5387             message_string = 'netCDF file for vertical profiles ' //          &
5388                              'from previous run found,' //                    &
5389                              '&but this file cannot be extended due to' //    &
5390                              ' variable mismatch.' //                         &
5391                              '&New file is created instead.'
5392             CALL message( 'define_netcdf_header', 'PA0254', 0, 1, 0, 6, 0 )
5393             extend = .FALSE.
5394             RETURN
5395          ENDIF
5396
5397!
5398!--       Get the id of the time coordinate (unlimited coordinate) and its
5399!--       last index on the file. The next time level is dopr..count+1.
5400!--       The current time must be larger than the last output time
5401!--       on the file.
5402          nc_stat = NF90_INQ_VARID( id_set_pr, 'time', id_var_time_pr )
5403          CALL netcdf_handle_error( 'netcdf_define_header', 241 )
5404
5405          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pr, id_var_time_pr, &
5406                                           dimids = id_dim_time_old )
5407          CALL netcdf_handle_error( 'netcdf_define_header', 242 )
5408          id_dim_time_pr = id_dim_time_old(1)
5409
5410          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pr, id_dim_time_pr, &
5411                                            len = dopr_time_count )
5412          CALL netcdf_handle_error( 'netcdf_define_header', 243 )
5413
5414          nc_stat = NF90_GET_VAR( id_set_pr, id_var_time_pr,        &
5415                                  last_time_coordinate,             &
5416                                  start = (/ dopr_time_count /), &
5417                                  count = (/ 1 /) )
5418          CALL netcdf_handle_error( 'netcdf_define_header', 244 )
5419
5420          IF ( last_time_coordinate(1) >= simulated_time )  THEN
5421             message_string = 'netCDF file for vertical profiles ' //          &
5422                              'from previous run found,' //                    &
5423                              '&but this file cannot be extended becaus' //    &
5424                              'e the current output time' //                   &
5425                              '&is less or equal than the last output t' //    &
5426                              'ime on this file.' //                           &
5427                              '&New file is created instead.'
5428             CALL message( 'define_netcdf_header', 'PA0255', 0, 1, 0, 6, 0 )
5429             dopr_time_count = 0
5430             extend = .FALSE.
5431             RETURN
5432          ENDIF
5433
5434!
5435!--       Dataset seems to be extendable.
5436!--       Now get the variable ids.
5437          i = 1
5438          DO  i = 1, dopr_n
5439
5440             IF ( statistic_regions == 0 )  THEN
5441                nc_stat = NF90_INQ_VARID( id_set_pr, data_output_pr(i),        &
5442                                          id_var_dopr(i,0) )
5443                CALL netcdf_handle_error( 'netcdf_define_header', 245 )
5444             ELSE
5445                DO  j = 0, statistic_regions
5446                   WRITE ( suffix, '(''_'',I2.2)' )  j
5447                   netcdf_var_name = TRIM( data_output_pr(i) ) // suffix
5448                   nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name,       &
5449                                             id_var_dopr(i,j) )
5450                   CALL netcdf_handle_error( 'netcdf_define_header', 246 )
5451                ENDDO
5452             ENDIF
5453
5454          ENDDO
5455
5456!
5457!--       Get ids of the normalization variables
5458          DO  i = 1, dopr_norm_num
5459             nc_stat = NF90_INQ_VARID( id_set_pr,                             &
5460                                       'NORM_' // TRIM( dopr_norm_names(i) ), &
5461                                       id_var_norm_dopr(i) )
5462             CALL netcdf_handle_error( 'netcdf_define_header', 247 )
5463          ENDDO
5464
5465!
5466!--       Update the title attribute on file
5467!--       In order to avoid 'data mode' errors if updated attributes are larger
5468!--       than their original size, NF90_PUT_ATT is called in 'define mode'
5469!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
5470!--       performance loss due to data copying; an alternative strategy would be
5471!--       to ensure equal attribute size in a job chain. Maybe revise later.
5472          IF ( averaging_interval_pr == 0.0_wp )  THEN
5473             time_average_text = ' '
5474          ELSE
5475             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
5476                                                            averaging_interval_pr
5477          ENDIF
5478          nc_stat = NF90_REDEF( id_set_pr )
5479          CALL netcdf_handle_error( 'netcdf_define_header', 437 )
5480          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title',             &
5481                                  TRIM( run_description_header ) //            &
5482                                  TRIM( time_average_text ) )
5483          CALL netcdf_handle_error( 'netcdf_define_header', 248 )
5484
5485          nc_stat = NF90_ENDDEF( id_set_pr )
5486          CALL netcdf_handle_error( 'netcdf_define_header', 438 )
5487          message_string = 'netCDF file for vertical profiles ' //             &
5488                           'from previous run found.' //                       &
5489                           '&This file will be extended.'
5490          CALL message( 'define_netcdf_header', 'PA0256', 0, 0, 0, 6, 0 )
5491
5492
5493       CASE ( 'ts_new' )
5494
5495!
5496!--       Define some global attributes of the dataset
5497          CALL netcdf_create_global_atts( id_set_ts, 'podsts', TRIM(run_description_header), 329 )
5498
5499          ! nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title',             &
5500          !                         TRIM( run_description_header ) )
5501          ! CALL netcdf_handle_error( 'netcdf_define_header', 249 )
5502
5503!
5504!--       Define time coordinate for time series (unlimited dimension)
5505          CALL netcdf_create_dim( id_set_ts, 'time', NF90_UNLIMITED,           &
5506                                  id_dim_time_ts, 250 )
5507          CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /), 'time',     &
5508                                  NF90_DOUBLE, id_var_time_ts, 'seconds', 'time',  &
5509                                  251, 252, 000 )
5510          CALL netcdf_create_att( id_set_ts, id_var_time_ts, 'standard_name', 'time', 000)
5511          CALL netcdf_create_att( id_set_ts, id_var_time_ts, 'axis', 'T', 000)
5512!
5513!--       Define the variables
5514          var_list = ';'
5515          DO  i = 1, dots_num
5516
5517             IF ( statistic_regions == 0 )  THEN
5518
5519                CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /),       &
5520                                        dots_label(i), nc_precision(6),        &
5521                                        id_var_dots(i,0),                      &
5522                                        TRIM( dots_unit(i) ),                  &
5523                                        TRIM( dots_label(i) ), 253, 254, 255 )
5524
5525                var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // ';'
5526
5527             ELSE
5528!
5529!--             If statistic regions are defined, add suffix _SR+#SR to the
5530!--             names
5531                DO  j = 0, statistic_regions
5532                   WRITE ( suffix, '(''_'',I2.2)' )  j
5533
5534                   CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /),    &
5535                                           TRIM( dots_label(i) ) // suffix,    &
5536                                           nc_precision(6), id_var_dots(i,j),  &
5537                                           TRIM( dots_unit(i) ),               &
5538                                           TRIM( dots_label(i) ) // ' SR ' //  &
5539                                           suffix(2:2), 256, 257, 347)
5540
5541                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // &
5542                              suffix // ';'
5543
5544                ENDDO
5545
5546             ENDIF
5547
5548          ENDDO
5549
5550!
5551!--       Write the list of variables as global attribute (this is used by
5552!--       restart runs)
5553          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', var_list )
5554          CALL netcdf_handle_error( 'netcdf_define_header', 258 )
5555
5556!
5557!--       Leave netCDF define mode
5558          nc_stat = NF90_ENDDEF( id_set_ts )
5559          CALL netcdf_handle_error( 'netcdf_define_header', 259 )
5560
5561
5562       CASE ( 'ts_ext' )
5563
5564!
5565!--       Get the list of variables and compare with the actual run.
5566!--       First var_list_old has to be reset, since GET_ATT does not assign
5567!--       trailing blanks.
5568          var_list_old = ' '
5569          nc_stat = NF90_GET_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', &
5570                                  var_list_old )
5571          CALL netcdf_handle_error( 'netcdf_define_header', 260 )
5572
5573          var_list = ';'
5574          i = 1
5575          DO  i = 1, dots_num
5576
5577             IF ( statistic_regions == 0 )  THEN
5578                var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // ';'
5579             ELSE
5580                DO  j = 0, statistic_regions
5581                   WRITE ( suffix, '(''_'',I2.2)' )  j
5582                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) //     &
5583                              suffix // ';'
5584                ENDDO
5585             ENDIF
5586
5587          ENDDO
5588
5589          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
5590             message_string = 'netCDF file for time series ' //                &
5591                              'from previous run found,' //                    &
5592                              '&but this file cannot be extended due to' //    &
5593                              ' variable mismatch.' //                         &
5594                              '&New file is created instead.'
5595             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
5596             extend = .FALSE.
5597             RETURN
5598          ENDIF
5599
5600!
5601!--       Get the id of the time coordinate (unlimited coordinate) and its
5602!--       last index on the file. The next time level is dots..count+1.
5603!--       The current time must be larger than the last output time
5604!--       on the file.
5605          nc_stat = NF90_INQ_VARID( id_set_ts, 'time', id_var_time_ts )
5606          CALL netcdf_handle_error( 'netcdf_define_header', 261 )
5607
5608          nc_stat = NF90_INQUIRE_VARIABLE( id_set_ts, id_var_time_ts,          &
5609                                           dimids = id_dim_time_old )
5610          CALL netcdf_handle_error( 'netcdf_define_header', 262 )
5611          id_dim_time_ts = id_dim_time_old(1)
5612
5613          nc_stat = NF90_INQUIRE_DIMENSION( id_set_ts, id_dim_time_ts,         &
5614                                            len = dots_time_count )
5615          CALL netcdf_handle_error( 'netcdf_define_header', 263 )
5616
5617          nc_stat = NF90_GET_VAR( id_set_ts, id_var_time_ts,                   &
5618                                  last_time_coordinate,                        &
5619                                  start = (/ dots_time_count /),               &
5620                                  count = (/ 1 /) )
5621          CALL netcdf_handle_error( 'netcdf_define_header', 264 )
5622
5623          IF ( last_time_coordinate(1) >= simulated_time )  THEN
5624             message_string = 'netCDF file for time series ' //                &
5625                              'from previous run found,' //                    &
5626                              '&but this file cannot be extended becaus' //    &
5627                              'e the current output time' //                   &
5628                              '&is less or equal than the last output t' //    &
5629                              'ime on this file.' //                           &
5630                              '&New file is created instead.'
5631             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
5632             dots_time_count = 0
5633             extend = .FALSE.
5634             RETURN
5635          ENDIF
5636
5637!
5638!--       Dataset seems to be extendable.
5639!--       Now get the variable ids
5640          i = 1
5641          DO  i = 1, dots_num
5642
5643             IF ( statistic_regions == 0 )  THEN
5644                nc_stat = NF90_INQ_VARID( id_set_ts, dots_label(i), &
5645                                          id_var_dots(i,0) )
5646                CALL netcdf_handle_error( 'netcdf_define_header', 265 )
5647             ELSE
5648                DO  j = 0, statistic_regions
5649                   WRITE ( suffix, '(''_'',I2.2)' )  j
5650                   netcdf_var_name = TRIM( dots_label(i) ) // suffix
5651                   nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, &
5652                                             id_var_dots(i,j) )
5653                   CALL netcdf_handle_error( 'netcdf_define_header', 266 )
5654                ENDDO
5655             ENDIF
5656
5657          ENDDO
5658
5659!
5660!--       Update the title attribute on file
5661!--       In order to avoid 'data mode' errors if updated attributes are larger
5662!--       than their original size, NF90_PUT_ATT is called in 'define mode'
5663!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
5664!--       performance loss due to data copying; an alternative strategy would be
5665!--       to ensure equal attribute size in a job chain. Maybe revise later.
5666          nc_stat = NF90_REDEF( id_set_ts )
5667          CALL netcdf_handle_error( 'netcdf_define_header', 439 )
5668          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title',             &
5669                                  TRIM( run_description_header ) )
5670          CALL netcdf_handle_error( 'netcdf_define_header', 267 )
5671          nc_stat = NF90_ENDDEF( id_set_ts )
5672          CALL netcdf_handle_error( 'netcdf_define_header', 440 )
5673          message_string = 'netCDF file for time series ' //                   &
5674                           'from previous run found.' //                       &
5675                           '&This file will be extended.'
5676          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
5677
5678
5679       CASE ( 'sp_new' )
5680
5681!
5682!--       Define some global attributes of the dataset
5683          IF ( averaging_interval_sp /= 0.0_wp )  THEN
5684             WRITE (time_average_text,'('', '',F7.1,'' s average'')')          &
5685                                                            averaging_interval_sp
5686             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',          &
5687                                     TRIM( run_description_header ) //         &
5688                                     TRIM( time_average_text ) )
5689             CALL netcdf_handle_error( 'netcdf_define_header', 268 )
5690
5691             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
5692             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', &
5693                                     TRIM( time_average_text ) )
5694          ELSE
5695             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title', &
5696                                     TRIM( run_description_header ) )
5697          ENDIF
5698          CALL netcdf_handle_error( 'netcdf_define_header', 269 )
5699
5700!
5701!--       Define time coordinate for spectra (unlimited dimension)
5702          CALL netcdf_create_dim( id_set_sp, 'time', NF90_UNLIMITED,           &
5703                                  id_dim_time_sp, 270 )
5704          CALL netcdf_create_var( id_set_sp, (/ id_dim_time_sp /), 'time',     &
5705                                  NF90_DOUBLE, id_var_time_sp, 'seconds', 'time',  &
5706                                  271, 272, 000 )
5707          CALL netcdf_create_att( id_set_sp, id_var_time_sp, 'standard_name', 'time', 000)
5708          CALL netcdf_create_att( id_set_sp, id_var_time_sp, 'axis', 'T', 000)
5709!
5710!--       Define the spatial dimensions and coordinates for spectra.
5711!--       First, determine the number of vertical levels for which spectra
5712!--       are to be output.
5713          ns = 1
5714          DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
5715             ns = ns + 1
5716          ENDDO
5717          ns = ns - 1
5718
5719!
5720!--       Define vertical coordinate grid (zu grid)
5721          CALL netcdf_create_dim( id_set_sp, 'zu_sp', ns, id_dim_zu_sp, 273 )
5722          CALL netcdf_create_var( id_set_sp, (/ id_dim_zu_sp /), 'zu_sp',      &
5723                                  NF90_DOUBLE, id_var_zu_sp, 'meters', '',     &
5724                                  274, 275, 000 )
5725!
5726!--       Define vertical coordinate grid (zw grid)
5727          CALL netcdf_create_dim( id_set_sp, 'zw_sp', ns, id_dim_zw_sp, 276 )
5728          CALL netcdf_create_var( id_set_sp, (/ id_dim_zw_sp /), 'zw_sp',      &
5729                                  NF90_DOUBLE, id_var_zw_sp, 'meters', '',     &
5730                                  277, 278, 000 )
5731!
5732!--       Define x-axis
5733          CALL netcdf_create_dim( id_set_sp, 'k_x', nx/2, id_dim_x_sp, 279 )
5734          CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp /), 'k_x',         &
5735                                  NF90_DOUBLE, id_var_x_sp, 'm-1', '', 280,    &
5736                                  281, 000 )
5737!
5738!--       Define y-axis
5739          CALL netcdf_create_dim( id_set_sp, 'k_y', ny/2, id_dim_y_sp, 282 )
5740          CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp /), 'k_y',         &
5741                                  NF90_DOUBLE, id_var_y_sp, 'm-1', '', 283,    &
5742                                  284, 000 )
5743!
5744!--       Define the variables
5745          var_list = ';'
5746          i = 1
5747          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
5748!
5749!--          First check for the vertical grid
5750             found = .FALSE.
5751             SELECT CASE ( data_output_sp(i) )
5752!
5753!--             Most variables are defined on the zu levels
5754                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',   &
5755                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
5756                       'rho_sea_water', 's', 'sa', &
5757                       'theta', 'thetal', 'thetav', 'u', 'v' )
5758
5759                   grid_z = 'zu'
5760!
5761!--             zw levels
5762                CASE ( 'w' )
5763
5764                   grid_z = 'zw'
5765
5766                CASE DEFAULT
5767!
5768!--                Check for user-defined quantities (found, grid_x and grid_y
5769!--                are dummies)
5770                   IF ( user_module_enabled )  THEN
5771                      CALL user_define_netcdf_grid( data_output_sp(i), found,  &
5772                                                    grid_x, grid_y, grid_z )
5773                   ENDIF
5774
5775             END SELECT
5776
5777             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
5778
5779!
5780!--             Define the variable
5781                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
5782                IF ( TRIM( grid_z ) == 'zw' )  THEN
5783                   CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp,          &
5784                                           id_dim_zw_sp, id_dim_time_sp /),    &
5785                                           netcdf_var_name, nc_precision(7),   &
5786                                           id_var_dospx(i), 'unknown',         &
5787                                           netcdf_var_name, 285, 286, 287 )
5788                ELSE
5789                   CALL netcdf_create_var( id_set_sp, (/ id_dim_x_sp,          &
5790                                           id_dim_zu_sp, id_dim_time_sp /),    &
5791                                           netcdf_var_name, nc_precision(7),   &
5792                                           id_var_dospx(i), 'unknown',         &
5793                                           netcdf_var_name, 285, 286, 287 )
5794                ENDIF
5795
5796                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
5797
5798             ENDIF
5799
5800             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
5801
5802!
5803!--             Define the variable
5804                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
5805                IF ( TRIM( grid_z ) == 'zw' )  THEN
5806                   CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp,          &
5807                                           id_dim_zw_sp, id_dim_time_sp /),    &
5808                                           netcdf_var_name, nc_precision(7),   &
5809                                           id_var_dospy(i), 'unknown',         &
5810                                           netcdf_var_name, 288, 289, 290 )
5811                ELSE
5812                   CALL netcdf_create_var( id_set_sp, (/ id_dim_y_sp,          &
5813                                           id_dim_zu_sp, id_dim_time_sp /),    &
5814                                           netcdf_var_name, nc_precision(7),   &
5815                                           id_var_dospy(i), 'unknown',         &
5816                                           netcdf_var_name, 288, 289, 290 )
5817                ENDIF
5818
5819                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
5820
5821             ENDIF
5822
5823             i = i + 1
5824
5825          ENDDO
5826
5827!
5828!--       Write the list of variables as global attribute (this is used by
5829!--       restart runs)
5830          nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', var_list )
5831          CALL netcdf_handle_error( 'netcdf_define_header', 291 )
5832
5833!
5834!--       Leave netCDF define mode
5835          nc_stat = NF90_ENDDEF( id_set_sp )
5836          CALL netcdf_handle_error( 'netcdf_define_header', 292 )
5837
5838!
5839!--       Write axis data: zu_sp, zw_sp, k_x, k_y
5840          ALLOCATE( netcdf_data(1:ns) )
5841
5842!
5843!--       Write zu data
5844          netcdf_data(1:ns) = zu( comp_spectra_level(1:ns) )
5845          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zu_sp, netcdf_data, &
5846                                  start = (/ 1 /), count = (/ ns /) )
5847          CALL netcdf_handle_error( 'netcdf_define_header', 293 )
5848
5849!
5850!--       Write zw data
5851          netcdf_data(1:ns) = zw( comp_spectra_level(1:ns) )
5852          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zw_sp, netcdf_data, &
5853                                  start = (/ 1 /), count = (/ ns /) )
5854          CALL netcdf_handle_error( 'netcdf_define_header', 294 )
5855
5856          DEALLOCATE( netcdf_data )
5857
5858!
5859!--       Write data for x and y axis (wavenumbers)
5860          ALLOCATE( netcdf_data(nx/2) )
5861          DO  i = 1, nx/2
5862             netcdf_data(i) = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
5863          ENDDO
5864
5865          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_x_sp, netcdf_data, &
5866                                  start = (/ 1 /), count = (/ nx/2 /) )
5867          CALL netcdf_handle_error( 'netcdf_define_header', 295 )
5868
5869          DEALLOCATE( netcdf_data )
5870
5871          ALLOCATE( netcdf_data(ny/2) )
5872          DO  i = 1, ny/2
5873             netcdf_data(i) = 2.0_wp * pi * i / ( dy * ( ny + 1 ) )
5874          ENDDO
5875
5876          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_y_sp, netcdf_data, &
5877                                  start = (/ 1 /), count = (/ ny/2 /) )
5878          CALL netcdf_handle_error( 'netcdf_define_header', 296 )
5879
5880          DEALLOCATE( netcdf_data )
5881
5882
5883       CASE ( 'sp_ext' )
5884
5885!
5886!--       Get the list of variables and compare with the actual run.
5887!--       First var_list_old has to be reset, since GET_ATT does not assign
5888!--       trailing blanks.
5889          var_list_old = ' '
5890          nc_stat = NF90_GET_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', &
5891                                  var_list_old )
5892          CALL netcdf_handle_error( 'netcdf_define_header', 297 )
5893          var_list = ';'
5894          i = 1
5895          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
5896
5897             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
5898                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
5899                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
5900             ENDIF
5901
5902             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
5903                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
5904                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
5905             ENDIF
5906
5907             i = i + 1
5908
5909          ENDDO
5910
5911          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
5912             message_string = 'netCDF file for spectra  ' //                   &
5913                              'from previous run found,' //                    &
5914                              '&but this file cannot be extended due to' //    &
5915                              ' variable mismatch.' //                         &
5916                              '&New file is created instead.'
5917             CALL message( 'define_netcdf_header', 'PA0260', 0, 1, 0, 6, 0 )
5918             extend = .FALSE.
5919             RETURN
5920          ENDIF
5921
5922!
5923!--       Determine the number of current vertical levels for which spectra
5924!--       shall be output
5925          ns = 1
5926          DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
5927             ns = ns + 1
5928          ENDDO
5929          ns = ns - 1
5930
5931!
5932!--       Get and compare the number of vertical levels
5933          nc_stat = NF90_INQ_VARID( id_set_sp, 'zu_sp', id_var_zu_sp )
5934          CALL netcdf_handle_error( 'netcdf_define_header', 298 )
5935
5936          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_zu_sp, &
5937                                           dimids = id_dim_zu_sp_old )
5938          CALL netcdf_handle_error( 'netcdf_define_header', 299 )
5939          id_dim_zu_sp = id_dim_zu_sp_old(1)
5940
5941          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_zu_sp, &
5942                                            len = ns_old )
5943          CALL netcdf_handle_error( 'netcdf_define_header', 300 )
5944
5945          IF ( ns /= ns_old )  THEN
5946             message_string = 'netCDF file for spectra ' //                    &
5947                              ' from previous run found,' //                   &
5948                              '&but this file cannot be extended due to' //    &
5949                              ' mismatch in number of' //                      &
5950                              ' vertical levels.' //                           &
5951                              '&New file is created instead.'
5952             CALL message( 'define_netcdf_header', 'PA0261', 0, 1, 0, 6, 0 )
5953             extend = .FALSE.
5954             RETURN
5955          ENDIF
5956
5957!
5958!--       Get and compare the heights of the cross sections
5959          ALLOCATE( netcdf_data(1:ns_old) )
5960
5961          nc_stat = NF90_GET_VAR( id_set_sp, id_var_zu_sp, netcdf_data )
5962          CALL netcdf_handle_error( 'netcdf_define_header', 301 )
5963
5964          DO  i = 1, ns
5965             IF ( zu(comp_spectra_level(i)) /= netcdf_data(i) )  THEN
5966                message_string = 'netCDF file for spectra ' //                 &
5967                                 ' from previous run found,' //                &
5968                                 '&but this file cannot be extended due to' // &
5969                                 ' mismatch in heights of' //                  &
5970                                 ' vertical levels.' //                        &
5971                                 '&New file is created instead.'
5972                CALL message( 'define_netcdf_header', 'PA0262', 0, 1, 0, 6, 0 )
5973                extend = .FALSE.
5974                RETURN
5975             ENDIF
5976          ENDDO
5977
5978          DEALLOCATE( netcdf_data )
5979
5980!
5981!--       Get the id of the time coordinate (unlimited coordinate) and its
5982!--       last index on the file. The next time level is plsp..count+1.
5983!--       The current time must be larger than the last output time
5984!--       on the file.
5985          nc_stat = NF90_INQ_VARID( id_set_sp, 'time', id_var_time_sp )
5986          CALL netcdf_handle_error( 'netcdf_define_header', 302 )
5987
5988          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_time_sp, &
5989                                           dimids = id_dim_time_old )
5990          CALL netcdf_handle_error( 'netcdf_define_header', 303 )
5991          id_dim_time_sp = id_dim_time_old(1)
5992
5993          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_time_sp, &
5994                                            len = dosp_time_count )
5995          CALL netcdf_handle_error( 'netcdf_define_header', 304 )
5996
5997          nc_stat = NF90_GET_VAR( id_set_sp, id_var_time_sp,        &
5998                                  last_time_coordinate,             &
5999                                  start = (/ dosp_time_count /), &
6000                                  count = (/ 1 /) )
6001          CALL netcdf_handle_error( 'netcdf_define_header', 305 )
6002
6003          IF ( last_time_coordinate(1) >= simulated_time )  THEN
6004             message_string = 'netCDF file for spectra ' //                    &
6005                              'from previous run found,' //                    &
6006                              '&but this file cannot be extended becaus' //    &
6007                              'e the current output time' //                   &
6008                              '&is less or equal than the last output t' //    &
6009                              'ime on this file.' //                           &
6010                              '&New file is created instead.'
6011             CALL message( 'define_netcdf_header', 'PA0263', 0, 1, 0, 6, 0 )
6012             dosp_time_count = 0
6013             extend = .FALSE.
6014             RETURN
6015          ENDIF
6016
6017!
6018!--       Dataset seems to be extendable.
6019!--       Now get the variable ids.
6020          i = 1
6021          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
6022
6023             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
6024                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
6025                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
6026                                          id_var_dospx(i) )
6027                CALL netcdf_handle_error( 'netcdf_define_header', 306 )
6028             ENDIF
6029
6030             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
6031                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
6032                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
6033                                          id_var_dospy(i) )
6034                CALL netcdf_handle_error( 'netcdf_define_header', 307 )
6035             ENDIF
6036
6037             i = i + 1
6038
6039          ENDDO
6040
6041!
6042!--       Update the title attribute on file
6043!--       In order to avoid 'data mode' errors if updated attributes are larger
6044!--       than their original size, NF90_PUT_ATT is called in 'define mode'
6045!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
6046!--       performance loss due to data copying; an alternative strategy would be
6047!--       to ensure equal attribute size in a job chain. Maybe revise later.
6048          nc_stat = NF90_REDEF( id_set_sp )
6049          CALL netcdf_handle_error( 'netcdf_define_header', 441 )
6050          IF ( averaging_interval_sp /= 0.0_wp )  THEN
6051             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
6052                                                           averaging_interval_sp
6053             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',  &
6054                                     TRIM( run_description_header ) // &
6055                                     TRIM( time_average_text ) )
6056             CALL netcdf_handle_error( 'netcdf_define_header', 308 )
6057
6058             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
6059             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg',       &
6060                                     TRIM( time_average_text ) )
6061          ELSE
6062             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',          &
6063                                     TRIM( run_description_header ) )
6064          ENDIF
6065          CALL netcdf_handle_error( 'netcdf_define_header', 309 )
6066          nc_stat = NF90_ENDDEF( id_set_sp )
6067          CALL netcdf_handle_error( 'netcdf_define_header', 442 )
6068          message_string = 'netCDF file for spectra ' //                       &
6069                           'from previous run found.' //                       &
6070                           '&This file will be extended.'
6071          CALL message( 'define_netcdf_header', 'PA0264', 0, 0, 0, 6, 0 )
6072
6073!
6074!--     Currently disabled (DATA_PRT_NETCDF)
6075!       CASE ( 'pt_new' )
6076
6077!
6078!--       Define some global attributes of the dataset
6079!          nc_stat = NF90_PUT_ATT( id_set_prt, NF90_GLOBAL, 'title',            &
6080!                                  TRIM( run_description_header ) )
6081!          CALL netcdf_handle_error( 'netcdf_define_header', 310 )
6082
6083!
6084!--       Define time coordinate for particles (unlimited dimension)
6085!          CALL netcdf_create_dim( id_set_prt, 'time', NF90_UNLIMITED,          &
6086!                                  id_dim_time_prt, 311 )
6087!          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /), 'time',   &
6088!                                  NF90_DOUBLE, id_var_time_prt, 'seconds', '', &
6089!                                  312, 313, 000 )
6090!
6091!--       netCDF4 allows more than one unlimited dimension
6092!          CALL netcdf_create_dim( id_set_prt, 'particle_number',            &
6093!                                  NF90_UNLIMITED, id_dim_prtnum, 314 )
6094
6095!          CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum /),             &
6096!                                  'particle_number', NF90_DOUBLE,              &
6097!                                  id_var_prtnum, 'particle number', '', 315,   &
6098!                                  316, 000 )
6099!
6100!--       Define variable which contains the real number of particles in use
6101!          CALL netcdf_create_var( id_set_prt, (/ id_dim_time_prt /),           &
6102!                                  'real_num_of_prt', NF90_DOUBLE,              &
6103!                                  id_var_rnop_prt, 'particle number', '', 317, &
6104!                                  318, 000 )
6105!
6106!--       Define the variables
6107!          DO  i = 1, 17
6108
6109!             CALL netcdf_create_var( id_set_prt, (/ id_dim_prtnum,             &
6110!                                     id_dim_time_prt /), prt_var_names(i),     &
6111!                                     nc_precision(8), id_var_prt(i),           &
6112!                                     TRIM( prt_var_units(i) ),                 &
6113!                                     TRIM( prt_var_names(i) ), 319, 320, 321 )
6114
6115!          ENDDO
6116
6117!
6118!--       Leave netCDF define mode
6119!          nc_stat = NF90_ENDDEF( id_set_prt )
6120!          CALL netcdf_handle_error( 'netcdf_define_header', 322 )
6121
6122!
6123!--     Currently disabled (DATA_PRT_NETCDF)
6124!       CASE ( 'pt_ext' )
6125
6126!
6127!--       Get the id of the time coordinate (unlimited coordinate) and its
6128!--       last index on the file. The next time level is prt..count+1.
6129!--       The current time must be larger than the last output time
6130!--       on the file.
6131!          nc_stat = NF90_INQ_VARID( id_set_prt, 'time', id_var_time_prt )
6132!          CALL netcdf_handle_error( 'netcdf_define_header', 323 )
6133
6134!          nc_stat = NF90_INQUIRE_VARIABLE( id_set_prt, id_var_time_prt, &
6135!                                           dimids = id_dim_time_old )
6136!          CALL netcdf_handle_error( 'netcdf_define_header', 324 )
6137!          id_dim_time_prt = id_dim_time_old(1)
6138
6139!          nc_stat = NF90_INQUIRE_DIMENSION( id_set_prt, id_dim_time_prt, &
6140!                                            len = prt_time_count )
6141!          CALL netcdf_handle_error( 'netcdf_define_header', 325 )
6142
6143!          nc_stat = NF90_GET_VAR( id_set_prt, id_var_time_prt,  &
6144!                                  last_time_coordinate,         &
6145!                                  start = (/ prt_time_count /), &
6146!                                  count = (/ 1 /) )
6147!          CALL netcdf_handle_error( 'netcdf_define_header', 326 )
6148
6149!          IF ( last_time_coordinate(1) >= simulated_time )  THEN
6150!             message_string = 'netCDF file for particles ' //                  &
6151!                              'from previous run found,' //                    &
6152!                              '&but this file cannot be extended becaus' //    &
6153!                              'e the current output time' //                   &
6154!                              '&is less or equal than the last output t' //    &
6155!                              'ime on this file.' //                           &
6156!                              '&New file is created instead.'
6157!             CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
6158!             prt_time_count = 0
6159!             extend = .FALSE.
6160!             RETURN
6161!          ENDIF
6162
6163!
6164!--       Dataset seems to be extendable.
6165!--       Now get the variable ids.
6166!         nc_stat = NF90_INQ_VARID( id_set_prt, 'real_num_of_prt',             &
6167!                                   id_var_rnop_prt )
6168!         CALL netcdf_handle_error( 'netcdf_define_header', 327 )
6169
6170!          DO  i = 1, 17
6171
6172!             nc_stat = NF90_INQ_VARID( id_set_prt, prt_var_names(i),           &
6173!                                       id_var_prt(i) )
6174!             CALL netcdf_handle_error( 'netcdf_define_header', 328 )
6175
6176!          ENDDO
6177
6178!          message_string = 'netCDF file for particles ' //                     &
6179!                           'from previous run found.' //                       &
6180!                           '&This file will be extended.'
6181!          CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
6182
6183
6184
6185       CASE ( 'ps_new' )
6186
6187!
6188!--       Define some global attributes of the dataset
6189          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title',            &
6190                                  TRIM( run_description_header ) )
6191          CALL netcdf_handle_error( 'netcdf_define_header', 396 )
6192
6193!
6194!--       Define time coordinate for particle time series (unlimited dimension)
6195          CALL netcdf_create_dim( id_set_pts, 'time', NF90_UNLIMITED,          &
6196                                  id_dim_time_pts, 397 )
6197          CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /), 'time',   &
6198                                  NF90_DOUBLE, id_var_time_pts, 'seconds', 'time', &
6199                                  398, 399, 000 )
6200          CALL netcdf_create_att( id_set_pts, id_var_time_pts, 'standard_name', 'time', 000)
6201          CALL netcdf_create_att( id_set_pts, id_var_time_pts, 'axis', 'T', 000)
6202!
6203!--       Define the variables. If more than one particle group is defined,
6204!--       define seperate variables for each group
6205          var_list = ';'
6206          DO  i = 1, dopts_num
6207
6208             DO  j = 0, number_of_particle_groups
6209
6210                IF ( j == 0 )  THEN
6211                   suffix = ''
6212                ELSE
6213                   WRITE ( suffix, '(''_'',I2.2)' )  j
6214                ENDIF
6215
6216                IF ( j == 0 )  THEN
6217                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
6218                                           TRIM( dopts_label(i) ) // suffix,  &
6219                                           nc_precision(6), id_var_dopts(i,j), &
6220                                           TRIM( dopts_unit(i) ),              &
6221                                           TRIM( dopts_label(i) ), 400, 401,   &
6222                                           402 )
6223                ELSE
6224                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
6225                                           TRIM( dopts_label(i) ) // suffix,  &
6226                                           nc_precision(6), id_var_dopts(i,j), &
6227                                           TRIM( dopts_unit(i) ),              &
6228                                           TRIM( dopts_label(i) ) // ' PG ' // &
6229                                           suffix(2:3), 400, 401, 402 )
6230                ENDIF
6231
6232                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
6233                           suffix // ';'
6234
6235                IF ( number_of_particle_groups == 1 )  EXIT
6236
6237             ENDDO
6238
6239          ENDDO
6240
6241!
6242!--       Write the list of variables as global attribute (this is used by
6243!--       restart runs)
6244          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
6245                                  var_list )
6246          CALL netcdf_handle_error( 'netcdf_define_header', 403 )
6247
6248
6249!
6250!--       Leave netCDF define mode
6251          nc_stat = NF90_ENDDEF( id_set_pts )
6252          CALL netcdf_handle_error( 'netcdf_define_header', 404 )
6253
6254
6255       CASE ( 'ps_ext' )
6256
6257!
6258!--       Get the list of variables and compare with the actual run.
6259!--       First var_list_old has to be reset, since GET_ATT does not assign
6260!--       trailing blanks.
6261          var_list_old = ' '
6262          nc_stat = NF90_GET_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
6263                                  var_list_old )
6264          CALL netcdf_handle_error( 'netcdf_define_header', 405 )
6265
6266          var_list = ';'
6267          i = 1
6268          DO  i = 1, dopts_num
6269
6270             DO  j = 0, number_of_particle_groups
6271
6272                IF ( j == 0 )  THEN
6273                   suffix = ''
6274                ELSE
6275                   WRITE ( suffix, '(''_'',I2.2)' )  j
6276                ENDIF
6277
6278                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
6279                           suffix // ';'
6280
6281                IF ( number_of_particle_groups == 1 )  EXIT
6282
6283             ENDDO
6284
6285          ENDDO
6286
6287          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
6288             message_string = 'netCDF file for particle time series ' //       &
6289                              'from previous run found,' //                    &
6290                              '&but this file cannot be extended due to' //    &
6291                              ' variable mismatch.' //                         &
6292                              '&New file is created instead.'
6293             CALL message( 'define_netcdf_header', 'PA0267', 0, 1, 0, 6, 0 )
6294             extend = .FALSE.
6295             RETURN
6296          ENDIF
6297
6298!
6299!--       Get the id of the time coordinate (unlimited coordinate) and its
6300!--       last index on the file. The next time level is dots..count+1.
6301!--       The current time must be larger than the last output time
6302!--       on the file.
6303          nc_stat = NF90_INQ_VARID( id_set_pts, 'time', id_var_time_pts )
6304          CALL netcdf_handle_error( 'netcdf_define_header', 406 )
6305
6306          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pts, id_var_time_pts, &
6307                                           dimids = id_dim_time_old )
6308          CALL netcdf_handle_error( 'netcdf_define_header', 407 )
6309          id_dim_time_pts = id_dim_time_old(1)
6310
6311          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pts, id_dim_time_pts, &
6312                                            len = dopts_time_count )
6313          CALL netcdf_handle_error( 'netcdf_define_header', 408 )
6314
6315          nc_stat = NF90_GET_VAR( id_set_pts, id_var_time_pts,    &
6316                                  last_time_coordinate,           &
6317                                  start = (/ dopts_time_count /), &
6318                                  count = (/ 1 /) )
6319          CALL netcdf_handle_error( 'netcdf_define_header', 409 )
6320
6321          IF ( last_time_coordinate(1) >= simulated_time )  THEN
6322             message_string = 'netCDF file for particle time series ' //       &
6323                              'from previous run found,' //                    &
6324                              '&but this file cannot be extended becaus' //    &
6325                              'e the current output time' //                   &
6326                              '&is less or equal than the last output t' //    &
6327                              'ime on this file.' //                           &
6328                              '&New file is created instead.'
6329             CALL message( 'define_netcdf_header', 'PA0268', 0, 1, 0, 6, 0 )
6330             dopts_time_count = 0
6331             extend = .FALSE.
6332             RETURN
6333          ENDIF
6334
6335!
6336!--       Dataset seems to be extendable.
6337!--       Now get the variable ids
6338          i = 1
6339          DO  i = 1, dopts_num
6340
6341             DO  j = 0, number_of_particle_groups
6342
6343                IF ( j == 0 )  THEN
6344                   suffix = ''
6345                ELSE
6346                   WRITE ( suffix, '(''_'',I2.2)' )  j
6347                ENDIF
6348
6349                netcdf_var_name = TRIM( dopts_label(i) ) // suffix
6350
6351                nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, &
6352                                          id_var_dopts(i,j) )
6353                CALL netcdf_handle_error( 'netcdf_define_header', 410 )
6354
6355                IF ( number_of_particle_groups == 1 )  EXIT
6356
6357             ENDDO
6358
6359          ENDDO
6360
6361!
6362!--       Update the title attribute on file
6363!--       In order to avoid 'data mode' errors if updated attributes are larger
6364!--       than their original size, NF90_PUT_ATT is called in 'define mode'
6365!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
6366!--       performance loss due to data copying; an alternative strategy would be
6367!--       to ensure equal attribute size in a job chain. Maybe revise later.
6368          nc_stat = NF90_REDEF( id_set_pts )
6369          CALL netcdf_handle_error( 'netcdf_define_header', 443 )
6370          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title',            &
6371                                  TRIM( run_description_header ) )
6372          CALL netcdf_handle_error( 'netcdf_define_header', 411 )
6373          nc_stat = NF90_ENDDEF( id_set_pts )
6374          CALL netcdf_handle_error( 'netcdf_define_header', 444 )
6375          message_string = 'netCDF file for particle time series ' //          &
6376                           'from previous run found.' //                       &
6377                           '&This file will be extended.'
6378          CALL message( 'netcdf_define_header', 'PA0269', 0, 0, 0, 6, 0 )
6379
6380!
6381!--    Flight data
6382       CASE ( 'fl_new' )
6383!
6384!--       Define some global attributes of the dataset
6385          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
6386                                  TRIM( run_description_header ) )
6387          CALL netcdf_handle_error( 'netcdf_define_header', 249 )
6388
6389!
6390!--       Define time and location coordinates for flight space-time series
6391!--       (unlimited dimension)
6392!--       Error number must still be set appropriately.
6393          CALL netcdf_create_dim( id_set_fl, 'time', NF90_UNLIMITED,           &
6394                                  id_dim_time_fl, 250 )
6395          CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /), 'time',     &
6396                                  NF90_DOUBLE, id_var_time_fl, 'seconds', 'time',  &
6397                                  251, 252, 000 )
6398          CALL netcdf_create_att( id_set_fl, id_var_time_fl, 'standard_name', 'time', 000)
6399          CALL netcdf_create_att( id_set_fl, id_var_time_fl, 'axis', 'T', 000)
6400
6401          DO l = 1, num_leg
6402             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_x(l),           &
6403                                     NF90_UNLIMITED, id_dim_x_fl(l), 250 )
6404             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_y(l),           &
6405                                     NF90_UNLIMITED, id_dim_y_fl(l), 250 )
6406             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_z(l),           &
6407                                     NF90_UNLIMITED, id_dim_z_fl(l), 250 )
6408
6409             CALL netcdf_create_var( id_set_fl, (/ id_dim_x_fl(l) /),          &
6410                                     dofl_dim_label_x(l), NF90_DOUBLE,         &
6411                                     id_var_x_fl(l), 'm', '', 251, 252, 000 )
6412             CALL netcdf_create_var( id_set_fl, (/ id_dim_y_fl(l) /),          &
6413                                     dofl_dim_label_y(l), NF90_DOUBLE,         &
6414                                     id_var_y_fl(l), 'm', '', 251, 252, 000 )
6415             CALL netcdf_create_var( id_set_fl, (/ id_dim_z_fl(l) /),          &
6416                                     dofl_dim_label_z(l), NF90_DOUBLE,         &
6417                                     id_var_z_fl(l), 'm', '', 251, 252, 000 )
6418          ENDDO
6419!
6420!--       Define the variables
6421          var_list = ';'
6422          k = 1
6423          DO  l = 1, num_leg
6424             DO i = 1, num_var_fl
6425
6426                CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /),       &
6427                                        dofl_label(k), nc_precision(9),        &
6428                                        id_var_dofl(k),                        &
6429                                        TRIM( dofl_unit(k) ),                  &
6430                                        TRIM( dofl_label(k) ), 253, 254, 255 )
6431
6432                k = k + 1
6433
6434             ENDDO
6435
6436          ENDDO
6437
6438!
6439!--       Write the list of variables as global attribute (this is used by
6440!--       restart runs)
6441          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST', var_list )
6442          CALL netcdf_handle_error( 'netcdf_define_header', 258 )
6443
6444!
6445!--       Leave netCDF define mode
6446          nc_stat = NF90_ENDDEF( id_set_fl )
6447          CALL netcdf_handle_error( 'netcdf_define_header', 259 )
6448
6449
6450       CASE ( 'fl_ext' )
6451
6452!
6453!--       Get the list of variables and compare with the actual run.
6454!--       First var_list_old has to be reset, since GET_ATT does not assign
6455!--       trailing blanks.
6456          var_list_old = ' '
6457          nc_stat = NF90_GET_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST',          &
6458                                  var_list_old )
6459          CALL netcdf_handle_error( 'netcdf_define_header', 260 )
6460
6461          var_list = ';'
6462          i = 1
6463          DO  i = 1, num_leg * num_var_fl
6464
6465             var_list = TRIM( var_list ) // TRIM( dofl_label(i) ) // ';'
6466
6467          ENDDO
6468
6469          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
6470             message_string = 'netCDF file for flight time series ' //         &
6471                              'from previous run found,' //                    &
6472                              '&but this file cannot be extended due to' //    &
6473                              ' variable mismatch.' //                         &
6474                              '&New file is created instead.'
6475             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
6476             extend = .FALSE.
6477             RETURN
6478          ENDIF
6479
6480!
6481!--       Get the id of the time coordinate (unlimited coordinate) and its
6482!--       last index on the file. The next time level is dofl_time_count+1.
6483!--       The current time must be larger than the last output time
6484!--       on the file.
6485          nc_stat = NF90_INQ_VARID( id_set_fl, 'time', id_var_time_fl )
6486          CALL netcdf_handle_error( 'netcdf_define_header', 261 )
6487
6488          nc_stat = NF90_INQUIRE_VARIABLE( id_set_fl, id_var_time_fl,          &
6489                                           dimids = id_dim_time_old )
6490          CALL netcdf_handle_error( 'netcdf_define_header', 262 )
6491          id_dim_time_fl = id_dim_time_old(1)
6492
6493          nc_stat = NF90_INQUIRE_DIMENSION( id_set_fl, id_dim_time_fl,         &
6494                                            len = dofl_time_count )
6495          CALL netcdf_handle_error( 'netcdf_define_header', 263 )
6496
6497          nc_stat = NF90_GET_VAR( id_set_fl, id_var_time_fl,        &
6498                                  last_time_coordinate,             &
6499                                  start = (/ dofl_time_count /), &
6500                                  count = (/ 1 /) )
6501          CALL netcdf_handle_error( 'netcdf_define_header', 264 )
6502
6503          IF ( last_time_coordinate(1) >= simulated_time )  THEN
6504             message_string = 'netCDF file for flight-time series ' //         &
6505                              'from previous run found,' //                    &
6506                              '&but this file cannot be extended becaus' //    &
6507                              'e the current output time' //                   &
6508                              '&is less or equal than the last output t' //    &
6509                              'ime on this file.' //                           &
6510                              '&New file is created instead.'
6511             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
6512             dofl_time_count = 0
6513             extend = .FALSE.
6514             RETURN
6515          ENDIF
6516
6517!
6518!--       Dataset seems to be extendable.
6519!--       Now get the remaining dimension and variable ids
6520          DO l = 1, num_leg
6521             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_x(l),         &
6522                                       id_var_x_fl(l) )
6523             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
6524             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_y(l),         &
6525                                       id_var_y_fl(l) )
6526             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
6527             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_z(l),         &
6528                                       id_var_z_fl(l) )
6529             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
6530
6531          ENDDO
6532
6533
6534          DO  i = 1, num_leg * num_var_fl
6535
6536            nc_stat = NF90_INQ_VARID( id_set_fl, dofl_label(i), &
6537                                       id_var_dofl(i) )
6538            CALL netcdf_handle_error( 'netcdf_define_header', 265 )
6539
6540          ENDDO
6541
6542!
6543!--       Update the title attribute on file
6544!--       In order to avoid 'data mode' errors if updated attributes are larger
6545!--       than their original size, NF90_PUT_ATT is called in 'define mode'
6546!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
6547!--       performance loss due to data copying; an alternative strategy would be
6548!--       to ensure equal attribute size in a job chain. Maybe revise later.
6549          nc_stat = NF90_REDEF( id_set_fl )
6550          CALL netcdf_handle_error( 'netcdf_define_header', 439 )
6551          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
6552                                  TRIM( run_description_header ) )
6553          CALL netcdf_handle_error( 'netcdf_define_header', 267 )
6554          nc_stat = NF90_ENDDEF( id_set_fl )
6555          CALL netcdf_handle_error( 'netcdf_define_header', 440 )
6556          message_string = 'netCDF file for flight-time series ' //            &
6557                           'from previous run found.' //                       &
6558                           '&This file will be extended.'
6559          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
6560
6561
6562       CASE DEFAULT
6563
6564          message_string = 'mode "' // TRIM( mode) // '" not supported'
6565          CALL message( 'netcdf_define_header', 'PA0270', 0, 0, 0, 6, 0 )
6566
6567    END SELECT
6568
6569#endif
6570 END SUBROUTINE netcdf_define_header
6571
6572
6573!------------------------------------------------------------------------------!
6574! Description:
6575! ------------
6576!> Creates a netCDF file and give back the id. The parallel flag has to be TRUE
6577!> for parallel netCDF output support.
6578!------------------------------------------------------------------------------!
6579
6580 SUBROUTINE netcdf_create_file( filename , id, parallel, errno )
6581#if defined( __netcdf )
6582
6583    USE pegrid
6584
6585    IMPLICIT NONE
6586
6587    CHARACTER (LEN=*), INTENT(IN) :: filename
6588    INTEGER, INTENT(IN)           :: errno
6589    INTEGER, INTENT(OUT)          :: id
6590    INTEGER                       :: idum  !< dummy variable used to avoid compiler warnings about unused variables
6591    LOGICAL, INTENT(IN)           :: parallel
6592
6593!
6594!-- Next line is just to avoid compiler warning about unused variable
6595    IF ( parallel )  idum = 0
6596
6597!
6598!-- Create a new netCDF output file with requested netCDF format
6599    IF ( netcdf_data_format == 1 )  THEN
6600!
6601!--    Classic netCDF format
6602       nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id )
6603
6604    ELSEIF ( netcdf_data_format == 2 )  THEN
6605!
6606!--    64bit-offset format
6607       nc_stat = NF90_CREATE( filename,                                        &
6608                              IOR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ), id )
6609
6610#if defined( __netcdf4 )
6611    ELSEIF ( netcdf_data_format == 3  .OR.                                     &
6612             ( .NOT. parallel  .AND.  netcdf_data_format == 5 ) )  THEN
6613!
6614!--    netCDF4/HDF5 format
6615       nc_stat = NF90_CREATE( filename, IOR( NF90_NOCLOBBER, NF90_NETCDF4 ), id )
6616
6617    ELSEIF ( netcdf_data_format == 4  .OR.                                     &
6618             ( .NOT. parallel  .AND.  netcdf_data_format == 6 ) )  THEN
6619!
6620!--    netCDF4/HDF5 format with classic model flag
6621       nc_stat = NF90_CREATE( filename,                                        &
6622                              IOR( NF90_NOCLOBBER,                             &
6623                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), id )
6624
6625#if defined( __netcdf4_parallel )
6626    ELSEIF ( netcdf_data_format == 5  .AND.  parallel )  THEN
6627!
6628!--    netCDF4/HDF5 format, parallel
6629       nc_stat = NF90_CREATE( filename,                                        &
6630                              IOR( NF90_NOCLOBBER,                             &
6631                              IOR( NF90_NETCDF4, NF90_MPIIO ) ),               &
6632                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
6633
6634    ELSEIF ( netcdf_data_format == 6  .AND.  parallel )  THEN
6635!
6636!--    netCDF4/HDF5 format with classic model flag, parallel
6637       nc_stat = NF90_CREATE( filename,                                        &
6638                              IOR( NF90_NOCLOBBER,                             &
6639                              IOR( NF90_MPIIO,                                 &
6640                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),        &
6641                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
6642
6643#endif
6644#endif
6645    ENDIF
6646
6647    CALL netcdf_handle_error( 'netcdf_create_file', errno )
6648#endif
6649 END SUBROUTINE netcdf_create_file
6650
6651!------------------------------------------------------------------------------!
6652! Description:
6653! ------------
6654!> Opens an existing netCDF file for writing and gives back the id.
6655!> The parallel flag has to be TRUE for parallel netCDF output support.
6656!------------------------------------------------------------------------------!
6657 SUBROUTINE netcdf_open_write_file( filename, id, parallel, errno )
6658#if defined( __netcdf )
6659
6660    USE pegrid
6661
6662    IMPLICIT NONE
6663
6664    CHARACTER (LEN=*), INTENT(IN) :: filename
6665    INTEGER, INTENT(IN)           :: errno
6666    INTEGER, INTENT(OUT)          :: id
6667    LOGICAL, INTENT(IN)           :: parallel
6668
6669
6670    IF ( netcdf_data_format < 5  .OR.  .NOT. parallel )  THEN
6671       nc_stat = NF90_OPEN( filename, NF90_WRITE, id )
6672#if defined( __netcdf4 )
6673#if defined( __netcdf4_parallel )
6674    ELSEIF ( netcdf_data_format > 4  .AND.  parallel )  THEN
6675       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id,  &
6676                            COMM = comm2d, INFO = MPI_INFO_NULL )
6677#endif
6678#endif
6679    ENDIF
6680
6681    CALL netcdf_handle_error( 'netcdf_open_write_file', errno )
6682#endif
6683 END SUBROUTINE netcdf_open_write_file
6684
6685
6686!------------------------------------------------------------------------------!
6687! Description:
6688! ------------
6689!> Prints out a text message corresponding to the current status.
6690!------------------------------------------------------------------------------!
6691
6692 SUBROUTINE netcdf_handle_error( routine_name, errno )
6693#if defined( __netcdf )
6694
6695
6696    USE control_parameters,                                                    &
6697        ONLY:  message_string
6698
6699    IMPLICIT NONE
6700
6701    CHARACTER(LEN=6) ::  message_identifier
6702    CHARACTER(LEN=*) ::  routine_name
6703
6704    INTEGER(iwp) ::  errno
6705
6706    IF ( nc_stat /= NF90_NOERR )  THEN
6707
6708       WRITE( message_identifier, '(''NC'',I4.4)' )  errno
6709
6710       message_string = TRIM( NF90_STRERROR( nc_stat ) )
6711
6712       CALL message( routine_name, message_identifier, 2, 2, 0, 6, 1 )
6713
6714    ENDIF
6715
6716#endif
6717 END SUBROUTINE netcdf_handle_error
6718
6719
6720!------------------------------------------------------------------------------!
6721! Description:
6722! ------------
6723!> Create a dimension in NetCDF file
6724!------------------------------------------------------------------------------!
6725
6726 SUBROUTINE netcdf_create_dim(ncid, dim_name, ncdim_type, ncdim_id, error_no)
6727
6728#if defined( __netcdf )
6729
6730    USE kinds
6731
6732    IMPLICIT NONE
6733
6734    CHARACTER(LEN=*), INTENT(IN) ::  dim_name
6735
6736    INTEGER, INTENT(IN)  ::  error_no
6737    INTEGER, INTENT(IN)  ::  ncid
6738    INTEGER, INTENT(OUT) ::  ncdim_id
6739    INTEGER, INTENT(IN)  ::  ncdim_type
6740
6741!
6742!-- Define time coordinate for volume data (unlimited dimension)
6743    nc_stat = NF90_DEF_DIM( ncid, dim_name, ncdim_type, ncdim_id )
6744    CALL netcdf_handle_error( 'netcdf_create_dim', error_no )
6745
6746#endif
6747
6748 END SUBROUTINE netcdf_create_dim
6749
6750
6751!------------------------------------------------------------------------------!
6752! Description:
6753! ------------
6754!> Create a one dimensional variable in specific units in NetCDF file
6755!------------------------------------------------------------------------------!
6756
6757 SUBROUTINE netcdf_create_var( ncid, dim_id, var_name, var_type, var_id,       &
6758                               unit_name, long_name, error_no1, error_no2,     &
6759                               error_no3, fill )
6760
6761#if defined( __netcdf )
6762    IMPLICIT NONE
6763
6764    CHARACTER(LEN=*), INTENT(IN) ::  long_name
6765    CHARACTER(LEN=*), INTENT(IN) ::  unit_name
6766    CHARACTER(LEN=*), INTENT(IN) ::  var_name
6767
6768    LOGICAL, OPTIONAL ::  fill  !< indicates setting of _FillValue attribute
6769
6770    INTEGER, INTENT(IN)  ::  error_no1
6771    INTEGER, INTENT(IN)  ::  error_no2
6772    INTEGER, INTENT(IN)  ::  error_no3
6773    INTEGER, INTENT(IN)  ::  ncid
6774    INTEGER, INTENT(OUT) ::  var_id
6775    INTEGER, INTENT(IN)  ::  var_type
6776
6777    INTEGER, DIMENSION(:), INTENT(IN) ::  dim_id
6778
6779!
6780!-- Define variable
6781    nc_stat = NF90_DEF_VAR( ncid, var_name, var_type, dim_id, var_id )
6782    CALL netcdf_handle_error( 'netcdf_create_var', error_no1 )
6783
6784#if defined( __netcdf4 )
6785!
6786!-- Check if variable should be deflate (including shuffling)
6787!-- and if it is possible (only NetCDF4 with HDF5 supports compression)
6788    IF ( netcdf_data_format > 2  .AND.  netcdf_deflate > 0 )  THEN
6789       nc_stat = NF90_DEF_VAR_DEFLATE( ncid, var_id, 1, 1, netcdf_deflate )
6790       CALL netcdf_handle_error( 'netcdf_create_var_deflate', error_no1 )
6791    ENDIF
6792#endif
6793!
6794!-- Set unit name if set
6795    IF ( unit_name /= '' )  THEN
6796       nc_stat = NF90_PUT_ATT( ncid, var_id, 'units', unit_name )
6797       CALL netcdf_handle_error( 'netcdf_create_var', error_no2 )
6798    ENDIF
6799
6800!
6801!-- Set long name if set
6802    IF ( long_name /= '' )  THEN
6803       nc_stat = NF90_PUT_ATT( ncid, var_id, 'long_name', long_name )
6804       CALL netcdf_handle_error( 'netcdf_create_var', error_no3 )
6805    ENDIF
6806
6807!
6808!-- Set _FillValue for all variables, except for dimension variables.
6809!-- Set the fill values accordingly to the corresponding output precision.
6810    IF ( PRESENT( fill ) )  THEN
6811       IF ( var_type == NF90_REAL4 )  THEN
6812          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
6813                                  REAL( fill_value, KIND = 4 ) )
6814          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
6815       ELSE
6816          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
6817                                  REAL( fill_value, KIND = 8 ) )
6818          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
6819       ENDIF
6820    ENDIF
6821
6822#endif
6823 END SUBROUTINE netcdf_create_var
6824
6825
6826!------------------------------------------------------------------------------!
6827! Description:
6828! ------------
6829!> Write attributes to file.
6830!------------------------------------------------------------------------------!
6831 SUBROUTINE netcdf_create_att_string( ncid, varid, name, value, err )
6832
6833    IMPLICIT NONE
6834
6835    CHARACTER(LEN=*), INTENT(IN) ::  name    !< attribute name
6836    CHARACTER(LEN=*), INTENT(IN) ::  value   !< attribute value
6837
6838    INTEGER, INTENT(IN) ::  err              !< error id
6839    INTEGER, INTENT(IN) ::  ncid             !< file id
6840
6841    INTEGER, INTENT(IN), OPTIONAL ::  varid  !< variable id
6842
6843#if defined( __netcdf )
6844    IF ( PRESENT( varid ) )  THEN
6845       nc_stat = NF90_PUT_ATT( ncid, varid, TRIM( name ), TRIM( value ) )
6846    ELSE
6847       nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( name ), TRIM( value ) )
6848    ENDIF
6849    CALL netcdf_handle_error( 'netcdf_create_att_string', err )
6850#endif
6851
6852 END SUBROUTINE netcdf_create_att_string
6853
6854
6855!------------------------------------------------------------------------------!
6856! Description:
6857! ------------
6858!> Write a set of global attributes to file.
6859!------------------------------------------------------------------------------!
6860 SUBROUTINE netcdf_create_global_atts( ncid, data_content, title, error_no )
6861
6862    USE control_parameters,                                                    &
6863        ONLY:  revision, run_date, run_time, run_zone, runnr, version
6864
6865    USE date_and_time_mod,                                                     &
6866       ONLY:   day_of_year_init, time_utc_init
6867
6868    USE netcdf_data_input_mod,                                                 &
6869        ONLY:  input_file_atts
6870
6871    IMPLICIT NONE
6872
6873    CHARACTER(LEN=23) ::  origin_time_string  !< string containing date and time of origin
6874
6875    CHARACTER(LEN=*), INTENT(IN)  ::  data_content  !< describes the type of data in file
6876    CHARACTER(LEN=*), INTENT(IN)  ::  title         !< file title
6877
6878    INTEGER, INTENT(IN)  ::  error_no  !< error number
6879    INTEGER, INTENT(IN)  ::  ncid      !< file id
6880!
6881!-- Compose date-time string for origin_time
6882    origin_time_string = date_time_string( day_of_year_init, time_utc_init )
6883
6884#if defined( __netcdf )
6885    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'title', TRIM( title ) )
6886    CALL netcdf_handle_error( 'netcdf_create_global_atts 1', error_no )
6887    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'Conventions', 'CF-1.7' )
6888    CALL netcdf_handle_error( 'netcdf_create_global_atts 2', error_no )
6889    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'creation_time', TRIM( run_date )//' '//TRIM( run_time )//' '//run_zone(1:3) )
6890    CALL netcdf_handle_error( 'netcdf_create_global_atts 3', error_no )
6891    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'data_content', TRIM(data_content) )
6892    CALL netcdf_handle_error( 'netcdf_create_global_atts 4', error_no )
6893    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'version', runnr+1 )
6894    CALL netcdf_handle_error( 'netcdf_create_global_atts 5', error_no )
6895
6896    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_time', origin_time_string )
6897    CALL netcdf_handle_error( 'netcdf_create_global_atts 6', error_no )
6898    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_lat', init_model%latitude )
6899    CALL netcdf_handle_error( 'netcdf_create_global_atts 7', error_no )
6900    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_lon', init_model%longitude )
6901    CALL netcdf_handle_error( 'netcdf_create_global_atts 8', error_no )
6902    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_x', init_model%origin_x )
6903    CALL netcdf_handle_error( 'netcdf_create_global_atts 9', error_no )
6904    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_y', init_model%origin_y )
6905    CALL netcdf_handle_error( 'netcdf_create_global_atts 10', error_no )
6906    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_z', init_model%origin_z )
6907    CALL netcdf_handle_error( 'netcdf_create_global_atts 11', error_no )
6908    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'rotation_angle', init_model%rotation_angle )
6909    CALL netcdf_handle_error( 'netcdf_create_global_atts 12', error_no )
6910
6911    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'dependencies', '' )
6912    CALL netcdf_handle_error( 'netcdf_create_global_atts 13', error_no )
6913    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'history', '' )
6914    CALL netcdf_handle_error( 'netcdf_create_global_atts 14', error_no )
6915
6916    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%author_char ), TRIM( input_file_atts%author ) )
6917    CALL netcdf_handle_error( 'netcdf_create_global_atts 15', error_no )
6918    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%contact_person_char ), TRIM( input_file_atts%contact_person ) )
6919    CALL netcdf_handle_error( 'netcdf_create_global_atts 16', error_no )
6920    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%institution_char ), TRIM( input_file_atts%institution ) )
6921    CALL netcdf_handle_error( 'netcdf_create_global_atts 17', error_no )
6922    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%acronym_char ), TRIM( input_file_atts%acronym ) )
6923    CALL netcdf_handle_error( 'netcdf_create_global_atts 18', error_no )
6924
6925    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%campaign_char ), TRIM( input_file_atts%campaign ) )
6926    CALL netcdf_handle_error( 'netcdf_create_global_atts 19', error_no )
6927    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%location_char ), TRIM( input_file_atts%location ) )
6928    CALL netcdf_handle_error( 'netcdf_create_global_atts 20', error_no )
6929    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%site_char ), TRIM( input_file_atts%site ) )
6930    CALL netcdf_handle_error( 'netcdf_create_global_atts 21', error_no )
6931
6932    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'source', TRIM( version )//' '//TRIM( revision ) )
6933    CALL netcdf_handle_error( 'netcdf_create_global_atts 22', error_no )
6934    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%references_char ), TRIM( input_file_atts%references ) )
6935    CALL netcdf_handle_error( 'netcdf_create_global_atts 23', error_no )
6936    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%keywords_char ), TRIM( input_file_atts%keywords ) )
6937    CALL netcdf_handle_error( 'netcdf_create_global_atts 24', error_no )
6938    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%licence_char ), TRIM( input_file_atts%licence ) )
6939    CALL netcdf_handle_error( 'netcdf_create_global_atts 25', error_no )
6940    nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, TRIM( input_file_atts%comment_char ), TRIM( input_file_atts%comment ) )
6941    CALL netcdf_handle_error( 'netcdf_create_global_atts 26', error_no )
6942
6943#endif
6944
6945 END SUBROUTINE netcdf_create_global_atts
6946
6947!------------------------------------------------------------------------------!
6948! Description:
6949! ------------
6950!> Create a variable holding the coordinate-reference-system information.
6951!------------------------------------------------------------------------------!
6952 SUBROUTINE netcdf_create_crs( ncid, error_no )
6953
6954    IMPLICIT NONE
6955
6956    INTEGER, INTENT(IN)  ::  error_no  !< error number
6957    INTEGER, INTENT(IN)  ::  ncid      !< file id
6958    INTEGER              ::  var_id    !< variable id
6959
6960#if defined( __netcdf )
6961!
6962!-- Define variable
6963    nc_stat = NF90_DEF_VAR( ncid, 'crs', NF90_INT, VARID = var_id )
6964    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6965!
6966!-- Set attributes
6967    nc_stat = NF90_PUT_ATT( ncid, var_id, 'epsg_code', &
6968                            coord_ref_sys%epsg_code )
6969    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6970
6971    nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_easting', &
6972                            coord_ref_sys%false_easting )
6973    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6974
6975    nc_stat = NF90_PUT_ATT( ncid, var_id, 'false_northing', &
6976                            coord_ref_sys%false_northing )
6977    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6978
6979    nc_stat = NF90_PUT_ATT( ncid, var_id, 'grid_mapping_name', &
6980                            coord_ref_sys%grid_mapping_name )
6981    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6982
6983    nc_stat = NF90_PUT_ATT( ncid, var_id, 'inverse_flattening', &
6984                            coord_ref_sys%inverse_flattening )
6985    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6986
6987    nc_stat = NF90_PUT_ATT( ncid, var_id, 'latitude_of_projection_origin', &
6988                            coord_ref_sys%latitude_of_projection_origin )
6989    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6990
6991    nc_stat = NF90_PUT_ATT( ncid, var_id, 'long_name', &
6992                            coord_ref_sys%long_name )
6993    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6994
6995    nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_central_meridian', &
6996                            coord_ref_sys%longitude_of_central_meridian )
6997    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
6998
6999    nc_stat = NF90_PUT_ATT( ncid, var_id, 'longitude_of_prime_meridian', &
7000                            coord_ref_sys%longitude_of_prime_meridian )
7001    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
7002
7003    nc_stat = NF90_PUT_ATT( ncid, var_id, 'scale_factor_at_central_meridian', &
7004                            coord_ref_sys%scale_factor_at_central_meridian )
7005    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
7006
7007    nc_stat = NF90_PUT_ATT( ncid, var_id, 'semi_major_axis', &
7008                            coord_ref_sys%semi_major_axis )
7009    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
7010
7011    nc_stat = NF90_PUT_ATT( ncid, var_id, 'units', &
7012                            coord_ref_sys%units )
7013    CALL netcdf_handle_error( 'netcdf_create_crs', error_no )
7014
7015#endif
7016 END SUBROUTINE netcdf_create_crs
7017
7018
7019!------------------------------------------------------------------------------!
7020! Description:
7021! ------------
7022!> Define UTM coordinates and longitude and latitude in file.
7023!------------------------------------------------------------------------------!
7024 SUBROUTINE define_geo_coordinates( id_set, id_dim_x, id_dim_y, id_var_eutm, id_var_nutm, id_var_lat, id_var_lon )
7025
7026    IMPLICIT NONE
7027
7028    INTEGER ::  i                    !< loop index
7029    INTEGER, INTENT(IN)  ::  id_set  !< file id
7030
7031    INTEGER(iwp), DIMENSION(0:1), INTENT(IN) ::  id_dim_x  !< dimension id of x and xu
7032    INTEGER(iwp), DIMENSION(0:1), INTENT(IN) ::  id_dim_y  !< dimension id of y and yv
7033
7034    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_eutm  !< variable id for E_UTM coordinates
7035    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_lat   !< variable id for latitude coordinates
7036    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_lon   !< variable id for longitude coordinates
7037    INTEGER(iwp), DIMENSION(0:2), INTENT(OUT) ::  id_var_nutm  !< variable id for N_UTM coordinates
7038
7039!
7040!-- Initialize return values
7041    id_var_lat  = -1
7042    id_var_lon  = -1
7043    id_var_eutm = -1
7044    id_var_nutm = -1
7045
7046#if defined( __netcdf )
7047!
7048!-- Define UTM coordinates
7049    IF ( init_model%rotation_angle == 0.0_wp )  THEN
7050       CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting', 000, 000, 000 )
7051       CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing', 000, 000, 000 )
7052       CALL netcdf_create_var( id_set, (/ id_dim_x(1) /), 'Eu_UTM', NF90_DOUBLE, id_var_eutm(1), 'm', 'easting', 000, 000, 000 )
7053       CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'Nu_UTM', NF90_DOUBLE, id_var_nutm(1), 'm', 'northing', 000, 000, 000 )
7054       CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'Ev_UTM', NF90_DOUBLE, id_var_eutm(2), 'm', 'easting', 000, 000, 000 )
7055       CALL netcdf_create_var( id_set, (/ id_dim_y(1) /), 'Nv_UTM', NF90_DOUBLE, id_var_nutm(2), 'm', 'northing', 000, 000, 000 )
7056    ELSE
7057       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), &
7058                               'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting', 000, 000, 000 )
7059       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), &
7060                               'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing', 000, 000, 000 )
7061       CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), &
7062                               'Eu_UTM', NF90_DOUBLE, id_var_eutm(1), 'm', 'easting', 000, 000, 000 )
7063       CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), &
7064                               'Nu_UTM', NF90_DOUBLE, id_var_nutm(1), 'm', 'northing', 000, 000, 000 )
7065       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), &
7066                               'Ev_UTM', NF90_DOUBLE, id_var_eutm(2), 'm', 'easting', 000, 000, 000 )
7067       CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), &
7068                               'Nv_UTM', NF90_DOUBLE, id_var_nutm(2), 'm', 'northing', 000, 000, 000 )
7069    ENDIF
7070!
7071!-- Define geographic coordinates
7072    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lon', NF90_DOUBLE, id_var_lon(0), &
7073                            'degrees_east', 'longitude', 000, 000, 000 )
7074    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(0) /), 'lat', NF90_DOUBLE, id_var_lat(0), &
7075                            'degrees_north', 'latitude', 000, 000, 000 )
7076    CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'lonu', NF90_DOUBLE, id_var_lon(1), &
7077                            'degrees_east', 'longitude', 000, 000, 000 )
7078    CALL netcdf_create_var( id_set, (/ id_dim_x(1), id_dim_y(0) /), 'latu', NF90_DOUBLE, id_var_lat(1), &
7079                            'degrees_north', 'latitude', 000, 000, 000 )
7080    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'lonv', NF90_DOUBLE, id_var_lon(2), &
7081                            'degrees_east', 'longitude', 000, 000, 000 )
7082    CALL netcdf_create_var( id_set, (/ id_dim_x(0), id_dim_y(1) /), 'latv', NF90_DOUBLE, id_var_lat(2), &
7083                            'degrees_north', 'latitude', 000, 000, 000 )
7084
7085    DO  i = 0, 2
7086       CALL netcdf_create_att( id_set, id_var_eutm(i), 'standard_name', 'projection_x_coordinate', 000)
7087       CALL netcdf_create_att( id_set, id_var_nutm(i), 'standard_name', 'projection_y_coordinate', 000)
7088
7089       CALL netcdf_create_att( id_set, id_var_lat(i), 'standard_name', 'latitude', 000)
7090       CALL netcdf_create_att( id_set, id_var_lon(i), 'standard_name', 'longitude', 000)
7091    ENDDO
7092
7093#endif
7094 END SUBROUTINE define_geo_coordinates
7095
7096
7097!------------------------------------------------------------------------------!
7098! Description:
7099! ------------
7100!> Convert UTM coordinates into geographic latitude and longitude. Conversion
7101!> is based on the work of KrÃŒger (1912) DOI: 10.2312/GFZ.b103-krueger28
7102!> and Karney (2013) DOI: 10.1007/s00190-012-0578-z
7103!> Based on a JavaScript of the geodesy function library written by chrisveness
7104!> https://github.com/chrisveness/geodesy
7105!------------------------------------------------------------------------------!
7106 SUBROUTINE convert_utm_to_geographic( crs, eutm, nutm, lon, lat )
7107
7108    USE basic_constants_and_equations_mod,                                     &
7109        ONLY:  pi
7110
7111    IMPLICIT NONE
7112
7113    INTEGER(iwp) ::  j   !< loop index
7114
7115    REAL(wp), INTENT(in)  ::  eutm !< easting (UTM)
7116    REAL(wp), INTENT(out) ::  lat  !< geographic latitude in degree
7117    REAL(wp), INTENT(out) ::  lon  !< geographic longitude in degree
7118    REAL(wp), INTENT(in)  ::  nutm !< northing (UTM)
7119
7120    REAL(wp) ::  a           !< 2*pi*a is the circumference of a meridian
7121    REAL(wp) ::  cos_eta_s   !< cos(eta_s)
7122    REAL(wp) ::  delta_i     !<
7123    REAL(wp) ::  delta_tau_i !<
7124    REAL(wp) ::  e           !< eccentricity
7125    REAL(wp) ::  eta         !<
7126    REAL(wp) ::  eta_s       !<
7127    REAL(wp) ::  n           !< 3rd flattening
7128    REAL(wp) ::  n2          !< n^2
7129    REAL(wp) ::  n3          !< n^3
7130    REAL(wp) ::  n4          !< n^4
7131    REAL(wp) ::  n5          !< n^5
7132    REAL(wp) ::  n6          !< n^6
7133    REAL(wp) ::  nu          !<
7134    REAL(wp) ::  nu_s        !<
7135    REAL(wp) ::  sin_eta_s   !< sin(eta_s)
7136    REAL(wp) ::  sinh_nu_s   !< sinush(nu_s)
7137    REAL(wp) ::  tau_i       !<
7138    REAL(wp) ::  tau_i_s     !<
7139    REAL(wp) ::  tau_s       !<
7140    REAL(wp) ::  x           !< adjusted easting
7141    REAL(wp) ::  y           !< adjusted northing
7142
7143    REAL(wp), DIMENSION(6) ::  beta !< 6th order KrÃŒger expressions
7144
7145    REAL(wp), DIMENSION(8), INTENT(in) ::  crs !< coordinate reference system, consists of
7146                                               !< (/semi_major_axis,
7147                                               !<   inverse_flattening,
7148                                               !<   longitude_of_prime_meridian,
7149                                               !<   longitude_of_central_meridian,
7150                                               !<   scale_factor_at_central_meridian,
7151                                               !<   latitude_of_projection_origin,
7152                                               !<   false_easting,
7153                                               !<   false_northing /)
7154
7155    x = eutm - crs(7)  ! remove false easting
7156    y = nutm - crs(8)  ! remove false northing
7157
7158!-- from Karney 2011 Eq 15-22, 36:
7159    e = SQRT( 1.0_wp / crs(2) * ( 2.0_wp - 1.0_wp / crs(2) ) )
7160    n = 1.0_wp / crs(2) / ( 2.0_wp - 1.0_wp / crs(2) )
7161    n2 = n * n
7162    n3 = n * n2
7163    n4 = n * n3
7164    n5 = n * n4
7165    n6 = n * n5
7166
7167    a = crs(1) / ( 1.0_wp + n ) * ( 1.0_wp + 0.25_wp * n2       &
7168                                           + 0.015625_wp * n4   &
7169                                           + 3.90625E-3_wp * n6 )
7170
7171    nu  = x / ( crs(5) * a )
7172    eta = y / ( crs(5) * a )
7173
7174!-- According to KrÃŒger (1912), eq. 26*
7175    beta(1) =        0.5_wp                  * n  &
7176            -        2.0_wp /         3.0_wp * n2 &
7177            +       37.0_wp /        96.0_wp * n3 &
7178            -        1.0_wp /       360.0_wp * n4 &
7179            -       81.0_wp /       512.0_wp * n5 &
7180            +    96199.0_wp /    604800.0_wp * n6
7181
7182    beta(2) =        1.0_wp /        48.0_wp * n2 &
7183            +        1.0_wp /        15.0_wp * n3 &
7184            -      437.0_wp /      1440.0_wp * n4 &
7185            +       46.0_wp /       105.0_wp * n5 &
7186            -  1118711.0_wp /   3870720.0_wp * n6
7187
7188    beta(3) =       17.0_wp /       480.0_wp * n3 &
7189            -       37.0_wp /       840.0_wp * n4 &
7190            -      209.0_wp /      4480.0_wp * n5 &
7191            +     5569.0_wp /     90720.0_wp * n6
7192
7193    beta(4) =     4397.0_wp /    161280.0_wp * n4 &
7194            -       11.0_wp /       504.0_wp * n5 &
7195            -   830251.0_wp /   7257600.0_wp * n6
7196
7197    beta(5) =     4583.0_wp /    161280.0_wp * n5 &
7198            -   108847.0_wp /   3991680.0_wp * n6
7199
7200    beta(6) = 20648693.0_wp / 638668800.0_wp * n6
7201
7202    eta_s = eta
7203    nu_s  = nu
7204    DO  j = 1, 6
7205      eta_s = eta_s - beta(j) * SIN(2.0_wp * j * eta) * COSH(2.0_wp * j * nu)
7206      nu_s  = nu_s  - beta(j) * COS(2.0_wp * j * eta) * SINH(2.0_wp * j * nu)
7207    ENDDO
7208
7209    sinh_nu_s = SINH( nu_s )
7210    sin_eta_s = SIN( eta_s )
7211    cos_eta_s = COS( eta_s )
7212
7213    tau_s = sin_eta_s / SQRT( sinh_nu_s**2 + cos_eta_s**2 )
7214
7215    tau_i = tau_s
7216    delta_tau_i = 1.0_wp
7217
7218    DO WHILE ( ABS( delta_tau_i ) > 1.0E-12_wp )
7219
7220      delta_i = SINH( e * ATANH( e * tau_i / SQRT( 1.0_wp + tau_i**2 ) ) )
7221
7222      tau_i_s = tau_i   * SQRT( 1.0_wp + delta_i**2 )  &
7223               - delta_i * SQRT( 1.0_wp + tau_i**2 )
7224
7225      delta_tau_i = ( tau_s - tau_i_s ) / SQRT( 1.0_wp + tau_i_s**2 )  &
7226                   * ( 1.0_wp + ( 1.0_wp - e**2 ) * tau_i**2 )          &
7227                   / ( ( 1.0_wp - e**2 ) * SQRT( 1.0_wp + tau_i**2 ) )
7228
7229      tau_i = tau_i + delta_tau_i
7230
7231    ENDDO
7232
7233    lat = ATAN( tau_i ) / pi * 180.0_wp
7234    lon = ATAN2( sinh_nu_s, cos_eta_s ) / pi * 180.0_wp + crs(4)
7235
7236 END SUBROUTINE convert_utm_to_geographic
7237
7238 !------------------------------------------------------------------------------!
7239 ! Description:
7240 ! ------------
7241 !> Compose string containing date and time of format 'YYYY-MM-DD hh:mm:ss ZZZ'
7242 !> from day_of_year and second_of_day.
7243 !------------------------------------------------------------------------------!
7244 FUNCTION date_time_string( day_of_year, second_of_day )
7245
7246    IMPLICIT NONE
7247
7248    CHARACTER(LEN=1) ::  plus_minus  !< either '+' or '-'
7249
7250    CHARACTER(LEN=23) ::  date_time_string  !< string containing date and time
7251
7252    INTEGER(iwp) ::  day          !< day of month
7253    INTEGER(iwp) ::  err          !< error code
7254    INTEGER(iwp) ::  i            !< loop index
7255    INTEGER(iwp) ::  hour         !< hour of the day
7256    INTEGER(iwp) ::  minute       !< minute of the hour
7257    INTEGER(iwp) ::  month        !< month of year
7258    INTEGER(iwp) ::  year = 2019  !< year (no leap year)
7259    INTEGER(iwp) ::  zone = 0     !< time zone
7260
7261    INTEGER(iwp), INTENT(IN) ::  day_of_year  !< day of year to start with
7262
7263    INTEGER, DIMENSION(12) :: days_per_month = &  !< total number of days for
7264    (/31,28,31,30,31,30,31,31,30,31,30,31/)       !< each month (no leap year)
7265
7266    REAL(wp) ::  second  !< second of the minute
7267
7268    REAL(wp), INTENT(IN) ::  second_of_day  !< second of the day
7269
7270
7271    err = 0_iwp
7272!
7273!-- Check day_of_year
7274    IF ( day_of_year < 1_iwp .OR. day_of_year > SUM(days_per_month) )  THEN
7275       err = err + 1_iwp
7276    ENDIF
7277!
7278!-- Check second_of_day
7279    IF ( second_of_day < 0.0_wp  .OR.  second_of_day > 86400.0_wp )  THEN
7280       err = err + 2_iwp
7281    ENDIF
7282!
7283!-- Execute only if given values are valid
7284    IF ( err == 0_iwp )  THEN
7285
7286       day = day_of_year
7287       month = 0_iwp
7288
7289       DO  i = 1, 12
7290          day = day - days_per_month(i)
7291          IF ( day < 0 )  THEN
7292             day = day + days_per_month(i)
7293             month = i
7294             EXIT
7295          ENDIF
7296       ENDDO
7297
7298       hour = INT( second_of_day / 3600.0_wp, KIND=iwp )
7299
7300       second = second_of_day - 3600.0_wp * REAL( hour, KIND=wp )
7301
7302       minute =  INT( second / 60.0_wp, KIND=iwp )
7303
7304       second = second - 60.0_wp * REAL( minute, KIND=wp )
7305
7306       IF ( zone < 0_iwp )  THEN
7307          plus_minus = '-'
7308       ELSE
7309          plus_minus = '+'
7310       ENDIF
7311
7312       WRITE( date_time_string, 100 )                               &
7313          year, month, day, hour, minute, INT( second, KIND=iwp ),  &
7314          plus_minus, zone
7315
7316    ELSE
7317!
7318!--   Return empty string if input is invalid
7319      date_time_string = REPEAT( " ", LEN(date_time_string) )
7320
7321    ENDIF
7322
7323 100 FORMAT (I4,'-',I2.2,'-',I2.2,1X,I2.2,':',I2.2,':',I2.2,1X,A1,I2.2)
7324
7325 END FUNCTION date_time_string
7326
7327 END MODULE netcdf_interface
Note: See TracBrowser for help on using the repository browser.