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

Last change on this file since 4393 was 4360, checked in by suehring, 5 years ago

Bugfix in output of time-averaged plant-canopy quanities; Output of plant-canopy data only where tall canopy is defined; land-surface model: fix wrong location strings; tests: update urban test case; all source code files: copyright update

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