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

Last change on this file since 3529 was 3529, checked in by gronemeier, 7 years ago

change date format in output files; add global attributes; change fill_value; move definition of UTM and lon/lat into subroutine; change attributes of time variable; read optional attributes from input netcdf file; update test cases

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