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

Last change on this file since 3485 was 3485, checked in by gronemeier, 6 years ago

Add information about reference point to output files; corrected calculation of longitude values in case crs is not defined in input file

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