source: palm/trunk/SOURCE/netcdf.f90 @ 1342

Last change on this file since 1342 was 1323, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 202.8 KB
Line 
1#if defined( __ibmy_special )
2@PROCESS NOOPTimize
3#endif
4 SUBROUTINE define_netcdf_header( callmode, extend, av )
5
6!--------------------------------------------------------------------------------!
7! This file is part of PALM.
8!
9! PALM is free software: you can redistribute it and/or modify it under the terms
10! of the GNU General Public License as published by the Free Software Foundation,
11! either version 3 of the License, or (at your option) any later version.
12!
13! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
14! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
15! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
16!
17! You should have received a copy of the GNU General Public License along with
18! PALM. If not, see <http://www.gnu.org/licenses/>.
19!
20! Copyright 1997-2014 Leibniz Universitaet Hannover
21!--------------------------------------------------------------------------------!
22!
23! Current revisions:
24! ------------------
25!
26!
27! Former revisions:
28! -----------------
29! $Id: netcdf.f90 1323 2014-03-20 17:09:54Z kanani $
30!
31! 1322 2014-03-20 16:38:49Z raasch
32! Forgotten ONLY-attribute added to USE-statements
33!
34! 1320 2014-03-20 08:40:49Z raasch
35! ONLY-attribute added to USE-statements,
36! kind-parameters added to all INTEGER and REAL declaration statements,
37! kinds are defined in new module kinds,
38! revision history before 2012 removed,
39! comment fields (!:) to be used for variable explanations added to
40! all variable declaration statements
41!
42! 1308 2014-03-13 14:58:42Z fricke
43! +ntime_count, oldmode
44! Adjust NF90_CREATE and NF90_OPEN statement for parallel output
45! To increase the performance for parallel output, the following is done:
46! - Limit time dimension
47! - Values of axis data are only written by PE0
48! - No fill is set for all variables
49! Check the number of output time levels for restart jobs
50!
51! 1206 2013-07-18 12:49:16Z witha
52! Bugfix: typo in preprocessor directive in subroutine open_write_netcdf_file
53!
54! 1092 2013-02-02 11:24:22Z raasch
55! unused variables removed
56!
57! 1053 2012-11-13 17:11:03Z hoffmann
58! +qr, nr, prr
59!
60! 1036 2012-10-22 13:43:42Z raasch
61! code put under GPL (PALM 3.9)
62!
63! 1031 2012-10-19 14:35:30Z raasch
64! netCDF4 without parallel file support implemented, new routines
65! create_netcdf_file and open_write_netcdf_file at end
66!
67! 992 2012-09-05 15:08:26Z hoffmann
68! Removal of the informative messages PA0352 and PA0353.
69
70! 983 2012-08-21 14:17:57Z hoffmann
71! Bugfix in cross_profiles.
72!
73! 964 2012-07-26 09:14:24Z raasch
74! rev 951 and 959 reformatted
75!
76! 959 2012-07-24 13:13:41Z hoffmann
77! Bugfix in cross_profiles. It is not allowed to arrange more than 100
78! profiles with cross_profiles.
79!
80! 951 2012-07-19 14:22:52Z hoffmann
81! cross_profiles, profile_rows, profile_columns are written to netCDF header
82!
83! Revision 1.1  2005/05/18 15:37:16  raasch
84! Initial revision
85!
86!
87! Description:
88! ------------
89! In case of extend = .FALSE.:
90! Define all necessary dimensions, axes and variables for the different
91! netCDF datasets. This subroutine is called from check_open after a new
92! dataset is created. It leaves the open netCDF files ready to write.
93!
94! In case of extend = .TRUE.:
95! Find out if dimensions and variables of an existing file match the values
96! of the actual run. If so, get all necessary informations (ids, etc.) from
97! this file.
98!
99! Parameter av can assume values 0 (non-averaged data) and 1 (time averaged
100! data)
101!------------------------------------------------------------------------------!
102#if defined( __netcdf )
103
104    USE arrays_3d,                                                              &
105        ONLY:  zu, zw
106
107    USE constants,                                                              &
108        ONLY:  pi
109
110    USE control_parameters,                                                     &
111        ONLY:  averaging_interval, averaging_interval_pr, averaging_interval_sp,&
112        data_output_pr,  domask,  dopr_n,dopr_time_count, dopts_time_count,     &
113        dots_time_count, dosp_time_count, do2d, do2d_xz_time_count, do3d,       &
114        do2d_yz_time_count, mask_size, do2d_xy_time_count, do3d_time_count,     &
115        domask_time_count, mask_i_global, mask_j_global,mask_k_global,          &
116        message_string, mid, netcdf_data_format, netcdf_precision, ntdim_2d_xy, &
117        ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,            &
118        run_description_header, section, simulated_time, topography
119
120    USE grid_variables,                                                         &
121        ONLY:  dx, dy, zu_s_inner, zw_w_inner
122
123    USE indices,                                                                &
124        ONLY:  nx, ny, nz ,nzb, nzt
125
126    USE netcdf_control
127
128    USE kinds
129
130    USE pegrid
131
132    USE particle_attributes,                                                    &
133        ONLY:  maximum_number_of_particles, number_of_particle_groups
134
135    USE profil_parameter,                                                       &
136        ONLY:  crmax, cross_profiles, dopr_index,profile_columns, profile_rows
137
138    USE spectrum,                                                               &
139        ONLY:  comp_spectra_level, data_output_sp, spectra_direction
140
141    USE statistics,                                                             &
142        ONLY:  hom, statistic_regions
143
144
145    IMPLICIT NONE
146
147    CHARACTER (LEN=2)              ::  suffix                !:
148    CHARACTER (LEN=2), INTENT (IN) ::  callmode              !:
149    CHARACTER (LEN=3)              ::  suffix1               !:
150    CHARACTER (LEN=4)              ::  grid_x                !:
151    CHARACTER (LEN=4)              ::  grid_y                !:
152    CHARACTER (LEN=4)              ::  grid_z                !:
153    CHARACTER (LEN=6)              ::  mode                  !:
154    CHARACTER (LEN=10)             ::  netcdf_var_name       !:
155    CHARACTER (LEN=10)             ::  precision             !:
156    CHARACTER (LEN=10)             ::  var                   !:
157    CHARACTER (LEN=80)             ::  time_average_text     !:
158    CHARACTER (LEN=2000)           ::  char_cross_profiles   !:
159    CHARACTER (LEN=2000)           ::  var_list              !:
160    CHARACTER (LEN=2000)           ::  var_list_old          !:
161
162    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_adj   !:
163    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_char  !:
164
165    INTEGER(iwp) ::  av                                      !:
166    INTEGER(iwp) ::  cross_profiles_count                    !:
167    INTEGER(iwp) ::  cross_profiles_maxi                     !:
168    INTEGER(iwp) ::  delim                                   !:
169    INTEGER(iwp) ::  delim_old                               !:
170    INTEGER(iwp) ::  file_id                                 !:
171    INTEGER(iwp) ::  i                                       !:
172    INTEGER(iwp) ::  id_last                                 !:
173    INTEGER(iwp) ::  id_x                                    !:
174    INTEGER(iwp) ::  id_y                                    !:
175    INTEGER(iwp) ::  id_z                                    !:
176    INTEGER(iwp) ::  j                                       !:
177    INTEGER(iwp) ::  k                                       !:
178    INTEGER(iwp) ::  kk                                      !:
179    INTEGER(iwp) ::  ns                                      !:
180    INTEGER(iwp) ::  ns_old                                  !:
181    INTEGER(iwp) ::  ntime_count                             !:
182    INTEGER(iwp) ::  nz_old                                  !:
183
184    INTEGER(iwp), SAVE ::  oldmode                           !:
185
186    INTEGER(iwp), DIMENSION(1) ::  id_dim_time_old           !:
187    INTEGER(iwp), DIMENSION(1) ::  id_dim_x_yz_old           !:
188    INTEGER(iwp), DIMENSION(1) ::  id_dim_y_xz_old           !:
189    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_sp_old          !:
190    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_xy_old          !:
191    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_3d_old          !:
192    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_mask_old        !:
193
194
195    INTEGER(iwp), DIMENSION(1:crmax) ::  cross_profiles_numb !:
196
197    LOGICAL ::  found                                        !:
198
199    LOGICAL, INTENT (INOUT) ::  extend                       !:
200
201    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !:
202
203    REAL(wp), DIMENSION(1) ::  last_time_coordinate          !:
204
205    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  netcdf_data    !:
206    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  netcdf_data_2d !:
207
208!
209!-- Initializing actions (return to calling routine check_parameters afterwards)
210    IF ( .NOT. init_netcdf )  THEN
211!
212!--    Check and set accuracy for netCDF output. First set default value
213       nc_precision = NF90_REAL4
214
215       i = 1
216       DO  WHILE ( netcdf_precision(i) /= ' ' )
217          j = INDEX( netcdf_precision(i), '_' )
218          IF ( j == 0 )  THEN
219             WRITE ( message_string, * ) 'netcdf_precision must contain a ', &
220                                         '"_"netcdf_precision(', i, ')="',   &
221                                         TRIM( netcdf_precision(i) ),'"'
222             CALL message( 'define_netcdf_header', 'PA0241', 1, 2, 0, 6, 0 )
223          ENDIF
224
225          var       = netcdf_precision(i)(1:j-1)
226          precision = netcdf_precision(i)(j+1:)
227
228          IF ( precision == 'NF90_REAL4' )  THEN
229             j = NF90_REAL4
230          ELSEIF ( precision == 'NF90_REAL8' )  THEN
231             j = NF90_REAL8
232          ELSE
233             WRITE ( message_string, * ) 'illegal netcdf precision: ',  &
234                                         'netcdf_precision(', i, ')="', &
235                                         TRIM( netcdf_precision(i) ),'"'
236             CALL message( 'define_netcdf_header', 'PA0242', 1, 2, 0, 6, 0 )
237          ENDIF
238
239          SELECT CASE ( var )
240             CASE ( 'xy' )
241                nc_precision(1) = j
242             CASE ( 'xz' )
243                nc_precision(2) = j
244             CASE ( 'yz' )
245                nc_precision(3) = j
246             CASE ( '2d' )
247                nc_precision(1:3) = j
248             CASE ( '3d' )
249                nc_precision(4) = j
250             CASE ( 'pr' )
251                nc_precision(5) = j
252             CASE ( 'ts' )
253                nc_precision(6) = j
254             CASE ( 'sp' )
255                nc_precision(7) = j
256             CASE ( 'prt' )
257                nc_precision(8) = j
258             CASE ( 'masks' )
259                nc_precision(11) = j
260             CASE ( 'all' )
261                nc_precision    = j
262
263             CASE DEFAULT
264                WRITE ( message_string, * ) 'unknown variable in inipar ',    & 
265                                  'assignment: netcdf_precision(', i, ')="',  &
266                                            TRIM( netcdf_precision(i) ),'"'
267                CALL message( 'define_netcdf_header', 'PA0243', 1, 2, 0, 6, 0 ) 
268
269          END SELECT
270
271          i = i + 1
272          IF ( i > 50 )  EXIT
273       ENDDO
274
275       init_netcdf = .TRUE.
276
277       RETURN
278
279    ENDIF
280
281!
282!-- Determine the mode to be processed
283    IF ( extend )  THEN
284       mode = callmode // '_ext'
285    ELSE
286       mode = callmode // '_new'
287    ENDIF
288
289!
290!-- Select the mode to be processed. Possibilities are 3d, mask, xy, xz, yz,
291!-- pr and ts.
292    SELECT CASE ( mode )
293
294       CASE ( 'ma_new' )
295
296!
297!--       decompose actual parameter file_id (=formal parameter av) into
298!--       mid and av
299          file_id = av
300          IF ( file_id <= 200+max_masks )  THEN
301             mid = file_id - 200
302             av = 0
303          ELSE
304             mid = file_id - (200+max_masks)
305             av = 1
306          ENDIF
307
308!
309!--       Define some global attributes of the dataset
310          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
311               'Conventions', 'COARDS' )
312          CALL handle_netcdf_error( 'netcdf', 464 )
313
314          IF ( av == 0 )  THEN
315             time_average_text = ' '
316          ELSE
317             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
318                                                            averaging_interval
319          ENDIF
320          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title', &
321                                  TRIM( run_description_header ) //    &
322                                  TRIM( time_average_text ) )
323          CALL handle_netcdf_error( 'netcdf', 465 )
324          IF ( av == 1 )  THEN
325             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
326             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
327                                     'time_avg', TRIM( time_average_text ) )
328             CALL handle_netcdf_error( 'netcdf', 466 )
329          ENDIF
330
331!
332!--       Define time coordinate for volume data (unlimited dimension)
333          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'time', NF90_UNLIMITED, &
334                                  id_dim_time_mask(mid,av) )
335          CALL handle_netcdf_error( 'netcdf', 467 )
336
337          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'time', NF90_DOUBLE, &
338                                  id_dim_time_mask(mid,av), &
339                                  id_var_time_mask(mid,av) )
340          CALL handle_netcdf_error( 'netcdf', 468 )
341
342          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
343                                  id_var_time_mask(mid,av), 'units', &
344                                  'seconds')
345          CALL handle_netcdf_error( 'netcdf', 469 )
346
347!
348!--       Define spatial dimensions and coordinates:
349!--       Define vertical coordinate grid (zu grid)
350          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'zu_3d', &
351                                  mask_size(mid,3), id_dim_zu_mask(mid,av) )
352          CALL handle_netcdf_error( 'netcdf', 470 )
353
354          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zu_3d', NF90_DOUBLE, &
355                                  id_dim_zu_mask(mid,av), &
356                                  id_var_zu_mask(mid,av) )
357          CALL handle_netcdf_error( 'netcdf', 471 )
358
359          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
360                                  'units', 'meters' )
361          CALL handle_netcdf_error( 'netcdf', 472 )
362
363!
364!--       Define vertical coordinate grid (zw grid)
365          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'zw_3d', &
366                                  mask_size(mid,3), id_dim_zw_mask(mid,av) )
367          CALL handle_netcdf_error( 'netcdf', 473 )
368
369          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zw_3d', NF90_DOUBLE, &
370                                  id_dim_zw_mask(mid,av), &
371                                  id_var_zw_mask(mid,av) )
372          CALL handle_netcdf_error( 'netcdf', 474 )
373
374          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
375                                  'units', 'meters' )
376          CALL handle_netcdf_error( 'netcdf', 475 )
377
378!
379!--       Define x-axis (for scalar position)
380          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'x', &
381                                  mask_size(mid,1), id_dim_x_mask(mid,av) )
382          CALL handle_netcdf_error( 'netcdf', 476 )
383
384          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'x', NF90_DOUBLE, &
385                                  id_dim_x_mask(mid,av), id_var_x_mask(mid,av) )
386          CALL handle_netcdf_error( 'netcdf', 477 )
387
388          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_x_mask(mid,av), &
389                                  'units', 'meters' )
390          CALL handle_netcdf_error( 'netcdf', 478 )
391
392!
393!--       Define x-axis (for u position)
394          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'xu', &
395                                  mask_size(mid,1), id_dim_xu_mask(mid,av) )
396          CALL handle_netcdf_error( 'netcdf', 479 )
397
398          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'xu', NF90_DOUBLE, &
399                                  id_dim_xu_mask(mid,av), &
400                                  id_var_xu_mask(mid,av) )
401          CALL handle_netcdf_error( 'netcdf', 480 )
402
403          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_xu_mask(mid,av), &
404                                  'units', 'meters' )
405          CALL handle_netcdf_error( 'netcdf', 481 )
406
407!
408!--       Define y-axis (for scalar position)
409          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'y', &
410                                  mask_size(mid,2), id_dim_y_mask(mid,av) )
411          CALL handle_netcdf_error( 'netcdf', 482 )
412
413          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'y', NF90_DOUBLE, &
414                                  id_dim_y_mask(mid,av), id_var_y_mask(mid,av) )
415          CALL handle_netcdf_error( 'netcdf', 483 )
416
417          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_y_mask(mid,av), &
418                                  'units', 'meters' )
419          CALL handle_netcdf_error( 'netcdf', 484 )
420
421!
422!--       Define y-axis (for v position)
423          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'yv', &
424                                  mask_size(mid,2), id_dim_yv_mask(mid,av) )
425          CALL handle_netcdf_error( 'netcdf', 485 )
426
427          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'yv', NF90_DOUBLE, &
428                                  id_dim_yv_mask(mid,av), &
429                                  id_var_yv_mask(mid,av) )
430          CALL handle_netcdf_error( 'netcdf', 486 )
431
432          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
433                                  'units', 'meters' )
434          CALL handle_netcdf_error( 'netcdf', 487 )
435
436!
437!--       In case of non-flat topography define 2d-arrays containing the height
438!--       informations
439          IF ( TRIM( topography ) /= 'flat' )  THEN
440!
441!--          Define zusi = zu(nzb_s_inner)
442             nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zusi', NF90_DOUBLE, &
443                                     (/ id_dim_x_mask(mid,av),    &
444                                        id_dim_y_mask(mid,av) /), &
445                                     id_var_zusi_mask(mid,av) )
446             CALL handle_netcdf_error( 'netcdf', 488 )
447             
448             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
449                                     id_var_zusi_mask(mid,av), &
450                                     'units', 'meters' )
451             CALL handle_netcdf_error( 'netcdf', 489 )
452             
453             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
454                                     id_var_zusi_mask(mid,av), &
455                                     'long_name', 'zu(nzb_s_inner)' )
456             CALL handle_netcdf_error( 'netcdf', 490 )
457
458!             
459!--          Define zwwi = zw(nzb_w_inner)
460             nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zwwi', NF90_DOUBLE, &
461                                     (/ id_dim_x_mask(mid,av),    &
462                                        id_dim_y_mask(mid,av) /), &
463                                     id_var_zwwi_mask(mid,av) )
464             CALL handle_netcdf_error( 'netcdf', 491 )
465             
466             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
467                                     id_var_zwwi_mask(mid,av), &
468                                     'units', 'meters' )
469             CALL handle_netcdf_error( 'netcdf', 492 )
470             
471             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
472                                     id_var_zwwi_mask(mid,av), &
473                                     'long_name', 'zw(nzb_w_inner)' )
474             CALL handle_netcdf_error( 'netcdf', 493 )
475
476          ENDIF             
477
478
479!
480!--       Define the variables
481          var_list = ';'
482          i = 1
483
484          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
485
486!
487!--          Check for the grid
488             found = .TRUE.
489             SELECT CASE ( domask(mid,av,i) )
490!
491!--             Most variables are defined on the scalar grid
492                CASE ( 'e', 'lpt', 'nr', 'p', 'pc', 'pr', 'prr', 'pt', 'q',&
493                       'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',    &
494                       'rho', 's', 'sa', 'vpt' )
495
496                   grid_x = 'x'
497                   grid_y = 'y'
498                   grid_z = 'zu'
499!
500!--             u grid
501                CASE ( 'u' )
502
503                   grid_x = 'xu'
504                   grid_y = 'y'
505                   grid_z = 'zu'
506!
507!--             v grid
508                CASE ( 'v' )
509
510                   grid_x = 'x'
511                   grid_y = 'yv'
512                   grid_z = 'zu'
513!
514!--             w grid
515                CASE ( 'w' )
516
517                   grid_x = 'x'
518                   grid_y = 'y'
519                   grid_z = 'zw'
520
521                CASE DEFAULT
522!
523!--                Check for user-defined quantities
524                   CALL user_define_netcdf_grid( domask(mid,av,i), found, &
525                                                 grid_x, grid_y, grid_z )
526
527             END SELECT
528
529!
530!--          Select the respective dimension ids
531             IF ( grid_x == 'x' )  THEN
532                id_x = id_dim_x_mask(mid,av)
533             ELSEIF ( grid_x == 'xu' )  THEN
534                id_x = id_dim_xu_mask(mid,av)
535             ENDIF
536
537             IF ( grid_y == 'y' )  THEN
538                id_y = id_dim_y_mask(mid,av)
539             ELSEIF ( grid_y == 'yv' )  THEN
540                id_y = id_dim_yv_mask(mid,av)
541             ENDIF
542
543             IF ( grid_z == 'zu' )  THEN
544                id_z = id_dim_zu_mask(mid,av)
545             ELSEIF ( grid_z == 'zw' )  THEN
546                id_z = id_dim_zw_mask(mid,av)
547             ENDIF
548
549!
550!--          Define the grid
551             nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), domask(mid,av,i), &
552                                     nc_precision(11),            &
553                                     (/ id_x, id_y, id_z,                   &
554                                        id_dim_time_mask(mid,av) /),        &
555                                     id_var_domask(mid,av,i) )
556
557             IF ( .NOT. found )  THEN
558                WRITE ( message_string, * ) 'no grid defined for', &
559                     ' variable ', TRIM( domask(mid,av,i) )
560                CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
561             ENDIF
562
563             var_list = TRIM( var_list ) // TRIM( domask(mid,av,i) ) // ';'
564
565             CALL handle_netcdf_error( 'netcdf', 494 )
566!
567!--          Store the 'real' name of the variable (with *, for example)
568!--          in the long_name attribute. This is evaluated by Ferret,
569!--          for example.
570             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av),     &
571                                     id_var_domask(mid,av,i), &
572                                     'long_name', domask(mid,av,i) )
573             CALL handle_netcdf_error( 'netcdf', 495 )
574!
575!--          Define the variable's unit
576             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
577                                     id_var_domask(mid,av,i), &
578                                     'units', TRIM( domask_unit(mid,av,i) ) )
579             CALL handle_netcdf_error( 'netcdf', 496 )
580
581             i = i + 1
582
583          ENDDO
584
585!
586!--       No arrays to output
587          IF ( i == 1 )  RETURN
588
589!
590!--       Write the list of variables as global attribute (this is used by
591!--       restart runs and by combine_plot_fields)
592          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
593                                  'VAR_LIST', var_list )
594          CALL handle_netcdf_error( 'netcdf', 497 )
595
596!
597!--       Leave netCDF define mode
598          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
599          CALL handle_netcdf_error( 'netcdf', 498 )
600
601!
602!--       Write data for x (shifted by +dx/2) and xu axis
603          ALLOCATE( netcdf_data(mask_size(mid,1)) )
604
605          netcdf_data = ( mask_i_global(mid,:mask_size(mid,1)) + 0.5 ) * dx
606
607          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_x_mask(mid,av), &
608                                  netcdf_data, start = (/ 1 /),               &
609                                  count = (/ mask_size(mid,1) /) )
610          CALL handle_netcdf_error( 'netcdf', 499 )
611
612          netcdf_data = mask_i_global(mid,:mask_size(mid,1)) * dx
613
614          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_xu_mask(mid,av),&
615                                  netcdf_data, start = (/ 1 /),               &
616                                  count = (/ mask_size(mid,1) /) )
617          CALL handle_netcdf_error( 'netcdf', 500 )
618
619          DEALLOCATE( netcdf_data )
620
621!
622!--       Write data for y (shifted by +dy/2) and yv axis
623          ALLOCATE( netcdf_data(mask_size(mid,2)) )
624
625          netcdf_data = ( mask_j_global(mid,:mask_size(mid,2)) + 0.5 ) * dy
626
627          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_y_mask(mid,av), &
628                                  netcdf_data, start = (/ 1 /),               &
629                                  count = (/ mask_size(mid,2) /))
630          CALL handle_netcdf_error( 'netcdf', 501 )
631
632          netcdf_data = mask_j_global(mid,:mask_size(mid,2)) * dy
633
634          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
635                                  netcdf_data, start = (/ 1 /),    &
636                                  count = (/ mask_size(mid,2) /))
637          CALL handle_netcdf_error( 'netcdf', 502 )
638
639          DEALLOCATE( netcdf_data )
640
641!
642!--       Write zu and zw data (vertical axes)
643          ALLOCATE( netcdf_data(mask_size(mid,3)) )
644
645          netcdf_data = zu( mask_k_global(mid,:mask_size(mid,3)) )
646
647          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
648                                  netcdf_data, start = (/ 1 /), &
649                                  count = (/ mask_size(mid,3) /) )
650          CALL handle_netcdf_error( 'netcdf', 503 )
651
652          netcdf_data = zw( mask_k_global(mid,:mask_size(mid,3)) )
653
654          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
655                                  netcdf_data, start = (/ 1 /), &
656                                  count = (/ mask_size(mid,3) /) )
657          CALL handle_netcdf_error( 'netcdf', 504 )
658
659          DEALLOCATE( netcdf_data )
660
661!
662!--       In case of non-flat topography write height information
663          IF ( TRIM( topography ) /= 'flat' )  THEN
664
665             ALLOCATE( netcdf_data_2d(mask_size(mid,1),mask_size(mid,2)) )
666             netcdf_data_2d = zu_s_inner( mask_i_global(mid,:mask_size(mid,1)),&
667                                          mask_j_global(mid,:mask_size(mid,2)) )
668
669             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),         &
670                                     id_var_zusi_mask(mid,av),    &
671                                     netcdf_data_2d,              &
672                                     start = (/ 1, 1 /),          &
673                                     count = (/ mask_size(mid,1), &
674                                                mask_size(mid,2) /) )
675             CALL handle_netcdf_error( 'netcdf', 505 )
676
677             netcdf_data_2d = zw_w_inner( mask_i_global(mid,:mask_size(mid,1)),&
678                                          mask_j_global(mid,:mask_size(mid,2)) )
679
680             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),         &
681                                     id_var_zwwi_mask(mid,av),    &
682                                     netcdf_data_2d,              &
683                                     start = (/ 1, 1 /),          &
684                                     count = (/ mask_size(mid,1), &
685                                                mask_size(mid,2) /) )
686             CALL handle_netcdf_error( 'netcdf', 506 )
687
688             DEALLOCATE( netcdf_data_2d )
689
690          ENDIF
691!
692!--       restore original parameter file_id (=formal parameter av) into av
693          av = file_id
694
695
696       CASE ( 'ma_ext' )
697
698!
699!--       decompose actual parameter file_id (=formal parameter av) into
700!--       mid and av
701          file_id = av
702          IF ( file_id <= 200+max_masks )  THEN
703             mid = file_id - 200
704             av = 0
705          ELSE
706             mid = file_id - (200+max_masks)
707             av = 1
708          ENDIF
709
710!
711!--       Get the list of variables and compare with the actual run.
712!--       First var_list_old has to be reset, since GET_ATT does not assign
713!--       trailing blanks.
714          var_list_old = ' '
715          nc_stat = NF90_GET_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST',&
716                                  var_list_old )
717          CALL handle_netcdf_error( 'netcdf', 507 )
718
719          var_list = ';'
720          i = 1
721          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
722             var_list = TRIM(var_list) // TRIM( domask(mid,av,i) ) // ';'
723             i = i + 1
724          ENDDO
725
726          IF ( av == 0 )  THEN
727             var = '(mask)'
728          ELSE
729             var = '(mask_av)'
730          ENDIF
731
732          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
733             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ), &
734                  ' data for mask', mid, ' from previous run found,', &
735                  '&but this file cannot be extended due to variable ', &
736                  'mismatch.&New file is created instead.'
737             CALL message( 'define_netcdf_header', 'PA0335', 0, 1, 0, 6, 0 )
738             extend = .FALSE.
739             RETURN
740          ENDIF
741
742!
743!--       Get and compare the number of vertical gridpoints
744          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'zu', &
745                                    id_var_zu_mask(mid,av) )
746          CALL handle_netcdf_error( 'netcdf', 508 )
747
748          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),     &
749                                           id_var_zu_mask(mid,av),  &
750                                           dimids = id_dim_zu_mask_old )
751          CALL handle_netcdf_error( 'netcdf', 509 )
752          id_dim_zu_mask(mid,av) = id_dim_zu_mask_old(1)
753
754          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av),    &
755                                            id_dim_zu_mask(mid,av), &
756                                            len = nz_old )
757          CALL handle_netcdf_error( 'netcdf', 510 )
758
759          IF ( mask_size(mid,3) /= nz_old )  THEN
760             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ), &
761                  ' data for mask', mid, ' from previous run found,', &
762                  '&but this file cannot be extended due to mismatch in ', &
763                  ' number of&vertical grid points.', &
764                  '&New file is created instead.'
765             CALL message( 'define_netcdf_header', 'PA0336', 0, 1, 0, 6, 0 )
766             extend = .FALSE.
767             RETURN
768          ENDIF
769
770!
771!--       Get the id of the time coordinate (unlimited coordinate) and its
772!--       last index on the file. The next time level is plmask..count+1.
773!--       The current time must be larger than the last output time
774!--       on the file.
775          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'time', &
776                                    id_var_time_mask(mid,av) )
777          CALL handle_netcdf_error( 'netcdf', 511 )
778
779          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av), &
780                                           id_var_time_mask(mid,av), &
781                                           dimids = id_dim_time_old )
782          CALL handle_netcdf_error( 'netcdf', 512 )
783          id_dim_time_mask(mid,av) = id_dim_time_old(1)
784
785          nc_stat = NF90_INQUIRE_DIMENSION( id_set_mask(mid,av), &
786                                            id_dim_time_mask(mid,av), &
787                                            len = domask_time_count(mid,av) )
788          CALL handle_netcdf_error( 'netcdf', 513 )
789
790          nc_stat = NF90_GET_VAR( id_set_mask(mid,av), &
791                                  id_var_time_mask(mid,av), &
792                                  last_time_coordinate,              &
793                                  start = (/ domask_time_count(mid,av) /), &
794                                  count = (/ 1 /) )
795          CALL handle_netcdf_error( 'netcdf', 514 )
796
797          IF ( last_time_coordinate(1) >= simulated_time )  THEN
798             WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ), &
799                  ' data for mask', mid, ' from previous run found,', &
800                  '&but this file cannot be extended because the current ', &
801                  'output time&is less or equal than the last output time ', &
802                  'on this file.&New file is created instead.'
803             CALL message( 'define_netcdf_header', 'PA0337', 0, 1, 0, 6, 0 )
804             domask_time_count(mid,av) = 0
805             extend = .FALSE.
806             RETURN
807          ENDIF
808
809!
810!--       Dataset seems to be extendable.
811!--       Now get the variable ids.
812          i = 1
813          DO WHILE ( domask(mid,av,i)(1:1) /= ' ' )
814             nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), &
815                                       TRIM( domask(mid,av,i) ), &
816                                       id_var_domask(mid,av,i) )
817             CALL handle_netcdf_error( 'netcdf', 515 )
818             i = i + 1
819          ENDDO
820
821!
822!--       Update the title attribute on file
823!--       In order to avoid 'data mode' errors if updated attributes are larger
824!--       than their original size, NF90_PUT_ATT is called in 'define mode'
825!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
826!--       performance loss due to data copying; an alternative strategy would be
827!--       to ensure equal attribute size in a job chain. Maybe revise later.
828          IF ( av == 0 )  THEN
829             time_average_text = ' '
830          ELSE
831             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
832                                                            averaging_interval
833          ENDIF
834          nc_stat = NF90_REDEF( id_set_mask(mid,av) )
835          CALL handle_netcdf_error( 'netcdf', 516 )
836          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title', &
837                                  TRIM( run_description_header ) //    &
838                                  TRIM( time_average_text ) )
839          CALL handle_netcdf_error( 'netcdf', 517 )
840          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
841          CALL handle_netcdf_error( 'netcdf', 518 )
842          WRITE ( message_string, * ) 'netCDF file for ', TRIM( var ), &
843               ' data for mask', mid, ' from previous run found.', &
844               '&This file will be extended.'
845          CALL message( 'define_netcdf_header', 'PA0338', 0, 0, 0, 6, 0 )
846!
847!--       restore original parameter file_id (=formal parameter av) into av
848          av = file_id
849
850
851       CASE ( '3d_new' )
852
853!
854!--       Define some global attributes of the dataset
855          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'Conventions', &
856                                  'COARDS' )
857          CALL handle_netcdf_error( 'netcdf', 62 )
858
859          IF ( av == 0 )  THEN
860             time_average_text = ' '
861          ELSE
862             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
863                                                            averaging_interval
864          ENDIF
865          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title', &
866                                  TRIM( run_description_header ) //    &
867                                  TRIM( time_average_text ) )
868          CALL handle_netcdf_error( 'netcdf', 63 )
869          IF ( av == 1 )  THEN
870             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
871             nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'time_avg', &
872                                     TRIM( time_average_text ) )
873             CALL handle_netcdf_error( 'netcdf', 63 )
874          ENDIF
875
876!
877!--       Define time coordinate for volume data.
878!--       For parallel output the time dimensions has to be limited, otherwise
879!--       the performance drops significantly.
880          IF ( netcdf_data_format < 5 )  THEN
881             nc_stat = NF90_DEF_DIM( id_set_3d(av), 'time', NF90_UNLIMITED, &
882                                     id_dim_time_3d(av) )
883             CALL handle_netcdf_error( 'netcdf', 64 )
884          ELSE
885             nc_stat = NF90_DEF_DIM( id_set_3d(av), 'time', ntdim_3d(av), &
886                                     id_dim_time_3d(av) )
887             CALL handle_netcdf_error( 'netcdf', 523 )
888          ENDIF
889
890          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'time', NF90_DOUBLE, &
891                                  id_dim_time_3d(av), id_var_time_3d(av) )
892          CALL handle_netcdf_error( 'netcdf', 65 )
893
894          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_time_3d(av), 'units', &
895                                  'seconds')
896          CALL handle_netcdf_error( 'netcdf', 66 )
897
898!
899!--       Define spatial dimensions and coordinates:
900!--       Define vertical coordinate grid (zu grid)
901          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'zu_3d', nz_do3d-nzb+1, &
902                                  id_dim_zu_3d(av) )
903          CALL handle_netcdf_error( 'netcdf', 67 )
904
905          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zu_3d', NF90_DOUBLE, &
906                                  id_dim_zu_3d(av), id_var_zu_3d(av) )
907          CALL handle_netcdf_error( 'netcdf', 68 )
908
909          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zu_3d(av), 'units', &
910                                  'meters' )
911          CALL handle_netcdf_error( 'netcdf', 69 )
912
913!
914!--       Define vertical coordinate grid (zw grid)
915          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'zw_3d', nz_do3d-nzb+1, &
916                                  id_dim_zw_3d(av) )
917          CALL handle_netcdf_error( 'netcdf', 70 )
918
919          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zw_3d', NF90_DOUBLE, &
920                                  id_dim_zw_3d(av), id_var_zw_3d(av) )
921          CALL handle_netcdf_error( 'netcdf', 71 )
922
923          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zw_3d(av), 'units', &
924                                  'meters' )
925          CALL handle_netcdf_error( 'netcdf', 72 )
926
927!
928!--       Define x-axis (for scalar position)
929          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'x', nx+2, id_dim_x_3d(av) )
930          CALL handle_netcdf_error( 'netcdf', 73 )
931
932          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'x', NF90_DOUBLE, &
933                                  id_dim_x_3d(av), id_var_x_3d(av) )
934          CALL handle_netcdf_error( 'netcdf', 74 )
935
936          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_x_3d(av), 'units', &
937                                  'meters' )
938          CALL handle_netcdf_error( 'netcdf', 75 )
939
940!
941!--       Define x-axis (for u position)
942          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'xu', nx+2, id_dim_xu_3d(av) )
943          CALL handle_netcdf_error( 'netcdf', 358 )
944
945          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'xu', NF90_DOUBLE, &
946                                  id_dim_xu_3d(av), id_var_xu_3d(av) )
947          CALL handle_netcdf_error( 'netcdf', 359 )
948
949          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_xu_3d(av), 'units', &
950                                  'meters' )
951          CALL handle_netcdf_error( 'netcdf', 360 )
952
953!
954!--       Define y-axis (for scalar position)
955          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'y', ny+2, id_dim_y_3d(av) )
956          CALL handle_netcdf_error( 'netcdf', 76 )
957
958          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'y', NF90_DOUBLE, &
959                                  id_dim_y_3d(av), id_var_y_3d(av) )
960          CALL handle_netcdf_error( 'netcdf', 77 )
961
962          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_y_3d(av), 'units', &
963                                  'meters' )
964          CALL handle_netcdf_error( 'netcdf', 78 )
965
966!
967!--       Define y-axis (for v position)
968          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'yv', ny+2, id_dim_yv_3d(av) )
969          CALL handle_netcdf_error( 'netcdf', 361 )
970
971          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'yv', NF90_DOUBLE, &
972                                  id_dim_yv_3d(av), id_var_yv_3d(av) )
973          CALL handle_netcdf_error( 'netcdf', 362 )
974
975          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_yv_3d(av), 'units', &
976                                  'meters' )
977          CALL handle_netcdf_error( 'netcdf', 363 )
978
979!
980!--       In case of non-flat topography define 2d-arrays containing the height
981!--       informations
982          IF ( TRIM( topography ) /= 'flat' )  THEN
983!
984!--          Define zusi = zu(nzb_s_inner)
985             nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zusi', NF90_DOUBLE,     &
986                                     (/ id_dim_x_3d(av), id_dim_y_3d(av) /), &
987                                     id_var_zusi_3d(av) )
988             CALL handle_netcdf_error( 'netcdf', 413 )
989             
990             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zusi_3d(av), &
991                                     'units', 'meters' )
992             CALL handle_netcdf_error( 'netcdf', 414 )
993             
994             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zusi_3d(av), &
995                                     'long_name', 'zu(nzb_s_inner)' )
996             CALL handle_netcdf_error( 'netcdf', 415 )
997
998!             
999!--          Define zwwi = zw(nzb_w_inner)
1000             nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zwwi', NF90_DOUBLE,     &
1001                                     (/ id_dim_x_3d(av), id_dim_y_3d(av) /), &
1002                                     id_var_zwwi_3d(av) )
1003             CALL handle_netcdf_error( 'netcdf', 416 )
1004             
1005             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zwwi_3d(av), &
1006                                     'units', 'meters' )
1007             CALL handle_netcdf_error( 'netcdf', 417 )
1008             
1009             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zwwi_3d(av), &
1010                                     'long_name', 'zw(nzb_w_inner)' )
1011             CALL handle_netcdf_error( 'netcdf', 418 )
1012
1013          ENDIF             
1014
1015
1016!
1017!--       Define the variables
1018          var_list = ';'
1019          i = 1
1020
1021          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
1022
1023!
1024!--          Check for the grid
1025             found = .TRUE.
1026             SELECT CASE ( do3d(av,i) )
1027!
1028!--             Most variables are defined on the scalar grid
1029                CASE ( 'e', 'lpt', 'nr', 'p', 'pc', 'pr', 'prr', 'pt', 'q',   &
1030                       'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv', 'rho',&
1031                       's', 'sa', 'vpt' )
1032
1033                   grid_x = 'x'
1034                   grid_y = 'y'
1035                   grid_z = 'zu'
1036!
1037!--             u grid
1038                CASE ( 'u' )
1039
1040                   grid_x = 'xu'
1041                   grid_y = 'y'
1042                   grid_z = 'zu'
1043!
1044!--             v grid
1045                CASE ( 'v' )
1046
1047                   grid_x = 'x'
1048                   grid_y = 'yv'
1049                   grid_z = 'zu'
1050!
1051!--             w grid
1052                CASE ( 'w' )
1053
1054                   grid_x = 'x'
1055                   grid_y = 'y'
1056                   grid_z = 'zw'
1057
1058                CASE DEFAULT
1059!
1060!--                Check for user-defined quantities
1061                   CALL user_define_netcdf_grid( do3d(av,i), found, grid_x, &
1062                                                 grid_y, grid_z )
1063
1064             END SELECT
1065
1066!
1067!--          Select the respective dimension ids
1068             IF ( grid_x == 'x' )  THEN
1069                id_x = id_dim_x_3d(av)
1070             ELSEIF ( grid_x == 'xu' )  THEN
1071                id_x = id_dim_xu_3d(av)
1072             ENDIF
1073
1074             IF ( grid_y == 'y' )  THEN
1075                id_y = id_dim_y_3d(av)
1076             ELSEIF ( grid_y == 'yv' )  THEN
1077                id_y = id_dim_yv_3d(av)
1078             ENDIF
1079
1080             IF ( grid_z == 'zu' )  THEN
1081                id_z = id_dim_zu_3d(av)
1082             ELSEIF ( grid_z == 'zw' )  THEN
1083                id_z = id_dim_zw_3d(av)
1084             ENDIF
1085
1086!
1087!--          Define the grid
1088             nc_stat = NF90_DEF_VAR( id_set_3d(av), do3d(av,i),                &
1089                                     nc_precision(4),                          &
1090                                   (/ id_x, id_y, id_z, id_dim_time_3d(av) /), &
1091                                     id_var_do3d(av,i) )
1092
1093             IF ( .NOT. found )  THEN
1094                WRITE ( message_string, * ) 'no grid defined for', &
1095                                            ' variable ', TRIM( do3d(av,i) )
1096                CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
1097             ENDIF
1098
1099             var_list = TRIM( var_list ) // TRIM( do3d(av,i) ) // ';'
1100
1101             CALL handle_netcdf_error( 'netcdf', 79 )
1102!
1103!--          Store the 'real' name of the variable (with *, for example)
1104!--          in the long_name attribute. This is evaluated by Ferret,
1105!--          for example.
1106             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_do3d(av,i), &
1107                                     'long_name', do3d(av,i) )
1108             CALL handle_netcdf_error( 'netcdf', 80 )
1109!
1110!--          Define the variable's unit
1111             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_do3d(av,i), &
1112                                     'units', TRIM( do3d_unit(av,i) ) )
1113             CALL handle_netcdf_error( 'netcdf', 357 )
1114#if defined( __netcdf4_parallel )
1115             IF ( netcdf_data_format > 4 )  THEN
1116!
1117!--             Set no fill for every variable to increase performance.
1118                nc_stat = NF90_DEF_VAR_FILL( id_set_3d(av),     &
1119                                             id_var_do3d(av,i), &
1120                                             1, 0 )
1121                CALL handle_netcdf_error( 'netcdf', 532 )
1122!
1123!--             Set collective io operations for parallel io
1124                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
1125                                               id_var_do3d(av,i), &
1126                                               NF90_COLLECTIVE )
1127                CALL handle_netcdf_error( 'netcdf', 445 )
1128             ENDIF
1129#endif
1130             i = i + 1
1131
1132          ENDDO
1133
1134!
1135!--       No arrays to output
1136          IF ( i == 1 )  RETURN
1137
1138!
1139!--       Write the list of variables as global attribute (this is used by
1140!--       restart runs and by combine_plot_fields)
1141          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
1142                                  var_list )
1143          CALL handle_netcdf_error( 'netcdf', 81 )
1144
1145!
1146!--       Set general no fill, otherwise the performance drops significantly for
1147!--       parallel output.
1148          nc_stat = NF90_SET_FILL( id_set_3d(av), NF90_NOFILL, oldmode )
1149          CALL handle_netcdf_error( 'netcdf', 528 )
1150
1151!
1152!--       Leave netCDF define mode
1153          nc_stat = NF90_ENDDEF( id_set_3d(av) )
1154          CALL handle_netcdf_error( 'netcdf', 82 )
1155
1156!
1157!--       These data are only written by PE0 for parallel output to increase
1158!--       the performance.
1159          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
1160!
1161!--          Write data for x (shifted by +dx/2) and xu axis
1162             ALLOCATE( netcdf_data(0:nx+1) )
1163
1164             DO  i = 0, nx+1
1165                netcdf_data(i) = ( i + 0.5 ) * dx
1166             ENDDO
1167
1168             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av),  &
1169                                     netcdf_data, start = (/ 1 /),    &
1170                                     count = (/ nx+2 /) )
1171             CALL handle_netcdf_error( 'netcdf', 83 )
1172
1173             DO  i = 0, nx+1
1174                netcdf_data(i) = i * dx
1175             ENDDO
1176
1177             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_xu_3d(av), &
1178                                     netcdf_data, start = (/ 1 /),    &
1179                                     count = (/ nx+2 /) )
1180             CALL handle_netcdf_error( 'netcdf', 385 )
1181
1182             DEALLOCATE( netcdf_data )
1183
1184!
1185!--          Write data for y (shifted by +dy/2) and yv axis
1186             ALLOCATE( netcdf_data(0:ny+1) )
1187
1188             DO  i = 0, ny+1
1189                netcdf_data(i) = ( i + 0.5 ) * dy
1190             ENDDO
1191
1192             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av),  &
1193                                     netcdf_data, start = (/ 1 /),    &
1194                                     count = (/ ny+2 /) )
1195             CALL handle_netcdf_error( 'netcdf', 84 )
1196
1197             DO  i = 0, ny+1
1198                netcdf_data(i) = i * dy
1199             ENDDO
1200
1201             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_yv_3d(av), &
1202                                     netcdf_data, start = (/ 1 /),    &
1203                                     count = (/ ny+2 /))
1204             CALL handle_netcdf_error( 'netcdf', 387 )
1205
1206             DEALLOCATE( netcdf_data )
1207
1208!
1209!--          Write zu and zw data (vertical axes)
1210             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zu_3d(av),  &
1211                                     zu(nzb:nz_do3d), start = (/ 1 /), &
1212                                     count = (/ nz_do3d-nzb+1 /) )
1213             CALL handle_netcdf_error( 'netcdf', 85 )
1214
1215
1216             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zw_3d(av),  &
1217                                     zw(nzb:nz_do3d), start = (/ 1 /), &
1218                                     count = (/ nz_do3d-nzb+1 /) )
1219             CALL handle_netcdf_error( 'netcdf', 86 )
1220
1221!
1222!--          In case of non-flat topography write height information
1223             IF ( TRIM( topography ) /= 'flat' )  THEN
1224
1225                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av), &
1226                                        zu_s_inner(0:nx+1,0:ny+1), &
1227                                        start = (/ 1, 1 /), &
1228                                        count = (/ nx+2, ny+2 /) )
1229                CALL handle_netcdf_error( 'netcdf', 419 )
1230
1231                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av), &
1232                                        zw_w_inner(0:nx+1,0:ny+1), &
1233                                        start = (/ 1, 1 /), &
1234                                        count = (/ nx+2, ny+2 /) )
1235                CALL handle_netcdf_error( 'netcdf', 420 )
1236
1237             ENDIF
1238          ENDIF
1239
1240       CASE ( '3d_ext' )
1241
1242!
1243!--       Get the list of variables and compare with the actual run.
1244!--       First var_list_old has to be reset, since GET_ATT does not assign
1245!--       trailing blanks.
1246          var_list_old = ' '
1247          nc_stat = NF90_GET_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
1248                                  var_list_old )
1249          CALL handle_netcdf_error( 'netcdf', 87 )
1250
1251          var_list = ';'
1252          i = 1
1253          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
1254             var_list = TRIM(var_list) // TRIM( do3d(av,i) ) // ';'
1255             i = i + 1
1256          ENDDO
1257
1258          IF ( av == 0 )  THEN
1259             var = '(3d)'
1260          ELSE
1261             var = '(3d_av)'
1262          ENDIF
1263
1264          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
1265             message_string = 'netCDF file for volume data ' //             &
1266                              TRIM( var ) // ' from previous run found,' // &
1267                              '&but this file cannot be extended due to' // &
1268                              ' variable mismatch.' //                      &
1269                              '&New file is created instead.'
1270             CALL message( 'define_netcdf_header', 'PA0245', 0, 1, 0, 6, 0 )
1271             extend = .FALSE.
1272             RETURN
1273          ENDIF
1274
1275!
1276!--       Get and compare the number of vertical gridpoints
1277          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'zu_3d', id_var_zu_3d(av) )
1278          CALL handle_netcdf_error( 'netcdf', 88 )
1279
1280          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_zu_3d(av), &
1281                                           dimids = id_dim_zu_3d_old )
1282          CALL handle_netcdf_error( 'netcdf', 89 )
1283          id_dim_zu_3d(av) = id_dim_zu_3d_old(1)
1284
1285          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_zu_3d(av), &
1286                                            len = nz_old )
1287          CALL handle_netcdf_error( 'netcdf', 90 )
1288
1289          IF ( nz_do3d-nzb+1 /= nz_old )  THEN
1290              message_string = 'netCDF file for volume data ' //             &
1291                               TRIM( var ) // ' from previous run found,' // &
1292                               '&but this file cannot be extended due to' // &
1293                               ' mismatch in number of' //                   &
1294                               '&vertical grid points (nz_do3d).' //         &
1295                               '&New file is created instead.'
1296             CALL message( 'define_netcdf_header', 'PA0246', 0, 1, 0, 6, 0 )
1297             extend = .FALSE.
1298             RETURN
1299          ENDIF
1300
1301!
1302!--       Get the id of the time coordinate (unlimited coordinate) and its
1303!--       last index on the file. The next time level is pl3d..count+1.
1304!--       The current time must be larger than the last output time
1305!--       on the file.
1306          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'time', id_var_time_3d(av) )
1307          CALL handle_netcdf_error( 'netcdf', 91 )
1308
1309          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_time_3d(av), &
1310                                           dimids = id_dim_time_old )
1311          CALL handle_netcdf_error( 'netcdf', 92 )
1312
1313          id_dim_time_3d(av) = id_dim_time_old(1)
1314
1315          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_time_3d(av), &
1316                                            len = ntime_count )
1317          CALL handle_netcdf_error( 'netcdf', 93 )
1318
1319!
1320!--       For non-parallel output use the last output time level of the netcdf
1321!--       file because the time dimension is unlimited. In case of parallel
1322!--       output the variable ntime_count could get the value of 9*10E36 because
1323!--       the time dimension is limited.
1324          IF ( netcdf_data_format < 5 ) do3d_time_count(av) = ntime_count
1325
1326          nc_stat = NF90_GET_VAR( id_set_3d(av), id_var_time_3d(av), &
1327                                  last_time_coordinate,              &
1328                                  start = (/ do3d_time_count(av) /), &
1329                                  count = (/ 1 /) )
1330          CALL handle_netcdf_error( 'netcdf', 94 )
1331
1332          IF ( last_time_coordinate(1) >= simulated_time )  THEN
1333             message_string = 'netCDF file for volume data ' // &
1334                              TRIM( var ) // ' from previous run found,' // &
1335                              '&but this file cannot be extended becaus' // &
1336                              'e the current output time' //                &
1337                              '&is less or equal than the last output t' // &
1338                              'ime on this file.' //                        &
1339                              '&New file is created instead.'
1340             CALL message( 'define_netcdf_header', 'PA0247', 0, 1, 0, 6, 0 )
1341             do3d_time_count(av) = 0
1342             extend = .FALSE.
1343             RETURN
1344          ENDIF
1345
1346          IF ( netcdf_data_format > 4 )  THEN
1347             IF ( ntdim_3d(av) > ntime_count )  THEN
1348                message_string = 'netCDF file for volume data ' // &
1349                                 TRIM( var ) // ' from previous run found,' // &
1350                                 '&but this file cannot be extended becaus' // &
1351                                 'e the number of output time levels&has b' // &
1352                                 'een increased compared to the previous s' // &
1353                                 'imulation.' //                                &
1354                                 '&New file is created instead.'
1355                CALL message( 'define_netcdf_header', 'PA0388', 0, 1, 0, 6, 0 )
1356                do3d_time_count(av) = 0
1357                extend = .FALSE.
1358                RETURN
1359             ENDIF
1360          ENDIF
1361
1362!
1363!--       Dataset seems to be extendable.
1364!--       Now get the variable ids.
1365          i = 1
1366          DO WHILE ( do3d(av,i)(1:1) /= ' ' )
1367             nc_stat = NF90_INQ_VARID( id_set_3d(av), TRIM( do3d(av,i) ), &
1368                                       id_var_do3d(av,i) )
1369             CALL handle_netcdf_error( 'netcdf', 95 )
1370#if defined( __netcdf4_parallel )
1371!
1372!--          Set collective io operations for parallel io
1373             IF ( netcdf_data_format > 4 )  THEN
1374                nc_stat = NF90_VAR_PAR_ACCESS( id_set_3d(av),     &
1375                                               id_var_do3d(av,i), &
1376                                               NF90_COLLECTIVE )
1377                CALL handle_netcdf_error( 'netcdf', 453 )
1378             ENDIF
1379#endif
1380             i = i + 1
1381          ENDDO
1382
1383!
1384!--       Update the title attribute on file
1385!--       In order to avoid 'data mode' errors if updated attributes are larger
1386!--       than their original size, NF90_PUT_ATT is called in 'define mode'
1387!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
1388!--       performance loss due to data copying; an alternative strategy would be
1389!--       to ensure equal attribute size. Maybe revise later.
1390          IF ( av == 0 )  THEN
1391             time_average_text = ' '
1392          ELSE
1393             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
1394                                                            averaging_interval
1395          ENDIF
1396          nc_stat = NF90_REDEF( id_set_3d(av) )
1397          CALL handle_netcdf_error( 'netcdf', 429 )
1398          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title', &
1399                                  TRIM( run_description_header ) //    &
1400                                  TRIM( time_average_text ) )
1401          CALL handle_netcdf_error( 'netcdf', 96 )
1402          nc_stat = NF90_ENDDEF( id_set_3d(av) )
1403          CALL handle_netcdf_error( 'netcdf', 430 )
1404          message_string = 'netCDF file for volume data ' //             &
1405                           TRIM( var ) // ' from previous run found.' // &
1406                           '&This file will be extended.'
1407          CALL message( 'define_netcdf_header', 'PA0248', 0, 0, 0, 6, 0 )
1408
1409       CASE ( 'xy_new' )
1410
1411!
1412!--       Define some global attributes of the dataset
1413          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'Conventions', &
1414                                  'COARDS' )
1415          CALL handle_netcdf_error( 'netcdf', 97 )
1416
1417          IF ( av == 0 )  THEN
1418             time_average_text = ' '
1419          ELSE
1420             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
1421                                                            averaging_interval
1422          ENDIF
1423          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title', &
1424                                  TRIM( run_description_header ) //    &
1425                                  TRIM( time_average_text ) )
1426          CALL handle_netcdf_error( 'netcdf', 98 )
1427          IF ( av == 1 )  THEN
1428             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
1429             nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'time_avg', &
1430                                     TRIM( time_average_text ) )
1431             CALL handle_netcdf_error( 'netcdf', 98 )
1432          ENDIF
1433
1434!
1435!--       Define time coordinate for xy sections.
1436!--       For parallel output the time dimensions has to be limited, otherwise
1437!--       the performance drops significantly.
1438          IF ( netcdf_data_format < 5 )  THEN
1439             nc_stat = NF90_DEF_DIM( id_set_xy(av), 'time', NF90_UNLIMITED, &
1440                                     id_dim_time_xy(av) )
1441             CALL handle_netcdf_error( 'netcdf', 99 )
1442          ELSE
1443             nc_stat = NF90_DEF_DIM( id_set_xy(av), 'time', ntdim_2d_xy(av), &
1444                                     id_dim_time_xy(av) )
1445             CALL handle_netcdf_error( 'netcdf', 524 )
1446          ENDIF
1447
1448          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'time', NF90_DOUBLE, &
1449                                  id_dim_time_xy(av), id_var_time_xy(av) )
1450          CALL handle_netcdf_error( 'netcdf', 100 )
1451
1452          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_time_xy(av), 'units', &
1453                                  'seconds')
1454          CALL handle_netcdf_error( 'netcdf', 101 )
1455
1456!
1457!--       Define the spatial dimensions and coordinates for xy-sections.
1458!--       First, determine the number of horizontal sections to be written.
1459          IF ( section(1,1) == -9999 )  THEN
1460             RETURN
1461          ELSE
1462             ns = 1
1463             DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
1464                ns = ns + 1
1465             ENDDO
1466             ns = ns - 1
1467          ENDIF
1468
1469!
1470!--       Define vertical coordinate grid (zu grid)
1471          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zu_xy', ns, id_dim_zu_xy(av) )
1472          CALL handle_netcdf_error( 'netcdf', 102 )
1473
1474          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zu_xy', NF90_DOUBLE, &
1475                                  id_dim_zu_xy(av), id_var_zu_xy(av) )
1476          CALL handle_netcdf_error( 'netcdf', 103 )
1477
1478          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zu_xy(av), 'units', &
1479                                  'meters' )
1480          CALL handle_netcdf_error( 'netcdf', 104 )
1481
1482!
1483!--       Define vertical coordinate grid (zw grid)
1484          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zw_xy', ns, id_dim_zw_xy(av) )
1485          CALL handle_netcdf_error( 'netcdf', 105 )
1486
1487          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zw_xy', NF90_DOUBLE, &
1488                                  id_dim_zw_xy(av), id_var_zw_xy(av) )
1489          CALL handle_netcdf_error( 'netcdf', 106 )
1490
1491          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zw_xy(av), 'units', &
1492                                  'meters' )
1493          CALL handle_netcdf_error( 'netcdf', 107 )
1494
1495!
1496!--       Define a pseudo vertical coordinate grid for the surface variables
1497!--       u* and t* to store their height level
1498          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zu1_xy', 1, &
1499                                  id_dim_zu1_xy(av) )
1500          CALL handle_netcdf_error( 'netcdf', 108 )
1501
1502          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zu1_xy', NF90_DOUBLE, &
1503                                  id_dim_zu1_xy(av), id_var_zu1_xy(av) )
1504          CALL handle_netcdf_error( 'netcdf', 109 )
1505
1506          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zu1_xy(av), 'units', &
1507                                  'meters' )
1508          CALL handle_netcdf_error( 'netcdf', 110 )
1509
1510!
1511!--       Define a variable to store the layer indices of the horizontal cross
1512!--       sections, too
1513          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'ind_z_xy', NF90_DOUBLE, &
1514                                  id_dim_zu_xy(av), id_var_ind_z_xy(av) )
1515          CALL handle_netcdf_error( 'netcdf', 111 )
1516
1517          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_ind_z_xy(av), 'units', &
1518                                  'gridpoints')
1519          CALL handle_netcdf_error( 'netcdf', 112 )
1520
1521!
1522!--       Define x-axis (for scalar position)
1523          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'x', nx+2, id_dim_x_xy(av) )
1524          CALL handle_netcdf_error( 'netcdf', 113 )
1525
1526          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'x', NF90_DOUBLE, &
1527                                  id_dim_x_xy(av), id_var_x_xy(av) )
1528          CALL handle_netcdf_error( 'netcdf', 114 )
1529
1530
1531          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_x_xy(av), 'units', &
1532                                  'meters' )
1533          CALL handle_netcdf_error( 'netcdf', 115 )
1534
1535!
1536!--       Define x-axis (for u position)
1537          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'xu', nx+2, id_dim_xu_xy(av) )
1538          CALL handle_netcdf_error( 'netcdf', 388 )
1539
1540          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'xu', NF90_DOUBLE, &
1541                                  id_dim_xu_xy(av), id_var_xu_xy(av) )
1542          CALL handle_netcdf_error( 'netcdf', 389 )
1543
1544          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_xu_xy(av), 'units', &
1545                                  'meters' )
1546          CALL handle_netcdf_error( 'netcdf', 390 )
1547
1548!
1549!--       Define y-axis (for scalar position)
1550          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'y', ny+2, id_dim_y_xy(av) )
1551          CALL handle_netcdf_error( 'netcdf', 116 )
1552
1553          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'y', NF90_DOUBLE, &
1554                                  id_dim_y_xy(av), id_var_y_xy(av) )
1555          CALL handle_netcdf_error( 'netcdf', 117 )
1556
1557          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_y_xy(av), 'units', &
1558                                  'meters' )
1559          CALL handle_netcdf_error( 'netcdf', 118 )
1560
1561!
1562!--       Define y-axis (for scalar position)
1563          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'yv', ny+2, id_dim_yv_xy(av) )
1564          CALL handle_netcdf_error( 'netcdf', 364 )
1565
1566          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'yv', NF90_DOUBLE, &
1567                                  id_dim_yv_xy(av), id_var_yv_xy(av) )
1568          CALL handle_netcdf_error( 'netcdf', 365 )
1569
1570          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_yv_xy(av), 'units', &
1571                                  'meters' )
1572          CALL handle_netcdf_error( 'netcdf', 366 )
1573
1574!
1575!--       In case of non-flat topography define 2d-arrays containing the height
1576!--       informations
1577          IF ( TRIM( topography ) /= 'flat' )  THEN
1578!
1579!--          Define zusi = zu(nzb_s_inner)
1580             nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zusi', NF90_DOUBLE, &
1581                                     (/ id_dim_x_xy(av), id_dim_y_xy(av) /), &
1582                                     id_var_zusi_xy(av) )
1583             CALL handle_netcdf_error( 'netcdf', 421 )
1584             
1585             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zusi_xy(av), &
1586                                     'units', 'meters' )
1587             CALL handle_netcdf_error( 'netcdf', 422 )
1588             
1589             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zusi_xy(av), &
1590                                     'long_name', 'zu(nzb_s_inner)' )
1591             CALL handle_netcdf_error( 'netcdf', 423 )
1592
1593!             
1594!--          Define zwwi = zw(nzb_w_inner)
1595             nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zwwi', NF90_DOUBLE, &
1596                                     (/ id_dim_x_xy(av), id_dim_y_xy(av) /), &
1597                                     id_var_zwwi_xy(av) )
1598             CALL handle_netcdf_error( 'netcdf', 424 )
1599             
1600             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zwwi_xy(av), &
1601                                     'units', 'meters' )
1602             CALL handle_netcdf_error( 'netcdf', 425 )
1603             
1604             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zwwi_xy(av), &
1605                                     'long_name', 'zw(nzb_w_inner)' )
1606             CALL handle_netcdf_error( 'netcdf', 426 )
1607
1608          ENDIF
1609
1610
1611!
1612!--       Define the variables
1613          var_list = ';'
1614          i = 1
1615
1616          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
1617
1618             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
1619!
1620!--             If there is a star in the variable name (u* or t*), it is a
1621!--             surface variable. Define it with id_dim_zu1_xy.
1622                IF ( INDEX( do2d(av,i), '*' ) /= 0 )  THEN
1623
1624                   nc_stat = NF90_DEF_VAR( id_set_xy(av),  do2d(av,i),         &
1625                                           nc_precision(1),                    &
1626                                           (/ id_dim_x_xy(av), id_dim_y_xy(av),&
1627                                              id_dim_zu1_xy(av),               &
1628                                              id_dim_time_xy(av) /),           &
1629                                           id_var_do2d(av,i) )
1630
1631                   var_list = TRIM(var_list) // TRIM( do2d(av,i) ) // ';'
1632
1633                ELSE
1634
1635!
1636!--                Check for the grid
1637                   found = .TRUE.
1638                   SELECT CASE ( do2d(av,i) )
1639!
1640!--                   Most variables are defined on the zu grid
1641                      CASE ( 'e_xy', 'lpt_xy', 'nr_xy', 'p_xy', 'pc_xy', 'pr_xy',&
1642                             'prr_xy', 'pt_xy', 'q_xy', 'qc_xy', 'ql_xy',        &
1643                             'ql_c_xy', 'ql_v_xy', 'ql_vp_xy', 'qr_xy', 'qv_xy', &
1644                             'rho_xy', 's_xy', 'sa_xy', 'vpt_xy' )
1645
1646                         grid_x = 'x'
1647                         grid_y = 'y'
1648                         grid_z = 'zu'
1649!
1650!--                   u grid
1651                      CASE ( 'u_xy' )
1652
1653                         grid_x = 'xu'
1654                         grid_y = 'y'
1655                         grid_z = 'zu'
1656!
1657!--                   v grid
1658                      CASE ( 'v_xy' )
1659
1660                         grid_x = 'x'
1661                         grid_y = 'yv'
1662                         grid_z = 'zu'
1663!
1664!--                   w grid
1665                      CASE ( 'w_xy' )
1666
1667                         grid_x = 'x'
1668                         grid_y = 'y'
1669                         grid_z = 'zw'
1670
1671                      CASE DEFAULT
1672!
1673!--                      Check for user-defined quantities
1674                         CALL user_define_netcdf_grid( do2d(av,i), found, &
1675                                                       grid_x, grid_y, grid_z )
1676
1677                   END SELECT
1678
1679!
1680!--                Select the respective dimension ids
1681                   IF ( grid_x == 'x' )  THEN
1682                      id_x = id_dim_x_xy(av)
1683                   ELSEIF ( grid_x == 'xu' )  THEN
1684                      id_x = id_dim_xu_xy(av)
1685                   ENDIF
1686
1687                   IF ( grid_y == 'y' )  THEN
1688                      id_y = id_dim_y_xy(av)
1689                   ELSEIF ( grid_y == 'yv' )  THEN
1690                      id_y = id_dim_yv_xy(av)
1691                   ENDIF
1692
1693                   IF ( grid_z == 'zu' )  THEN
1694                      id_z = id_dim_zu_xy(av)
1695                   ELSEIF ( grid_z == 'zw' )  THEN
1696                      id_z = id_dim_zw_xy(av)
1697                   ENDIF
1698
1699!
1700!--                Define the grid
1701                   nc_stat = NF90_DEF_VAR( id_set_xy(av), do2d(av,i),          &
1702                                           nc_precision(1),                    &
1703                                   (/ id_x, id_y, id_z, id_dim_time_xy(av) /), &
1704                                           id_var_do2d(av,i) )
1705
1706                   IF ( .NOT. found )  THEN
1707                      WRITE ( message_string, * ) 'no grid defined for', &
1708                                            ' variable ', TRIM( do2d(av,i) )
1709                      CALL message( 'define_netcdf_header', 'PA0244',&
1710                                                                0, 1, 0, 6, 0 )
1711                   ENDIF
1712
1713                   var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
1714
1715                ENDIF
1716
1717                CALL handle_netcdf_error( 'netcdf', 119 )
1718!
1719!--             Store the 'real' name of the variable (with *, for example)
1720!--             in the long_name attribute. This is evaluated by Ferret,
1721!--             for example.
1722                nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_do2d(av,i), &
1723                                        'long_name', do2d(av,i) )
1724                CALL handle_netcdf_error( 'netcdf', 120 )
1725!
1726!--             Define the variable's unit
1727                nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_do2d(av,i), &
1728                                        'units', TRIM( do2d_unit(av,i) ) )
1729                CALL handle_netcdf_error( 'netcdf', 354 ) 
1730#if defined( __netcdf4_parallel )
1731                IF ( netcdf_data_format > 4 )  THEN
1732!
1733!--                Set no fill for every variable to increase performance.
1734                   nc_stat = NF90_DEF_VAR_FILL( id_set_xy(av),     &
1735                                                id_var_do2d(av,i), &
1736                                                1, 0 )
1737                   CALL handle_netcdf_error( 'netcdf', 533 )
1738!
1739!--                Set collective io operations for parallel io
1740                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
1741                                                  id_var_do2d(av,i), &
1742                                                  NF90_COLLECTIVE )
1743                   CALL handle_netcdf_error( 'netcdf', 448 )
1744                ENDIF
1745#endif
1746             ENDIF
1747
1748             i = i + 1
1749
1750          ENDDO
1751
1752!
1753!--       No arrays to output. Close the netcdf file and return.
1754          IF ( i == 1 )  RETURN
1755
1756!
1757!--       Write the list of variables as global attribute (this is used by
1758!--       restart runs and by combine_plot_fields)
1759          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
1760                                  var_list )
1761          CALL handle_netcdf_error( 'netcdf', 121 ) 
1762
1763!
1764!--       Set general no fill, otherwise the performance drops significantly for
1765!--       parallel output.
1766          nc_stat = NF90_SET_FILL( id_set_xy(av), NF90_NOFILL, oldmode )
1767          CALL handle_netcdf_error( 'netcdf', 529 )
1768
1769!
1770!--       Leave netCDF define mode
1771          nc_stat = NF90_ENDDEF( id_set_xy(av) )
1772          CALL handle_netcdf_error( 'netcdf', 122 ) 
1773
1774!
1775!--       These data are only written by PE0 for parallel output to increase
1776!--       the performance.
1777          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
1778
1779!
1780!--          Write axis data: z_xy, x, y
1781             ALLOCATE( netcdf_data(1:ns) )
1782
1783!
1784!--          Write zu data
1785             DO  i = 1, ns
1786                IF( section(i,1) == -1 )  THEN
1787                   netcdf_data(i) = -1.0  ! section averaged along z
1788                ELSE
1789                   netcdf_data(i) = zu( section(i,1) )
1790                ENDIF
1791             ENDDO
1792             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu_xy(av), &
1793                                     netcdf_data, start = (/ 1 /),    &
1794                                     count = (/ ns /) )
1795             CALL handle_netcdf_error( 'netcdf', 123 )
1796
1797!
1798!--          Write zw data
1799             DO  i = 1, ns
1800                IF( section(i,1) == -1 )  THEN
1801                   netcdf_data(i) = -1.0  ! section averaged along z
1802                ELSE
1803                   netcdf_data(i) = zw( section(i,1) )
1804                ENDIF
1805             ENDDO
1806             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zw_xy(av), &
1807                                     netcdf_data, start = (/ 1 /),    &
1808                                     count = (/ ns /) )
1809             CALL handle_netcdf_error( 'netcdf', 124 )
1810
1811!
1812!--          Write gridpoint number data
1813             netcdf_data(1:ns) = section(1:ns,1)
1814             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_ind_z_xy(av), &
1815                                     netcdf_data, start = (/ 1 /),       &
1816                                     count = (/ ns /) )
1817             CALL handle_netcdf_error( 'netcdf', 125 )
1818
1819             DEALLOCATE( netcdf_data )
1820
1821!
1822!--          Write the cross section height u*, t*
1823             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zu1_xy(av), &
1824                                     (/ zu(nzb+1) /), start = (/ 1 /), &
1825                                     count = (/ 1 /) )
1826             CALL handle_netcdf_error( 'netcdf', 126 )
1827
1828!
1829!--          Write data for x (shifted by +dx/2) and xu axis
1830             ALLOCATE( netcdf_data(0:nx+1) )
1831
1832             DO  i = 0, nx+1
1833                netcdf_data(i) = ( i + 0.5 ) * dx
1834             ENDDO
1835
1836             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av), &
1837                                     netcdf_data, start = (/ 1 /),   &
1838                                     count = (/ nx+2 /) )
1839             CALL handle_netcdf_error( 'netcdf', 127 )
1840
1841             DO  i = 0, nx+1
1842                netcdf_data(i) = i * dx
1843             ENDDO
1844
1845             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_xu_xy(av), &
1846                                     netcdf_data, start = (/ 1 /),    &
1847                                     count = (/ nx+2 /) )
1848             CALL handle_netcdf_error( 'netcdf', 367 )
1849
1850             DEALLOCATE( netcdf_data )
1851
1852!
1853!--          Write data for y (shifted by +dy/2) and yv axis
1854             ALLOCATE( netcdf_data(0:ny+1) )
1855
1856             DO  i = 0, ny+1
1857                netcdf_data(i) = ( i + 0.5 ) * dy
1858             ENDDO
1859
1860             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av), &
1861                                     netcdf_data, start = (/ 1 /),   &
1862                                     count = (/ ny+2 /))
1863             CALL handle_netcdf_error( 'netcdf', 128 )
1864
1865             DO  i = 0, ny+1
1866                netcdf_data(i) = i * dy
1867             ENDDO
1868
1869             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_yv_xy(av), &
1870                                     netcdf_data, start = (/ 1 /),    &
1871                                     count = (/ ny+2 /))
1872             CALL handle_netcdf_error( 'netcdf', 368 )
1873
1874             DEALLOCATE( netcdf_data )
1875
1876!
1877!--          In case of non-flat topography write height information
1878             IF ( TRIM( topography ) /= 'flat' )  THEN
1879
1880                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av), &
1881                                        zu_s_inner(0:nx+1,0:ny+1), &
1882                                        start = (/ 1, 1 /), &
1883                                        count = (/ nx+2, ny+2 /) )
1884                CALL handle_netcdf_error( 'netcdf', 427 )
1885
1886                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av), &
1887                                        zw_w_inner(0:nx+1,0:ny+1), &
1888                                        start = (/ 1, 1 /), &
1889                                        count = (/ nx+2, ny+2 /) )
1890                CALL handle_netcdf_error( 'netcdf', 428 )
1891
1892             ENDIF
1893          ENDIF
1894
1895       CASE ( 'xy_ext' )
1896
1897!
1898!--       Get the list of variables and compare with the actual run.
1899!--       First var_list_old has to be reset, since GET_ATT does not assign
1900!--       trailing blanks.
1901          var_list_old = ' '
1902          nc_stat = NF90_GET_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
1903                                  var_list_old )
1904          CALL handle_netcdf_error( 'netcdf', 129 )
1905
1906          var_list = ';'
1907          i = 1
1908          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
1909             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
1910                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
1911             ENDIF
1912             i = i + 1
1913          ENDDO
1914
1915          IF ( av == 0 )  THEN
1916             var = '(xy)'
1917          ELSE
1918             var = '(xy_av)'
1919          ENDIF
1920
1921          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
1922             message_string = 'netCDF file for cross-sections ' //           &
1923                              TRIM( var ) // ' from previous run found,' //  &
1924                              '& but this file cannot be extended due to' // &
1925                              ' variable mismatch.' //                       &
1926                              '&New file is created instead.'
1927             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
1928             extend = .FALSE.
1929             RETURN
1930          ENDIF
1931
1932!
1933!--       Calculate the number of current sections
1934          ns = 1
1935          DO WHILE ( section(ns,1) /= -9999  .AND.  ns <= 100 )
1936             ns = ns + 1
1937          ENDDO
1938          ns = ns - 1
1939
1940!
1941!--       Get and compare the number of horizontal cross sections
1942          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'zu_xy', id_var_zu_xy(av) )
1943          CALL handle_netcdf_error( 'netcdf', 130 )
1944
1945          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_zu_xy(av), &
1946                                           dimids = id_dim_zu_xy_old )
1947          CALL handle_netcdf_error( 'netcdf', 131 )
1948          id_dim_zu_xy(av) = id_dim_zu_xy_old(1)
1949
1950          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_zu_xy(av), &
1951                                            len = ns_old )
1952          CALL handle_netcdf_error( 'netcdf', 132 )
1953
1954          IF ( ns /= ns_old )  THEN
1955             message_string = 'netCDF file for cross-sections ' //          &
1956                              TRIM( var ) // ' from previous run found,' // &
1957                              '&but this file cannot be extended due to' // &
1958                              ' mismatch in number of' //                   &
1959                              '&cross sections.' //                         &
1960                              '&New file is created instead.'
1961             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
1962             extend = .FALSE.
1963             RETURN
1964          ENDIF
1965
1966!
1967!--       Get and compare the heights of the cross sections
1968          ALLOCATE( netcdf_data(1:ns_old) )
1969
1970          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_zu_xy(av), netcdf_data )
1971          CALL handle_netcdf_error( 'netcdf', 133 )
1972
1973          DO  i = 1, ns
1974             IF ( section(i,1) /= -1 )  THEN
1975                IF ( zu(section(i,1)) /= netcdf_data(i) )  THEN
1976                   message_string = 'netCDF file for cross-sections ' //     &
1977                               TRIM( var ) // ' from previous run found,' // &
1978                               '&but this file cannot be extended' //        &
1979                               ' due to mismatch in cross' //                &
1980                               '&section levels.' //                         &
1981                               '&New file is created instead.'
1982                   CALL message( 'define_netcdf_header', 'PA0251', &
1983                                                                 0, 1, 0, 6, 0 )
1984                   extend = .FALSE.
1985                   RETURN
1986                ENDIF
1987             ELSE
1988                IF ( -1.0 /= netcdf_data(i) )  THEN
1989                   message_string = 'netCDF file for cross-sections ' //     &
1990                               TRIM( var ) // ' from previous run found,' // &
1991                               '&but this file cannot be extended' //        &
1992                               ' due to mismatch in cross' //                &
1993                               '&section levels.' //                         &
1994                               '&New file is created instead.'
1995                   CALL message( 'define_netcdf_header', 'PA0251',&
1996                                                                 0, 1, 0, 6, 0 )
1997                   extend = .FALSE.
1998                   RETURN
1999                ENDIF
2000             ENDIF
2001          ENDDO
2002
2003          DEALLOCATE( netcdf_data )
2004
2005!
2006!--       Get the id of the time coordinate (unlimited coordinate) and its
2007!--       last index on the file. The next time level is do2d..count+1.
2008!--       The current time must be larger than the last output time
2009!--       on the file.
2010          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'time', id_var_time_xy(av) )
2011          CALL handle_netcdf_error( 'netcdf', 134 )
2012
2013          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_time_xy(av), &
2014                                           dimids = id_dim_time_old )
2015          CALL handle_netcdf_error( 'netcdf', 135 )
2016          id_dim_time_xy(av) = id_dim_time_old(1)
2017
2018          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_time_xy(av), &
2019                                            len = ntime_count )
2020          CALL handle_netcdf_error( 'netcdf', 136 )
2021
2022!
2023!--       For non-parallel output use the last output time level of the netcdf
2024!--       file because the time dimension is unlimited. In case of parallel
2025!--       output the variable ntime_count could get the value of 9*10E36 because
2026!--       the time dimension is limited.
2027          IF ( netcdf_data_format < 5 ) do2d_xy_time_count(av) = ntime_count
2028
2029          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_time_xy(av),    &
2030                                  last_time_coordinate,                 &
2031                                  start = (/ do2d_xy_time_count(av) /), &
2032                                  count = (/ 1 /) )
2033          CALL handle_netcdf_error( 'netcdf', 137 )
2034
2035          IF ( last_time_coordinate(1) >= simulated_time )  THEN
2036             message_string = 'netCDF file for cross sections ' //          &
2037                              TRIM( var ) // ' from previous run found,' // &
2038                              '&but this file cannot be extended becaus' // &
2039                              'e the current output time' //                &
2040                              '&is less or equal than the last output t' // &
2041                              'ime on this file.' //                        &
2042                              '&New file is created instead.'
2043             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
2044             do2d_xy_time_count(av) = 0
2045             extend = .FALSE.
2046             RETURN
2047          ENDIF
2048
2049          IF ( netcdf_data_format > 4 )  THEN
2050             IF ( ntdim_2d_xy(av) > ntime_count )  THEN
2051                message_string = 'netCDF file for cross sections ' //          &
2052                                 TRIM( var ) // ' from previous run found,' // &
2053                                 '&but this file cannot be extended becaus' // &
2054                                 'e the number of output time levels&has b' // &
2055                                 'een increased compared to the previous s' // &
2056                                 'imulation.' //                                &
2057                                 '&New file is created instead.'
2058                CALL message( 'define_netcdf_header', 'PA0389', 0, 1, 0, 6, 0 )
2059                do2d_xy_time_count(av) = 0
2060                extend = .FALSE.
2061                RETURN
2062             ENDIF
2063          ENDIF
2064
2065!
2066!--       Dataset seems to be extendable.
2067!--       Now get the variable ids.
2068          i = 1
2069          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2070             IF ( INDEX( do2d(av,i), 'xy' ) /= 0 )  THEN
2071                nc_stat = NF90_INQ_VARID( id_set_xy(av), do2d(av,i), &
2072                                          id_var_do2d(av,i) )
2073                CALL handle_netcdf_error( 'netcdf', 138 )
2074#if defined( __netcdf4_parallel )
2075!
2076!--             Set collective io operations for parallel io
2077                IF ( netcdf_data_format > 4 )  THEN
2078                   nc_stat = NF90_VAR_PAR_ACCESS( id_set_xy(av),     &
2079                                                  id_var_do2d(av,i), &
2080                                                  NF90_COLLECTIVE )
2081                   CALL handle_netcdf_error( 'netcdf', 454 )
2082                ENDIF
2083#endif
2084             ENDIF
2085             i = i + 1
2086          ENDDO
2087
2088!
2089!--       Update the title attribute on file
2090!--       In order to avoid 'data mode' errors if updated attributes are larger
2091!--       than their original size, NF90_PUT_ATT is called in 'define mode'
2092!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
2093!--       performance loss due to data copying; an alternative strategy would be
2094!--       to ensure equal attribute size in a job chain. Maybe revise later.
2095          IF ( av == 0 )  THEN
2096             time_average_text = ' '
2097          ELSE
2098             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
2099                                                            averaging_interval
2100          ENDIF
2101          nc_stat = NF90_REDEF( id_set_xy(av) )
2102          CALL handle_netcdf_error( 'netcdf', 431 )
2103          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title', &
2104                                  TRIM( run_description_header ) //    &
2105                                  TRIM( time_average_text ) )
2106          CALL handle_netcdf_error( 'netcdf', 139 )
2107          nc_stat = NF90_ENDDEF( id_set_xy(av) )
2108          CALL handle_netcdf_error( 'netcdf', 432 )
2109          message_string = 'netCDF file for cross-sections ' //           &
2110                            TRIM( var ) // ' from previous run found.' // &
2111                           '&This file will be extended.'
2112          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
2113         
2114
2115       CASE ( 'xz_new' )
2116
2117!
2118!--       Define some global attributes of the dataset
2119          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'Conventions', &
2120                                  'COARDS' )
2121          CALL handle_netcdf_error( 'netcdf', 140 )
2122
2123          IF ( av == 0 )  THEN
2124             time_average_text = ' '
2125          ELSE
2126             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
2127                                                            averaging_interval
2128          ENDIF
2129          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title', &
2130                                  TRIM( run_description_header )  //   &
2131                                  TRIM( time_average_text ) )
2132          CALL handle_netcdf_error( 'netcdf', 141 )
2133          IF ( av == 1 )  THEN
2134             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
2135             nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'time_avg', &
2136                                     TRIM( time_average_text ) )
2137             CALL handle_netcdf_error( 'netcdf', 141 )
2138          ENDIF
2139
2140!
2141!--       Define time coordinate for xz sections.
2142!--       For parallel output the time dimensions has to be limited, otherwise
2143!--       the performance drops significantly.
2144          IF ( netcdf_data_format < 5 )  THEN
2145             nc_stat = NF90_DEF_DIM( id_set_xz(av), 'time', NF90_UNLIMITED, &
2146                                     id_dim_time_xz(av) )
2147             CALL handle_netcdf_error( 'netcdf', 142 )
2148          ELSE
2149             nc_stat = NF90_DEF_DIM( id_set_xz(av), 'time', ntdim_2d_xz(av), &
2150                                     id_dim_time_xz(av) )
2151             CALL handle_netcdf_error( 'netcdf', 525 )
2152          ENDIF
2153
2154          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'time', NF90_DOUBLE, &
2155                                  id_dim_time_xz(av), id_var_time_xz(av) )
2156          CALL handle_netcdf_error( 'netcdf', 143 )
2157
2158          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_time_xz(av), 'units', &
2159                                  'seconds')
2160          CALL handle_netcdf_error( 'netcdf', 144 )
2161
2162!
2163!--       Define the spatial dimensions and coordinates for xz-sections.
2164!--       First, determine the number of vertical sections to be written.
2165          IF ( section(1,2) == -9999 )  THEN
2166             RETURN
2167          ELSE
2168             ns = 1
2169             DO WHILE ( section(ns,2) /= -9999  .AND.  ns <= 100 )
2170                ns = ns + 1
2171             ENDDO
2172             ns = ns - 1
2173          ENDIF
2174
2175!
2176!--       Define y-axis (for scalar position)
2177          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'y_xz', ns, id_dim_y_xz(av) )
2178          CALL handle_netcdf_error( 'netcdf', 145 )
2179
2180          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'y_xz', NF90_DOUBLE, &
2181                                  id_dim_y_xz(av), id_var_y_xz(av) )
2182          CALL handle_netcdf_error( 'netcdf', 146 )
2183
2184          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_y_xz(av), 'units', &
2185                                  'meters' )
2186          CALL handle_netcdf_error( 'netcdf', 147 )
2187
2188!
2189!--       Define y-axis (for v position)
2190          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'yv_xz', ns, id_dim_yv_xz(av) )
2191          CALL handle_netcdf_error( 'netcdf', 369 )
2192
2193          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'yv_xz', NF90_DOUBLE, &
2194                                  id_dim_yv_xz(av), id_var_yv_xz(av) )
2195          CALL handle_netcdf_error( 'netcdf', 370 )
2196
2197          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_yv_xz(av), 'units', &
2198                                  'meters' )
2199          CALL handle_netcdf_error( 'netcdf', 371 )
2200
2201!
2202!--       Define a variable to store the layer indices of the vertical cross
2203!--       sections
2204          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'ind_y_xz', NF90_DOUBLE, &
2205                                  id_dim_y_xz(av), id_var_ind_y_xz(av) )
2206          CALL handle_netcdf_error( 'netcdf', 148 )
2207
2208          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_ind_y_xz(av), 'units', &
2209                                  'gridpoints')
2210          CALL handle_netcdf_error( 'netcdf', 149 )
2211
2212!
2213!--       Define x-axis (for scalar position)
2214          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'x', nx+2, id_dim_x_xz(av) )
2215          CALL handle_netcdf_error( 'netcdf', 150 )
2216
2217          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'x', NF90_DOUBLE, &
2218                                  id_dim_x_xz(av), id_var_x_xz(av) )
2219          CALL handle_netcdf_error( 'netcdf', 151 )
2220
2221          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_x_xz(av), 'units', &
2222                                  'meters' )
2223          CALL handle_netcdf_error( 'netcdf', 152 )
2224
2225!
2226!--       Define x-axis (for u position)
2227          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'xu', nx+2, id_dim_xu_xz(av) )
2228          CALL handle_netcdf_error( 'netcdf', 372 )
2229
2230          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'xu', NF90_DOUBLE, &
2231                                  id_dim_xu_xz(av), id_var_xu_xz(av) )
2232          CALL handle_netcdf_error( 'netcdf', 373 )
2233
2234          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_xu_xz(av), 'units', &
2235                                  'meters' )
2236          CALL handle_netcdf_error( 'netcdf', 374 )
2237
2238!
2239!--       Define the two z-axes (zu and zw)
2240          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av) )
2241          CALL handle_netcdf_error( 'netcdf', 153 )
2242
2243          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'zu', NF90_DOUBLE, &
2244                                  id_dim_zu_xz(av), id_var_zu_xz(av) )
2245          CALL handle_netcdf_error( 'netcdf', 154 )
2246
2247          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_zu_xz(av), 'units', &
2248                                  'meters' )
2249          CALL handle_netcdf_error( 'netcdf', 155 )
2250
2251          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zw', nz+2, id_dim_zw_xz(av) )
2252          CALL handle_netcdf_error( 'netcdf', 156 )
2253
2254          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'zw', NF90_DOUBLE, &
2255                                  id_dim_zw_xz(av), id_var_zw_xz(av) )
2256          CALL handle_netcdf_error( 'netcdf', 157 )
2257
2258          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_zw_xz(av), 'units', &
2259                                  'meters' )
2260          CALL handle_netcdf_error( 'netcdf', 158 )
2261
2262
2263!
2264!--       Define the variables
2265          var_list = ';'
2266          i = 1
2267
2268          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2269
2270             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
2271
2272!
2273!--             Check for the grid
2274                found = .TRUE.
2275                SELECT CASE ( do2d(av,i) )
2276!
2277!--                Most variables are defined on the zu grid
2278                   CASE ( 'e_xz', 'lpt_xz', 'nr_xz', 'p_xz', 'pc_xz', 'pr_xz', &
2279                          'prr_xz', 'pt_xz', 'q_xz', 'qc_xz', 'ql_xz',         &
2280                          'ql_c_xz', 'ql_v_xz', 'ql_vp_xz', 'qr_xz', 'qv_xz',  &
2281                          'rho_xz', 's_xz', 'sa_xz', 'vpt_xz' )
2282
2283                      grid_x = 'x'
2284                      grid_y = 'y'
2285                      grid_z = 'zu'
2286!
2287!--                u grid
2288                   CASE ( 'u_xz' )
2289
2290                      grid_x = 'xu'
2291                      grid_y = 'y'
2292                      grid_z = 'zu'
2293!
2294!--                v grid
2295                   CASE ( 'v_xz' )
2296
2297                      grid_x = 'x'
2298                      grid_y = 'yv'
2299                      grid_z = 'zu'
2300!
2301!--                w grid
2302                   CASE ( 'w_xz' )
2303
2304                      grid_x = 'x'
2305                      grid_y = 'y'
2306                      grid_z = 'zw'
2307
2308                   CASE DEFAULT
2309!
2310!--                   Check for user-defined quantities
2311                      CALL user_define_netcdf_grid( do2d(av,i), found, &
2312                                                    grid_x, grid_y, grid_z )
2313
2314                END SELECT
2315
2316!
2317!--             Select the respective dimension ids
2318                IF ( grid_x == 'x' )  THEN
2319                   id_x = id_dim_x_xz(av)
2320                ELSEIF ( grid_x == 'xu' )  THEN
2321                   id_x = id_dim_xu_xz(av)
2322                ENDIF
2323
2324                IF ( grid_y == 'y' )  THEN
2325                   id_y = id_dim_y_xz(av)
2326                ELSEIF ( grid_y == 'yv' )  THEN
2327                   id_y = id_dim_yv_xz(av)
2328                ENDIF
2329
2330                IF ( grid_z == 'zu' )  THEN
2331                   id_z = id_dim_zu_xz(av)
2332                ELSEIF ( grid_z == 'zw' )  THEN
2333                   id_z = id_dim_zw_xz(av)
2334                ENDIF
2335
2336!
2337!--             Define the grid
2338                nc_stat = NF90_DEF_VAR( id_set_xz(av), do2d(av,i),             &
2339                                        nc_precision(2),                       &
2340                                   (/ id_x, id_y, id_z, id_dim_time_xz(av) /), &
2341                                        id_var_do2d(av,i) )
2342
2343                IF ( .NOT. found )  THEN
2344                   WRITE ( message_string, * ) 'no grid defined for', &
2345                                            ' variable ', TRIM( do2d(av,i) )
2346                   CALL message( 'define_netcdf_header', 'PA0244',&
2347                                                                 0, 1, 0, 6, 0 )
2348                ENDIF
2349
2350                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
2351
2352                CALL handle_netcdf_error( 'netcdf', 159 )
2353!
2354!--             Store the 'real' name of the variable (with *, for example)
2355!--             in the long_name attribute. This is evaluated by Ferret,
2356!--             for example.
2357                nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_do2d(av,i), &
2358                                        'long_name', do2d(av,i) )
2359                CALL handle_netcdf_error( 'netcdf', 160 )
2360!
2361!--             Define the variable's unit
2362                nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_do2d(av,i), &
2363                                        'units', TRIM( do2d_unit(av,i) ) )
2364                CALL handle_netcdf_error( 'netcdf', 355 )
2365#if defined( __netcdf4_parallel )
2366
2367                IF ( netcdf_data_format > 4 )  THEN
2368!
2369!--                Set no fill for every variable to increase performance.
2370                   nc_stat = NF90_DEF_VAR_FILL( id_set_xz(av),     &
2371                                                id_var_do2d(av,i), &
2372                                                1, 0 )
2373                   CALL handle_netcdf_error( 'netcdf', 534 )
2374!
2375!--                Set independent io operations for parallel io. Collective io
2376!--                is only allowed in case of a 1d-decomposition along x,
2377!--                because otherwise, not all PEs have output data.
2378                   IF ( npey == 1 )  THEN
2379                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
2380                                                     id_var_do2d(av,i), &
2381                                                     NF90_COLLECTIVE )
2382                   ELSE
2383!
2384!--                   Test simulations showed that the output of cross sections
2385!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
2386!--                   faster than the output by the first row of PEs in
2387!--                   x-direction using NF90_INDEPENDENT.
2388                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),    & 
2389                                                    id_var_do2d(av,i), &
2390                                                    NF90_COLLECTIVE )
2391!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
2392!                                                     id_var_do2d(av,i), &
2393!                                                     NF90_INDEPENDENT )
2394                   ENDIF
2395                   CALL handle_netcdf_error( 'netcdf', 449 )
2396                ENDIF
2397#endif
2398             ENDIF
2399
2400             i = i + 1
2401
2402          ENDDO
2403
2404!
2405!--       No arrays to output. Close the netcdf file and return.
2406          IF ( i == 1 )  RETURN
2407
2408!
2409!--       Write the list of variables as global attribute (this is used by
2410!--       restart runs and by combine_plot_fields)
2411          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
2412                                  var_list )
2413          CALL handle_netcdf_error( 'netcdf', 161 )
2414
2415!
2416!--       Set general no fill, otherwise the performance drops significantly for
2417!--       parallel output.
2418          nc_stat = NF90_SET_FILL( id_set_xz(av), NF90_NOFILL, oldmode )
2419          CALL handle_netcdf_error( 'netcdf', 530 )
2420
2421!
2422!--       Leave netCDF define mode
2423          nc_stat = NF90_ENDDEF( id_set_xz(av) )
2424          CALL handle_netcdf_error( 'netcdf', 162 )
2425
2426!
2427!--       These data are only written by PE0 for parallel output to increase
2428!--       the performance.
2429          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
2430
2431!
2432!--          Write axis data: y_xz, x, zu, zw
2433             ALLOCATE( netcdf_data(1:ns) )
2434
2435!
2436!--          Write y_xz data (shifted by +dy/2)
2437             DO  i = 1, ns
2438                IF( section(i,2) == -1 )  THEN
2439                   netcdf_data(i) = -1.0  ! section averaged along y
2440                ELSE
2441                   netcdf_data(i) = ( section(i,2) + 0.5 ) * dy
2442                ENDIF
2443             ENDDO
2444             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), &
2445                                     netcdf_data, start = (/ 1 /),   &
2446                                     count = (/ ns /) )
2447             CALL handle_netcdf_error( 'netcdf', 163 )
2448
2449!
2450!--          Write yv_xz data
2451             DO  i = 1, ns
2452                IF( section(i,2) == -1 )  THEN
2453                   netcdf_data(i) = -1.0  ! section averaged along y
2454                ELSE
2455                   netcdf_data(i) = section(i,2) * dy
2456                ENDIF
2457             ENDDO
2458             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_yv_xz(av), &
2459                                     netcdf_data, start = (/ 1 /),    &
2460                                     count = (/ ns /) )
2461             CALL handle_netcdf_error( 'netcdf', 375 )
2462
2463!
2464!--          Write gridpoint number data
2465             netcdf_data(1:ns) = section(1:ns,2)
2466             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_ind_y_xz(av), &
2467                                     netcdf_data, start = (/ 1 /),       &
2468                                     count = (/ ns /) )
2469             CALL handle_netcdf_error( 'netcdf', 164 )
2470
2471
2472             DEALLOCATE( netcdf_data )
2473
2474!
2475!--          Write data for x (shifted by +dx/2) and xu axis
2476             ALLOCATE( netcdf_data(0:nx+1) )
2477
2478             DO  i = 0, nx+1
2479                netcdf_data(i) = ( i + 0.5 ) * dx
2480             ENDDO
2481
2482             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av), &
2483                                     netcdf_data, start = (/ 1 /),   &
2484                                     count = (/ nx+2 /) )
2485             CALL handle_netcdf_error( 'netcdf', 165 )
2486
2487             DO  i = 0, nx+1
2488                netcdf_data(i) = i * dx
2489             ENDDO
2490
2491             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_xu_xz(av), &
2492                                     netcdf_data, start = (/ 1 /),    &
2493                                     count = (/ nx+2 /) )
2494             CALL handle_netcdf_error( 'netcdf', 377 )
2495
2496             DEALLOCATE( netcdf_data )
2497
2498!
2499!--          Write zu and zw data (vertical axes)
2500             ALLOCATE( netcdf_data(0:nz+1) )
2501
2502             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
2503             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zu_xz(av), &
2504                                     netcdf_data, start = (/ 1 /),    &
2505                                     count = (/ nz+2 /) )
2506             CALL handle_netcdf_error( 'netcdf', 166 )
2507
2508             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
2509             nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_zw_xz(av), &
2510                                     netcdf_data, start = (/ 1 /),    &
2511                                     count = (/ nz+2 /) )
2512             CALL handle_netcdf_error( 'netcdf', 167 )
2513
2514             DEALLOCATE( netcdf_data )
2515
2516          ENDIF
2517
2518
2519       CASE ( 'xz_ext' )
2520
2521!
2522!--       Get the list of variables and compare with the actual run.
2523!--       First var_list_old has to be reset, since GET_ATT does not assign
2524!--       trailing blanks.
2525          var_list_old = ' '
2526          nc_stat = NF90_GET_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
2527                                  var_list_old )
2528          CALL handle_netcdf_error( 'netcdf', 168 )
2529
2530          var_list = ';'
2531          i = 1
2532          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2533             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
2534                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
2535             ENDIF
2536             i = i + 1
2537          ENDDO
2538
2539          IF ( av == 0 )  THEN
2540             var = '(xz)'
2541          ELSE
2542             var = '(xz_av)'
2543          ENDIF
2544
2545          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
2546             message_string = 'netCDF file for cross-sections ' //           &
2547                              TRIM( var ) // ' from previous run found,' //  &
2548                              '& but this file cannot be extended due to' // &
2549                              ' variable mismatch.' //                       &
2550                              '&New file is created instead.'
2551             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
2552             extend = .FALSE.
2553             RETURN
2554          ENDIF
2555
2556!
2557!--       Calculate the number of current sections
2558          ns = 1
2559          DO WHILE ( section(ns,2) /= -9999  .AND.  ns <= 100 )
2560             ns = ns + 1
2561          ENDDO
2562          ns = ns - 1
2563
2564!
2565!--       Get and compare the number of vertical cross sections
2566          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'y_xz', id_var_y_xz(av) )
2567          CALL handle_netcdf_error( 'netcdf', 169 )
2568
2569          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_y_xz(av), &
2570                                           dimids = id_dim_y_xz_old )
2571          CALL handle_netcdf_error( 'netcdf', 170 )
2572          id_dim_y_xz(av) = id_dim_y_xz_old(1)
2573
2574          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_y_xz(av), &
2575                                            len = ns_old )
2576          CALL handle_netcdf_error( 'netcdf', 171 )
2577
2578          IF ( ns /= ns_old )  THEN
2579             message_string = 'netCDF file for cross-sections ' //          &
2580                              TRIM( var ) // ' from previous run found,' // &
2581                              '&but this file cannot be extended due to' // &
2582                              ' mismatch in number of' //                   & 
2583                              '&cross sections.' //                         &
2584                              '&New file is created instead.'
2585             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
2586             extend = .FALSE.
2587             RETURN
2588          ENDIF
2589
2590!
2591!--       Get and compare the heights of the cross sections
2592          ALLOCATE( netcdf_data(1:ns_old) )
2593
2594          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data )
2595          CALL handle_netcdf_error( 'netcdf', 172 )
2596
2597          DO  i = 1, ns
2598             IF ( section(i,2) /= -1 )  THEN
2599                IF ( ( ( section(i,2) + 0.5 ) * dy ) /= netcdf_data(i) )  THEN
2600                   message_string = 'netCDF file for cross-sections ' //     &
2601                               TRIM( var ) // ' from previous run found,' // &
2602                               '&but this file cannot be extended' //        &
2603                               ' due to mismatch in cross' //                &
2604                               '&section levels.' //                         &
2605                                '&New file is created instead.'
2606                   CALL message( 'define_netcdf_header', 'PA0251', &
2607                                                                 0, 1, 0, 6, 0 )
2608                   extend = .FALSE.
2609                   RETURN
2610                ENDIF
2611             ELSE
2612                IF ( -1.0 /= netcdf_data(i) )  THEN
2613                   message_string = 'netCDF file for cross-sections ' //     &
2614                               TRIM( var ) // ' from previous run found,' // &
2615                               '&but this file cannot be extended' //        &
2616                               ' due to mismatch in cross' //                &
2617                               '&section levels.' //                         &
2618                               '&New file is created instead.'
2619                   CALL message( 'define_netcdf_header', 'PA0251', &
2620                                                                 0, 1, 0, 6, 0 )
2621                   extend = .FALSE.
2622                   RETURN
2623                ENDIF
2624             ENDIF
2625          ENDDO
2626
2627          DEALLOCATE( netcdf_data )
2628
2629!
2630!--       Get the id of the time coordinate (unlimited coordinate) and its
2631!--       last index on the file. The next time level is do2d..count+1.
2632!--       The current time must be larger than the last output time
2633!--       on the file.
2634          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'time', id_var_time_xz(av) )
2635          CALL handle_netcdf_error( 'netcdf', 173 )
2636
2637          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_time_xz(av), &
2638                                           dimids = id_dim_time_old )
2639          CALL handle_netcdf_error( 'netcdf', 174 )
2640          id_dim_time_xz(av) = id_dim_time_old(1)
2641
2642          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_time_xz(av), &
2643                                            len = ntime_count )
2644          CALL handle_netcdf_error( 'netcdf', 175 )
2645
2646!
2647!--       For non-parallel output use the last output time level of the netcdf
2648!--       file because the time dimension is unlimited. In case of parallel
2649!--       output the variable ntime_count could get the value of 9*10E36 because
2650!--       the time dimension is limited.
2651          IF ( netcdf_data_format < 5 ) do2d_xz_time_count(av) = ntime_count
2652
2653          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_time_xz(av),    &
2654                                  last_time_coordinate,                 &
2655                                  start = (/ do2d_xz_time_count(av) /), &
2656                                  count = (/ 1 /) )
2657          CALL handle_netcdf_error( 'netcdf', 176 )
2658
2659          IF ( last_time_coordinate(1) >= simulated_time )  THEN
2660             message_string = 'netCDF file for cross sections ' //          &
2661                              TRIM( var ) // ' from previous run found,' // &
2662                              '&but this file cannot be extended becaus' // &
2663                              'e the current output time' //                &
2664                              '&is less or equal than the last output t' // &
2665                              'ime on this file.' //                        &
2666                              '&New file is created instead.'
2667             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
2668             do2d_xz_time_count(av) = 0
2669             extend = .FALSE.
2670             RETURN
2671          ENDIF
2672         
2673          IF ( netcdf_data_format > 4 )  THEN
2674             IF ( ntdim_2d_xz(av) > ntime_count )  THEN
2675                message_string = 'netCDF file for cross sections ' // &
2676                                 TRIM( var ) // ' from previous run found,' // &
2677                                 '&but this file cannot be extended becaus' // &
2678                                 'e the number of output time levels&has b' // &
2679                                 'een increased compared to the previous s' // &
2680                                 'imulation.' //                                &
2681                                 '&New file is created instead.'
2682                CALL message( 'define_netcdf_header', 'PA0390', 0, 1, 0, 6, 0 )
2683                do2d_xz_time_count(av) = 0
2684                extend = .FALSE.
2685                RETURN
2686             ENDIF
2687          ENDIF
2688
2689!
2690!--       Dataset seems to be extendable.
2691!--       Now get the variable ids.
2692          i = 1
2693          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2694             IF ( INDEX( do2d(av,i), 'xz' ) /= 0 )  THEN
2695                nc_stat = NF90_INQ_VARID( id_set_xz(av), do2d(av,i), &
2696                                          id_var_do2d(av,i) )
2697                CALL handle_netcdf_error( 'netcdf', 177 )
2698#if defined( __netcdf4_parallel )
2699!
2700!--             Set independent io operations for parallel io. Collective io
2701!--             is only allowed in case of a 1d-decomposition along x, because
2702!--             otherwise, not all PEs have output data.
2703                IF ( netcdf_data_format > 4 )  THEN
2704                   IF ( npey == 1 )  THEN
2705                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
2706                                                     id_var_do2d(av,i), &
2707                                                     NF90_COLLECTIVE )
2708                   ELSE
2709!
2710!--                   Test simulations showed that the output of cross sections
2711!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
2712!--                   faster than the output by the first row of PEs in
2713!--                   x-direction using NF90_INDEPENDENT.
2714                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
2715                                                     id_var_do2d(av,i), &
2716                                                     NF90_COLLECTIVE )
2717!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_xz(av),     &
2718!                                                     id_var_do2d(av,i), &
2719!                                                     NF90_INDEPENDENT )
2720                   ENDIF
2721                   CALL handle_netcdf_error( 'netcdf', 455 )
2722                ENDIF
2723#endif
2724             ENDIF
2725             i = i + 1
2726          ENDDO
2727
2728!
2729!--       Update the title attribute on file
2730!--       In order to avoid 'data mode' errors if updated attributes are larger
2731!--       than their original size, NF90_PUT_ATT is called in 'define mode'
2732!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
2733!--       performance loss due to data copying; an alternative strategy would be
2734!--       to ensure equal attribute size in a job chain. Maybe revise later.
2735          IF ( av == 0 )  THEN
2736             time_average_text = ' '
2737          ELSE
2738             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
2739                                                            averaging_interval
2740          ENDIF
2741          nc_stat = NF90_REDEF( id_set_xz(av) )
2742          CALL handle_netcdf_error( 'netcdf', 433 )
2743          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title', &
2744                                  TRIM( run_description_header ) //    &
2745                                  TRIM( time_average_text ) )
2746          CALL handle_netcdf_error( 'netcdf', 178 )
2747          nc_stat = NF90_ENDDEF( id_set_xz(av) )
2748          CALL handle_netcdf_error( 'netcdf', 434 )
2749          message_string = 'netCDF file for cross-sections ' //           &
2750                            TRIM( var ) // ' from previous run found.' // &
2751                           '&This file will be extended.'
2752          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
2753
2754
2755       CASE ( 'yz_new' )
2756
2757!
2758!--       Define some global attributes of the dataset
2759          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'Conventions', &
2760                                  'COARDS' )
2761          CALL handle_netcdf_error( 'netcdf', 179 )
2762
2763          IF ( av == 0 )  THEN
2764             time_average_text = ' '
2765          ELSE
2766             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
2767                                                            averaging_interval
2768          ENDIF
2769          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title', &
2770                                  TRIM( run_description_header ) //    &
2771                                  TRIM( time_average_text ) )
2772          CALL handle_netcdf_error( 'netcdf', 180 )
2773          IF ( av == 1 )  THEN
2774             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
2775             nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'time_avg', &
2776                                     TRIM( time_average_text ) )
2777             CALL handle_netcdf_error( 'netcdf', 180 )
2778          ENDIF
2779
2780!
2781!--       Define time coordinate for yz sections.
2782!--       For parallel output the time dimensions has to be limited, otherwise
2783!--       the performance drops significantly.
2784          IF ( netcdf_data_format < 5 )  THEN
2785             nc_stat = NF90_DEF_DIM( id_set_yz(av), 'time', NF90_UNLIMITED, &
2786                                     id_dim_time_yz(av) )
2787             CALL handle_netcdf_error( 'netcdf', 181 )
2788          ELSE
2789             nc_stat = NF90_DEF_DIM( id_set_yz(av), 'time', ntdim_2d_yz(av), &
2790                                     id_dim_time_yz(av) )
2791             CALL handle_netcdf_error( 'netcdf', 526 )
2792          ENDIF
2793
2794          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'time', NF90_DOUBLE, &
2795                                  id_dim_time_yz(av), id_var_time_yz(av) )
2796          CALL handle_netcdf_error( 'netcdf', 182 )
2797
2798          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_time_yz(av), 'units', &
2799                                  'seconds')
2800          CALL handle_netcdf_error( 'netcdf', 183 )
2801
2802!
2803!--       Define the spatial dimensions and coordinates for yz-sections.
2804!--       First, determine the number of vertical sections to be written.
2805          IF ( section(1,3) == -9999 )  THEN
2806             RETURN
2807          ELSE
2808             ns = 1
2809             DO WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
2810                ns = ns + 1
2811             ENDDO
2812             ns = ns - 1
2813          ENDIF
2814
2815!
2816!--       Define x axis (for scalar position)
2817          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'x_yz', ns, id_dim_x_yz(av) )
2818          CALL handle_netcdf_error( 'netcdf', 184 )
2819
2820          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'x_yz', NF90_DOUBLE, &
2821                                  id_dim_x_yz(av), id_var_x_yz(av) )
2822          CALL handle_netcdf_error( 'netcdf', 185 )
2823
2824          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_x_yz(av), 'units', &
2825                                  'meters' )
2826          CALL handle_netcdf_error( 'netcdf', 186 )
2827
2828!
2829!--       Define x axis (for u position)
2830          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'xu_yz', ns, id_dim_xu_yz(av) )
2831          CALL handle_netcdf_error( 'netcdf', 377 )
2832
2833          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'xu_yz', NF90_DOUBLE, &
2834                                  id_dim_xu_yz(av), id_var_xu_yz(av) )
2835          CALL handle_netcdf_error( 'netcdf', 378 )
2836
2837          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_xu_yz(av), 'units', &
2838                                  'meters' )
2839          CALL handle_netcdf_error( 'netcdf', 379 )
2840
2841!
2842!--       Define a variable to store the layer indices of the vertical cross
2843!--       sections
2844          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'ind_x_yz', NF90_DOUBLE, &
2845                                  id_dim_x_yz(av), id_var_ind_x_yz(av) )
2846          CALL handle_netcdf_error( 'netcdf', 187 )
2847
2848          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_ind_x_yz(av), 'units', &
2849                                  'gridpoints')
2850          CALL handle_netcdf_error( 'netcdf', 188 )
2851
2852!
2853!--       Define y-axis (for scalar position)
2854          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'y', ny+2, id_dim_y_yz(av) )
2855          CALL handle_netcdf_error( 'netcdf', 189 )
2856
2857          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'y', NF90_DOUBLE, &
2858                                  id_dim_y_yz(av), id_var_y_yz(av) )
2859          CALL handle_netcdf_error( 'netcdf', 190 )
2860
2861          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_y_yz(av), 'units', &
2862                                  'meters' )
2863          CALL handle_netcdf_error( 'netcdf', 191 )
2864
2865!
2866!--       Define y-axis (for v position)
2867          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'yv', ny+2, id_dim_yv_yz(av) )
2868          CALL handle_netcdf_error( 'netcdf', 380 )
2869
2870          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'yv', NF90_DOUBLE, &
2871                                  id_dim_yv_yz(av), id_var_yv_yz(av) )
2872          CALL handle_netcdf_error( 'netcdf', 381 )
2873
2874          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_yv_yz(av), 'units', &
2875                                  'meters' )
2876          CALL handle_netcdf_error( 'netcdf', 382 )
2877
2878!
2879!--       Define the two z-axes (zu and zw)
2880          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'zu', nz+2, id_dim_zu_yz(av) )
2881          CALL handle_netcdf_error( 'netcdf', 192 )
2882
2883          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'zu', NF90_DOUBLE, &
2884                                  id_dim_zu_yz(av), id_var_zu_yz(av) )
2885          CALL handle_netcdf_error( 'netcdf', 193 )
2886
2887          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_zu_yz(av), 'units', &
2888                                  'meters' )
2889          CALL handle_netcdf_error( 'netcdf', 194 )
2890
2891          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'zw', nz+2, id_dim_zw_yz(av) )
2892          CALL handle_netcdf_error( 'netcdf', 195 )
2893
2894          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'zw', NF90_DOUBLE, &
2895                                  id_dim_zw_yz(av), id_var_zw_yz(av) )
2896          CALL handle_netcdf_error( 'netcdf', 196 )
2897
2898          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_zw_yz(av), 'units', &
2899                                  'meters' )
2900          CALL handle_netcdf_error( 'netcdf', 197 )
2901
2902
2903!
2904!--       Define the variables
2905          var_list = ';'
2906          i = 1
2907
2908          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
2909
2910             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
2911
2912!
2913!--             Check for the grid
2914                found = .TRUE.
2915                SELECT CASE ( do2d(av,i) )
2916!
2917!--                Most variables are defined on the zu grid
2918                   CASE ( 'e_yz', 'lpt_yz', 'nr_yz', 'p_yz', 'pc_yz', 'pr_yz',&
2919                          'prr_yz', 'pt_yz', 'q_yz', 'qc_yz', 'ql_yz',        &
2920                          'ql_c_yz', 'ql_v_yz', 'ql_vp_yz', 'qr_yz', 'qv_yz', &
2921                          'rho_yz', 's_yz', 'sa_yz', 'vpt_yz' )
2922
2923                      grid_x = 'x'
2924                      grid_y = 'y'
2925                      grid_z = 'zu'
2926!
2927!--                u grid
2928                   CASE ( 'u_yz' )
2929
2930                      grid_x = 'xu'
2931                      grid_y = 'y'
2932                      grid_z = 'zu'
2933!
2934!--                v grid
2935                   CASE ( 'v_yz' )
2936
2937                      grid_x = 'x'
2938                      grid_y = 'yv'
2939                      grid_z = 'zu'
2940!
2941!--                w grid
2942                   CASE ( 'w_yz' )
2943
2944                      grid_x = 'x'
2945                      grid_y = 'y'
2946                      grid_z = 'zw'
2947
2948                   CASE DEFAULT
2949!
2950!--                   Check for user-defined quantities
2951                      CALL user_define_netcdf_grid( do2d(av,i), found, &
2952                                                    grid_x, grid_y, grid_z )
2953
2954                END SELECT
2955
2956!
2957!--             Select the respective dimension ids
2958                IF ( grid_x == 'x' )  THEN
2959                   id_x = id_dim_x_yz(av)
2960                ELSEIF ( grid_x == 'xu' )  THEN
2961                   id_x = id_dim_xu_yz(av)
2962                ENDIF
2963
2964                IF ( grid_y == 'y' )  THEN
2965                   id_y = id_dim_y_yz(av)
2966                ELSEIF ( grid_y == 'yv' )  THEN
2967                   id_y = id_dim_yv_yz(av)
2968                ENDIF
2969
2970                IF ( grid_z == 'zu' )  THEN
2971                   id_z = id_dim_zu_yz(av)
2972                ELSEIF ( grid_z == 'zw' )  THEN
2973                   id_z = id_dim_zw_yz(av)
2974                ENDIF
2975
2976!
2977!--             Define the grid
2978                nc_stat = NF90_DEF_VAR( id_set_yz(av), do2d(av,i),             &
2979                                        nc_precision(3),                       &
2980                                   (/ id_x, id_y, id_z, id_dim_time_yz(av) /), &
2981                                        id_var_do2d(av,i) )
2982
2983                IF ( .NOT. found )  THEN
2984                   WRITE ( message_string, * ) 'no grid defined for', &
2985                                            ' variable ', TRIM( do2d(av,i) )
2986                   CALL message( 'define_netcdf_header', 'PA0244',&
2987                                                                 0, 1, 0, 6, 0 )
2988                ENDIF
2989
2990                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
2991
2992                CALL handle_netcdf_error( 'netcdf', 198 )
2993!
2994!--             Store the 'real' name of the variable (with *, for example)
2995!--             in the long_name attribute. This is evaluated by Ferret,
2996!--             for example.
2997                nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_do2d(av,i), &
2998                                        'long_name', do2d(av,i) )
2999                CALL handle_netcdf_error( 'netcdf', 199 )
3000!
3001!--             Define the variable's unit
3002                nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_do2d(av,i), &
3003                                        'units', TRIM( do2d_unit(av,i) ) )
3004                CALL handle_netcdf_error( 'netcdf', 356 )
3005#if defined( __netcdf4_parallel )
3006                IF ( netcdf_data_format > 4 )  THEN
3007!
3008!--                Set no fill for every variable to increase performance.
3009                   nc_stat = NF90_DEF_VAR_FILL( id_set_yz(av),     &
3010                                                id_var_do2d(av,i), &
3011                                                1, 0 )
3012                   CALL handle_netcdf_error( 'netcdf', 535 )
3013!
3014!--                Set independent io operations for parallel io. Collective io
3015!--                is only allowed in case of a 1d-decomposition along y,
3016!--                because otherwise, not all PEs have output data.
3017                   IF ( npex == 1 )  THEN
3018                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3019                                                     id_var_do2d(av,i), &
3020                                                     NF90_COLLECTIVE )
3021                   ELSE
3022!
3023!--                   Test simulations showed that the output of cross sections
3024!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
3025!--                   faster than the output by the first row of PEs in
3026!--                   y-direction using NF90_INDEPENDENT.
3027                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3028                                                     id_var_do2d(av,i), &
3029                                                     NF90_COLLECTIVE )
3030!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3031!                                                     id_var_do2d(av,i), &
3032!                                                     NF90_INDEPENDENT )
3033                   ENDIF
3034                   CALL handle_netcdf_error( 'netcdf', 450 )
3035                ENDIF
3036#endif
3037             ENDIF
3038
3039             i = i + 1
3040
3041          ENDDO
3042
3043!
3044!--       No arrays to output. Close the netcdf file and return.
3045          IF ( i == 1 )  RETURN
3046
3047!
3048!--       Write the list of variables as global attribute (this is used by
3049!--       restart runs and by combine_plot_fields)
3050          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
3051                                  var_list )
3052          CALL handle_netcdf_error( 'netcdf', 200 )
3053
3054!
3055!--       Set general no fill, otherwise the performance drops significantly for
3056!--       parallel output.
3057          nc_stat = NF90_SET_FILL( id_set_yz(av), NF90_NOFILL, oldmode )
3058          CALL handle_netcdf_error( 'netcdf', 531 )
3059
3060!
3061!--       Leave netCDF define mode
3062          nc_stat = NF90_ENDDEF( id_set_yz(av) )
3063          CALL handle_netcdf_error( 'netcdf', 201 )
3064
3065!
3066!--       These data are only written by PE0 for parallel output to increase
3067!--       the performance.
3068          IF ( myid == 0  .OR.  netcdf_data_format < 5 )  THEN
3069
3070!
3071!--          Write axis data: x_yz, y, zu, zw
3072             ALLOCATE( netcdf_data(1:ns) )
3073
3074!
3075!--          Write x_yz data (shifted by +dx/2)
3076             DO  i = 1, ns
3077                IF( section(i,3) == -1 )  THEN
3078                   netcdf_data(i) = -1.0  ! section averaged along x
3079                ELSE
3080                   netcdf_data(i) = ( section(i,3) + 0.5 ) * dx
3081                ENDIF
3082             ENDDO
3083             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), &
3084                                     netcdf_data, start = (/ 1 /),   &
3085                                     count = (/ ns /) )
3086             CALL handle_netcdf_error( 'netcdf', 202 ) 
3087
3088!
3089!--          Write x_yz data (xu grid)
3090             DO  i = 1, ns
3091                IF( section(i,3) == -1 )  THEN
3092                   netcdf_data(i) = -1.0  ! section averaged along x
3093                ELSE
3094                   netcdf_data(i) = section(i,3) * dx
3095                ENDIF
3096             ENDDO
3097             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av), &
3098                                     netcdf_data, start = (/ 1 /),    &
3099                                     count = (/ ns /) )
3100             CALL handle_netcdf_error( 'netcdf', 383 ) 
3101
3102!
3103!--          Write gridpoint number data
3104             netcdf_data(1:ns) = section(1:ns,3)
3105             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_ind_x_yz(av), &
3106                                     netcdf_data, start = (/ 1 /),       &
3107                                     count = (/ ns /) )
3108             CALL handle_netcdf_error( 'netcdf', 203 ) 
3109
3110             DEALLOCATE( netcdf_data )
3111
3112!
3113!--          Write data for y (shifted by +dy/2) and yv axis
3114             ALLOCATE( netcdf_data(0:ny+1) )
3115
3116             DO  j = 0, ny+1
3117                netcdf_data(j) = ( j + 0.5 ) * dy
3118             ENDDO
3119
3120             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av), &
3121                                     netcdf_data, start = (/ 1 /),   &
3122                                     count = (/ ny+2 /) )
3123             CALL handle_netcdf_error( 'netcdf', 204 ) 
3124
3125             DO  j = 0, ny+1
3126                netcdf_data(j) = j * dy
3127             ENDDO
3128
3129             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_yv_yz(av), &
3130                                     netcdf_data, start = (/ 1 /),    &
3131                                     count = (/ ny+2 /) )
3132             CALL handle_netcdf_error( 'netcdf', 384 ) 
3133
3134             DEALLOCATE( netcdf_data )
3135
3136!
3137!--          Write zu and zw data (vertical axes)
3138             ALLOCATE( netcdf_data(0:nz+1) )
3139
3140             netcdf_data(0:nz+1) = zu(nzb:nzt+1)
3141             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zu_yz(av), &
3142                                     netcdf_data, start = (/ 1 /),    &
3143                                     count = (/ nz+2 /) )
3144             CALL handle_netcdf_error( 'netcdf', 205 ) 
3145
3146             netcdf_data(0:nz+1) = zw(nzb:nzt+1)
3147             nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_zw_yz(av), &
3148                                     netcdf_data, start = (/ 1 /),    &
3149                                     count = (/ nz+2 /) )
3150             CALL handle_netcdf_error( 'netcdf', 206 ) 
3151
3152             DEALLOCATE( netcdf_data )
3153
3154          ENDIF
3155
3156
3157       CASE ( 'yz_ext' )
3158
3159!
3160!--       Get the list of variables and compare with the actual run.
3161!--       First var_list_old has to be reset, since GET_ATT does not assign
3162!--       trailing blanks.
3163          var_list_old = ' '
3164          nc_stat = NF90_GET_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
3165                                  var_list_old )
3166          CALL handle_netcdf_error( 'netcdf', 207 )
3167
3168          var_list = ';'
3169          i = 1
3170          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
3171             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
3172                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
3173             ENDIF
3174             i = i + 1
3175          ENDDO
3176
3177          IF ( av == 0 )  THEN
3178             var = '(yz)'
3179          ELSE
3180             var = '(yz_av)'
3181          ENDIF
3182
3183          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
3184             message_string = 'netCDF file for cross-sections ' //           &
3185                              TRIM( var ) // ' from previous run found,' //  &
3186                              '& but this file cannot be extended due to' // &
3187                              ' variable mismatch.' //                       & 
3188                              '&New file is created instead.'
3189             CALL message( 'define_netcdf_header', 'PA0249', 0, 1, 0, 6, 0 )
3190             extend = .FALSE.
3191             RETURN
3192          ENDIF
3193
3194!
3195!--       Calculate the number of current sections
3196          ns = 1
3197          DO WHILE ( section(ns,3) /= -9999  .AND.  ns <= 100 )
3198             ns = ns + 1
3199          ENDDO
3200          ns = ns - 1
3201
3202!
3203!--       Get and compare the number of vertical cross sections
3204          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'x_yz', id_var_x_yz(av) )
3205          CALL handle_netcdf_error( 'netcdf', 208 )
3206
3207          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_x_yz(av), &
3208                                           dimids = id_dim_x_yz_old )
3209          CALL handle_netcdf_error( 'netcdf', 209 )
3210          id_dim_x_yz(av) = id_dim_x_yz_old(1)
3211
3212          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_x_yz(av), &
3213                                            len = ns_old )
3214          CALL handle_netcdf_error( 'netcdf', 210 )
3215
3216          IF ( ns /= ns_old )  THEN
3217             message_string = 'netCDF file for cross-sections ' //          &
3218                              TRIM( var ) // ' from previous run found,' // &
3219                              '&but this file cannot be extended due to' // &
3220                              ' mismatch in number of' //                   &
3221                              '&cross sections.' //                         &
3222                              '&New file is created instead.'
3223             CALL message( 'define_netcdf_header', 'PA0250', 0, 1, 0, 6, 0 )
3224             extend = .FALSE.
3225             RETURN
3226          ENDIF
3227
3228!
3229!--       Get and compare the heights of the cross sections
3230          ALLOCATE( netcdf_data(1:ns_old) )
3231
3232          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data )
3233          CALL handle_netcdf_error( 'netcdf', 211 )
3234
3235          DO  i = 1, ns
3236             IF ( section(i,3) /= -1 )  THEN
3237                IF ( ( ( section(i,3) + 0.5 ) * dx ) /= netcdf_data(i) )  THEN
3238                   message_string = 'netCDF file for cross-sections ' //    &
3239                              TRIM( var ) // ' from previous run found,' // &
3240                              '&but this file cannot be extended' //        &
3241                              ' due to mismatch in cross' //                &
3242                              '&section levels.' //                         &
3243                             '&New file is created instead.'
3244                   CALL message( 'define_netcdf_header', 'PA0251', &
3245                                                                 0, 1, 0, 6, 0 )
3246                   extend = .FALSE.
3247                   RETURN
3248                ENDIF
3249             ELSE
3250                IF ( -1.0 /= netcdf_data(i) )  THEN
3251                   message_string = 'netCDF file for cross-sections ' //    &
3252                              TRIM( var ) // ' from previous run found,' // &
3253                              '&but this file cannot be extended' //        &
3254                              ' due to mismatch in cross' //                &
3255                              '&section levels.' //                         &
3256                              '&New file is created instead.'
3257                   CALL message( 'define_netcdf_header', 'PA0251', &
3258                                                                 0, 1, 0, 6, 0 )
3259                   extend = .FALSE.
3260                   RETURN
3261                ENDIF
3262             ENDIF
3263          ENDDO
3264
3265          DEALLOCATE( netcdf_data )
3266
3267!
3268!--       Get the id of the time coordinate (unlimited coordinate) and its
3269!--       last index on the file. The next time level is pl2d..count+1.
3270!--       The current time must be larger than the last output time
3271!--       on the file.
3272          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'time', id_var_time_yz(av) )
3273          CALL handle_netcdf_error( 'netcdf', 212 )
3274
3275          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_time_yz(av), &
3276                                           dimids = id_dim_time_old )
3277          CALL handle_netcdf_error( 'netcdf', 213 )
3278          id_dim_time_yz(av) = id_dim_time_old(1)
3279
3280          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_time_yz(av), &
3281                                            len = ntime_count )
3282          CALL handle_netcdf_error( 'netcdf', 214 )
3283
3284!
3285!--       For non-parallel output use the last output time level of the netcdf
3286!--       file because the time dimension is unlimited. In case of parallel
3287!--       output the variable ntime_count could get the value of 9*10E36 because
3288!--       the time dimension is limited.
3289          IF ( netcdf_data_format < 5 ) do2d_yz_time_count(av) = ntime_count
3290
3291          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_time_yz(av),    &
3292                                  last_time_coordinate,                 &
3293                                  start = (/ do2d_yz_time_count(av) /), &
3294                                  count = (/ 1 /) )
3295          CALL handle_netcdf_error( 'netcdf', 215 )
3296
3297          IF ( last_time_coordinate(1) >= simulated_time )  THEN
3298             message_string = 'netCDF file for cross sections ' //          &
3299                              TRIM( var ) // ' from previous run found,' // &
3300                              '&but this file cannot be extended becaus' // &
3301                              'e the current output time' //                &
3302                              '&is less or equal than the last output t' // &
3303                              'ime on this file.' //                        &
3304                              '&New file is created instead.'
3305             CALL message( 'define_netcdf_header', 'PA0252', 0, 1, 0, 6, 0 )
3306             do2d_yz_time_count(av) = 0
3307             extend = .FALSE.
3308             RETURN
3309          ENDIF
3310
3311          IF ( netcdf_data_format > 4 )  THEN
3312             IF ( ntdim_2d_yz(av) > ntime_count )  THEN
3313                message_string = 'netCDF file for cross sections ' //          &
3314                                 TRIM( var ) // ' from previous run found,' // &
3315                                 '&but this file cannot be extended becaus' // &
3316                                 'e the number of output time levels&has b' // &
3317                                 'een increased compared to the previous s' // &
3318                                 'imulation.' //                               &
3319                                 '&New file is created instead.'
3320                CALL message( 'define_netcdf_header', 'PA0391', 0, 1, 0, 6, 0 )
3321                do2d_yz_time_count(av) = 0
3322                extend = .FALSE.
3323                RETURN
3324             ENDIF
3325          ENDIF
3326
3327!
3328!--       Dataset seems to be extendable.
3329!--       Now get the variable ids.
3330          i = 1
3331          DO WHILE ( do2d(av,i)(1:1) /= ' ' )
3332             IF ( INDEX( do2d(av,i), 'yz' ) /= 0 )  THEN
3333                nc_stat = NF90_INQ_VARID( id_set_yz(av), do2d(av,i), &
3334                                          id_var_do2d(av,i) )
3335                CALL handle_netcdf_error( 'netcdf', 216 )
3336#if defined( __netcdf4_parallel )
3337!
3338!--             Set independent io operations for parallel io. Collective io
3339!--             is only allowed in case of a 1d-decomposition along y, because
3340!--             otherwise, not all PEs have output data.
3341                IF ( netcdf_data_format > 4 )  THEN
3342                   IF ( npex == 1 )  THEN
3343                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3344                                                     id_var_do2d(av,i), &
3345                                                     NF90_COLLECTIVE )
3346                   ELSE
3347!
3348!--                   Test simulations showed that the output of cross sections
3349!--                   by all PEs in data_output_2d using NF90_COLLECTIVE is
3350!--                   faster than the output by the first row of PEs in
3351!--                   y-direction using NF90_INDEPENDENT.
3352                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3353                                                     id_var_do2d(av,i), &
3354                                                     NF90_COLLECTIVE )
3355!                      nc_stat = NF90_VAR_PAR_ACCESS( id_set_yz(av),     &
3356!                                                     id_var_do2d(av,i), &
3357!                                                     NF90_INDEPENDENT )
3358                   ENDIF
3359                   CALL handle_netcdf_error( 'netcdf', 450 )
3360                ENDIF
3361#endif
3362             ENDIF
3363             i = i + 1
3364          ENDDO
3365
3366!
3367!--       Update the title attribute on file
3368!--       In order to avoid 'data mode' errors if updated attributes are larger
3369!--       than their original size, NF90_PUT_ATT is called in 'define mode'
3370!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
3371!--       performance loss due to data copying; an alternative strategy would be
3372!--       to ensure equal attribute size in a job chain. Maybe revise later.
3373          IF ( av == 0 )  THEN
3374             time_average_text = ' '
3375          ELSE
3376             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
3377                                                            averaging_interval
3378          ENDIF
3379          nc_stat = NF90_REDEF( id_set_yz(av) )
3380          CALL handle_netcdf_error( 'netcdf', 435 )
3381          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title', &
3382                                  TRIM( run_description_header ) //    &
3383                                  TRIM( time_average_text ) )
3384          CALL handle_netcdf_error( 'netcdf', 217 )
3385          nc_stat = NF90_ENDDEF( id_set_yz(av) )
3386          CALL handle_netcdf_error( 'netcdf', 436 )
3387          message_string = 'netCDF file for cross-sections ' //           &
3388                            TRIM( var ) // ' from previous run found.' // &
3389                           '&This file will be extended.'
3390          CALL message( 'define_netcdf_header', 'PA0253', 0, 0, 0, 6, 0 )
3391
3392
3393       CASE ( 'pr_new' )
3394
3395!
3396!--       Define some global attributes of the dataset
3397          IF ( averaging_interval_pr /= 0.0 )  THEN
3398             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
3399                                                            averaging_interval_pr
3400             nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title',   &
3401                                     TRIM( run_description_header ) //  &
3402                                     TRIM( time_average_text ) )
3403             CALL handle_netcdf_error( 'netcdf', 218 )
3404
3405             WRITE ( time_average_text,'(F7.1,'' s avg'')' ) averaging_interval_pr
3406             nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'time_avg', &
3407                                     TRIM( time_average_text ) )
3408          ELSE
3409             nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title', &
3410                                     TRIM( run_description_header ) )
3411          ENDIF
3412          CALL handle_netcdf_error( 'netcdf', 219 )
3413
3414!
3415!--       Write number of columns and rows of coordinate systems to be plotted
3416!--       on one page to the netcdf header.
3417!--       This information can be used by palmplot.
3418          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
3419                                  'no_rows',                                  & 
3420                                  profile_rows ) 
3421          CALL handle_netcdf_error( 'netcdf', 519 )
3422
3423          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL,                     &
3424                                  'no_columns',                               & 
3425                                  profile_columns ) 
3426          CALL handle_netcdf_error( 'netcdf', 520 )
3427
3428
3429          cross_profiles_adj  = ADJUSTL( cross_profiles )
3430          cross_profiles_numb = 999999
3431          cross_profiles_char = ''
3432
3433!
3434!--       Each profile defined in cross_profiles is written to an array
3435!--       (cross_profiles_char). The number of the respective coordinate
3436!--       system is assigned in a second array (cross_profiles_numb).
3437          k = 1
3438
3439          DO  i = 1, crmax
3440
3441             IF ( TRIM( cross_profiles_adj(i) ) == ' ' )  EXIT
3442             delim_old = 0
3443
3444             DO   j = 1, crmax
3445                delim = INDEX( cross_profiles_adj(i)(delim_old+1:), ' ' )
3446                IF ( delim == 1 )  EXIT
3447                kk = MIN( crmax, k )
3448                cross_profiles_char(kk) = cross_profiles_adj(i)(delim_old+1: &
3449                                                              delim_old+delim-1)
3450                cross_profiles_numb(kk) = i
3451                k = k + 1
3452                cross_profiles_maxi  = i
3453                delim_old = delim_old + delim
3454             ENDDO
3455
3456          ENDDO
3457
3458          cross_profiles_count = MIN( crmax, k-1 )
3459!
3460!--       Check if all profiles defined in cross_profiles are defined in
3461!--       data_output_pr. If not, they will be skipped.
3462
3463          DO  i = 1, cross_profiles_count
3464             DO  j = 1, dopr_n
3465
3466                IF ( TRIM(cross_profiles_char(i)) == TRIM(data_output_pr(j)) ) &
3467                THEN
3468                   EXIT
3469                ENDIF
3470
3471                IF ( j == dopr_n )  THEN
3472                   cross_profiles_numb(i) = 999999
3473                ENDIF
3474
3475             ENDDO
3476          ENDDO
3477
3478          DO i = 1, crmax
3479             IF ( cross_profiles_numb(i) == 999999 ) THEN
3480                DO j = i + 1, crmax
3481                   IF ( cross_profiles_numb(j) /= 999999 ) THEN
3482                      cross_profiles_char(i) = cross_profiles_char(j)
3483                      cross_profiles_numb(i) = cross_profiles_numb(j)
3484                      cross_profiles_numb(j) = 999999
3485                      EXIT
3486                   ENDIF
3487                ENDDO
3488             ENDIF
3489          ENDDO
3490
3491          DO i = 1, crmax-1
3492             IF ( cross_profiles_numb(i + 1) == 999999 ) THEN
3493                cross_profiles_count = i
3494                EXIT
3495             ENDIF
3496          ENDDO
3497!
3498!--       Check if all profiles defined in data_output_pr are defined in
3499!--       cross_profiles. If not, they will be added to cross_profiles.
3500
3501          DO  i = 1, dopr_n
3502             DO  j = 1, cross_profiles_count
3503
3504                IF ( TRIM(cross_profiles_char(j)) == TRIM(data_output_pr(i))) &
3505                THEN
3506                   EXIT
3507                ENDIF
3508
3509                IF (( j == cross_profiles_count ) .AND.                        &
3510                    ( cross_profiles_count <= crmax - 1))  THEN
3511                   cross_profiles_count = cross_profiles_count + 1
3512                   cross_profiles_maxi  = cross_profiles_maxi  + 1
3513                   cross_profiles_char(MIN( crmax, cross_profiles_count )) =  &
3514                                                      TRIM( data_output_pr(i) )
3515                   cross_profiles_numb(MIN( crmax, cross_profiles_count )) =  &
3516                                                      cross_profiles_maxi
3517                ENDIF
3518
3519             ENDDO
3520          ENDDO
3521
3522          IF ( cross_profiles_count >= crmax )  THEN
3523             message_string = 'It is not allowed to arrange more than '     &
3524                              // '100 profiles with & cross_profiles. Apart'&
3525                              // ' from that, all profiles are saved & to ' &
3526                              // 'the netCDF file.'
3527             CALL message( 'define_netcdf_header', 'PA0354', 0, 0, 0, 6, 0 )
3528          ENDIF
3529
3530!
3531!--       Writing cross_profiles to netcdf header. This information can be
3532!--       used by palmplot. Each profile is separated by ",", each cross is
3533!--       separated by ";".
3534          char_cross_profiles = ';'
3535          id_last = 1
3536          cross_profiles_count = MIN( cross_profiles_count, crmax )
3537
3538          DO  i = 1, cross_profiles_count
3539
3540             IF ( cross_profiles_numb(i) /= 999999 )  THEN
3541                IF ( TRIM( char_cross_profiles ) == ';' )  THEN
3542                   char_cross_profiles = TRIM( char_cross_profiles ) // &
3543                                         TRIM( cross_profiles_char(i) )
3544                ELSEIF ( id_last == cross_profiles_numb(i) )  THEN
3545                   char_cross_profiles = TRIM( char_cross_profiles ) // &
3546                                         ',' // TRIM( cross_profiles_char(i) )
3547                ELSE
3548                   char_cross_profiles = TRIM( char_cross_profiles ) // &
3549                                         ';' // TRIM( cross_profiles_char(i) )
3550                ENDIF
3551                id_last = cross_profiles_numb(i)
3552             ENDIF
3553
3554          ENDDO
3555
3556          char_cross_profiles = TRIM( char_cross_profiles ) // ';'
3557
3558          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'cross_profiles',   &
3559                                  TRIM( char_cross_profiles ) )
3560          CALL handle_netcdf_error( 'netcdf', 521 )
3561
3562!
3563!--       Define time coordinate for profiles (unlimited dimension)
3564          nc_stat = NF90_DEF_DIM( id_set_pr, 'time', NF90_UNLIMITED, &
3565                                  id_dim_time_pr )
3566          CALL handle_netcdf_error( 'netcdf', 220 )
3567
3568          nc_stat = NF90_DEF_VAR( id_set_pr, 'time', NF90_DOUBLE, &
3569                                  id_dim_time_pr, id_var_time_pr )
3570          CALL handle_netcdf_error( 'netcdf', 221 )
3571
3572          nc_stat = NF90_PUT_ATT( id_set_pr, id_var_time_pr, 'units', 'seconds')
3573          CALL handle_netcdf_error( 'netcdf', 222 )
3574
3575!
3576!--       Define the variables
3577          var_list = ';'
3578          DO  i = 1, dopr_n
3579
3580             IF ( statistic_regions == 0 )  THEN
3581
3582!
3583!--             Define the z-axes (each variable gets its own z-axis)
3584                nc_stat = NF90_DEF_DIM( id_set_pr,                        &
3585                                        'z' // TRIM( data_output_pr(i) ), &
3586                                        nzt+2-nzb, id_dim_z_pr(i,0) )
3587                CALL handle_netcdf_error( 'netcdf', 223 )
3588
3589                nc_stat = NF90_DEF_VAR( id_set_pr,                        &
3590                                        'z' // TRIM( data_output_pr(i) ), &
3591                                        NF90_DOUBLE, id_dim_z_pr(i,0),    &
3592                                        id_var_z_pr(i,0) )
3593                CALL handle_netcdf_error( 'netcdf', 224 )
3594
3595                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_z_pr(i,0), 'units', &
3596                                        'meters' )
3597                CALL handle_netcdf_error( 'netcdf', 225 )
3598!
3599!--             Define the variable
3600                nc_stat = NF90_DEF_VAR( id_set_pr, data_output_pr(i),         &
3601                                        nc_precision(5), (/ id_dim_z_pr(i,0), &
3602                                        id_dim_time_pr /), id_var_dopr(i,0) )
3603                CALL handle_netcdf_error( 'netcdf', 226 )
3604
3605                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,0), &
3606                                        'long_name', TRIM( data_output_pr(i) ) )
3607                CALL handle_netcdf_error( 'netcdf', 227 )
3608
3609                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,0), &
3610                                        'units', TRIM( dopr_unit(i) ) )
3611                CALL handle_netcdf_error( 'netcdf', 228 )
3612
3613                var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) //  ';'
3614
3615             ELSE
3616!
3617!--             If statistic regions are defined, add suffix _SR+#SR to the
3618!--             names
3619                DO  j = 0, statistic_regions
3620                   WRITE ( suffix, '(''_'',I1)' )  j
3621
3622!
3623!--                Define the z-axes (each variable gets it own z-axis)
3624                   nc_stat = NF90_DEF_DIM( id_set_pr,                          &
3625                                         'z'//TRIM(data_output_pr(i))//suffix, &
3626                                           nzt+2-nzb, id_dim_z_pr(i,j) )
3627                   CALL handle_netcdf_error( 'netcdf', 229 )
3628
3629                   nc_stat = NF90_DEF_VAR( id_set_pr,                          &
3630                                         'z'//TRIM(data_output_pr(i))//suffix, &
3631                                           nc_precision(5), id_dim_z_pr(i,j),  &
3632                                           id_var_z_pr(i,j) )
3633                   CALL handle_netcdf_error( 'netcdf', 230 )
3634
3635                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_z_pr(i,j), &
3636                                           'units', 'meters' )
3637                   CALL handle_netcdf_error( 'netcdf', 231 )
3638
3639!
3640!--                Define the variable
3641                   nc_stat = NF90_DEF_VAR( id_set_pr,                         &
3642                                           TRIM(data_output_pr(i)) // suffix, &
3643                                           nc_precision(5),                   &
3644                                           (/ id_dim_z_pr(i,j),               &
3645                                           id_dim_time_pr /), id_var_dopr(i,j) )
3646                   CALL handle_netcdf_error( 'netcdf', 232 )
3647
3648                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,j),        &
3649                                           'long_name',                        &
3650                                           TRIM( data_output_pr(i) ) // ' SR ' &
3651                                           // suffix(2:2) )
3652                   CALL handle_netcdf_error( 'netcdf', 233 )
3653
3654                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,j), &
3655                                           'units', TRIM( dopr_unit(i) ) )
3656                   CALL handle_netcdf_error( 'netcdf', 234 )
3657
3658                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
3659                              suffix // ';'
3660
3661                ENDDO
3662
3663             ENDIF
3664
3665          ENDDO
3666
3667!
3668!--       Write the list of variables as global attribute (this is used by
3669!--       restart runs)
3670          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', var_list )
3671          CALL handle_netcdf_error( 'netcdf', 235 )
3672
3673!
3674!--       Define normalization variables (as time series)
3675          DO  i = 1, dopr_norm_num
3676
3677             nc_stat = NF90_DEF_VAR( id_set_pr, 'NORM_' // &
3678                                     TRIM( dopr_norm_names(i) ), &
3679                                     nc_precision(5), (/ id_dim_time_pr /), &
3680                                     id_var_norm_dopr(i) )
3681             CALL handle_netcdf_error( 'netcdf', 236 )
3682
3683             nc_stat = NF90_PUT_ATT( id_set_pr, id_var_norm_dopr(i), &
3684                                     'long_name',                    &
3685                                     TRIM( dopr_norm_longnames(i) ) )
3686             CALL handle_netcdf_error( 'netcdf', 237 )
3687
3688          ENDDO
3689
3690!
3691!--       Leave netCDF define mode
3692          nc_stat = NF90_ENDDEF( id_set_pr )
3693          CALL handle_netcdf_error( 'netcdf', 238 )
3694
3695!
3696!--       Write z-axes data
3697          DO  i = 1, dopr_n
3698             DO  j = 0, statistic_regions
3699
3700                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_z_pr(i,j),      &
3701                                        hom(nzb:nzt+1,2,dopr_index(i),0), &
3702                                        start = (/ 1 /),                  &
3703                                        count = (/ nzt-nzb+2 /) )
3704                CALL handle_netcdf_error( 'netcdf', 239 )
3705
3706             ENDDO
3707          ENDDO
3708
3709
3710       CASE ( 'pr_ext' )
3711
3712!
3713!--       Get the list of variables and compare with the actual run.
3714!--       First var_list_old has to be reset, since GET_ATT does not assign
3715!--       trailing blanks.
3716          var_list_old = ' '
3717          nc_stat = NF90_GET_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', &
3718                                  var_list_old )
3719          CALL handle_netcdf_error( 'netcdf', 240 )
3720
3721          var_list = ';'
3722          DO  i = 1, dopr_n
3723
3724             IF ( statistic_regions == 0 )  THEN
3725                var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // ';'
3726             ELSE
3727                DO  j = 0, statistic_regions
3728                   WRITE ( suffix, '(''_'',I1)' )  j
3729                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
3730                              suffix // ';'
3731                ENDDO
3732             ENDIF
3733
3734          ENDDO
3735
3736          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
3737             message_string = 'netCDF file for vertical profiles ' //        &
3738                              'from previous run found,' //                  &
3739                              '& but this file cannot be extended due to' // &
3740                              ' variable mismatch.' //                       &
3741                              '&New file is created instead.'
3742             CALL message( 'define_netcdf_header', 'PA0254', 0, 1, 0, 6, 0 )
3743             extend = .FALSE.
3744             RETURN
3745          ENDIF
3746
3747!
3748!--       Get the id of the time coordinate (unlimited coordinate) and its
3749!--       last index on the file. The next time level is dopr..count+1.
3750!--       The current time must be larger than the last output time
3751!--       on the file.
3752          nc_stat = NF90_INQ_VARID( id_set_pr, 'time', id_var_time_pr )
3753          CALL handle_netcdf_error( 'netcdf', 241 )
3754
3755          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pr, id_var_time_pr, &
3756                                           dimids = id_dim_time_old )
3757          CALL handle_netcdf_error( 'netcdf', 242 )
3758          id_dim_time_pr = id_dim_time_old(1)
3759
3760          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pr, id_dim_time_pr, &
3761                                            len = dopr_time_count )
3762          CALL handle_netcdf_error( 'netcdf', 243 )
3763
3764          nc_stat = NF90_GET_VAR( id_set_pr, id_var_time_pr,        &
3765                                  last_time_coordinate,             &
3766                                  start = (/ dopr_time_count /), &
3767                                  count = (/ 1 /) )
3768          CALL handle_netcdf_error( 'netcdf', 244 )
3769
3770          IF ( last_time_coordinate(1) >= simulated_time )  THEN
3771             message_string = 'netCDF file for vertical profiles ' //       &
3772                              'from previous run found,' //                 &
3773                              '&but this file cannot be extended becaus' // &
3774                              'e the current output time' //                &
3775                              '&is less or equal than the last output t' // &
3776                              'ime on this file.' //                        &
3777                              '&New file is created instead.'
3778             CALL message( 'define_netcdf_header', 'PA0255', 0, 1, 0, 6, 0 )
3779             dopr_time_count = 0
3780             extend = .FALSE.
3781             RETURN
3782          ENDIF
3783
3784!
3785!--       Dataset seems to be extendable.
3786!--       Now get the variable ids.
3787          i = 1
3788          DO  i = 1, dopr_n
3789 
3790             IF ( statistic_regions == 0 )  THEN
3791                nc_stat = NF90_INQ_VARID( id_set_pr, data_output_pr(i), &
3792                                          id_var_dopr(i,0) )
3793                CALL handle_netcdf_error( 'netcdf', 245 )
3794             ELSE
3795                DO  j = 0, statistic_regions
3796                   WRITE ( suffix, '(''_'',I1)' )  j
3797                   netcdf_var_name = TRIM( data_output_pr(i) ) // suffix
3798                   nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name, &
3799                                             id_var_dopr(i,j) )
3800                   CALL handle_netcdf_error( 'netcdf', 246 )
3801                ENDDO
3802             ENDIF
3803
3804          ENDDO
3805
3806!
3807!--       Get ids of the normalization variables
3808          DO  i = 1, dopr_norm_num
3809             nc_stat = NF90_INQ_VARID( id_set_pr,                             &
3810                                       'NORM_' // TRIM( dopr_norm_names(i) ), &
3811                                       id_var_norm_dopr(i) )
3812             CALL handle_netcdf_error( 'netcdf', 247 )
3813          ENDDO
3814
3815!
3816!--       Update the title attribute on file
3817!--       In order to avoid 'data mode' errors if updated attributes are larger
3818!--       than their original size, NF90_PUT_ATT is called in 'define mode'
3819!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
3820!--       performance loss due to data copying; an alternative strategy would be
3821!--       to ensure equal attribute size in a job chain. Maybe revise later.
3822          IF ( averaging_interval_pr == 0.0 )  THEN
3823             time_average_text = ' '
3824          ELSE
3825             WRITE (time_average_text, '('', '',F7.1,'' s average'')') &
3826                                                            averaging_interval_pr
3827          ENDIF
3828          nc_stat = NF90_REDEF( id_set_pr )
3829          CALL handle_netcdf_error( 'netcdf', 437 )
3830          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title', &
3831                                  TRIM( run_description_header ) //    &
3832                                  TRIM( time_average_text ) )
3833          CALL handle_netcdf_error( 'netcdf', 248 )
3834
3835          nc_stat = NF90_ENDDEF( id_set_pr )
3836          CALL handle_netcdf_error( 'netcdf', 438 )
3837          message_string = 'netCDF file for vertical profiles ' // &
3838                           'from previous run found.' //           &
3839                           '&This file will be extended.'
3840          CALL message( 'define_netcdf_header', 'PA0256', 0, 0, 0, 6, 0 )
3841
3842
3843       CASE ( 'ts_new' )
3844
3845!
3846!--       Define some global attributes of the dataset
3847          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', &
3848                                  TRIM( run_description_header ) )
3849          CALL handle_netcdf_error( 'netcdf', 249 )
3850
3851!
3852!--       Define time coordinate for time series (unlimited dimension)
3853          nc_stat = NF90_DEF_DIM( id_set_ts, 'time', NF90_UNLIMITED, &
3854                                  id_dim_time_ts )
3855          CALL handle_netcdf_error( 'netcdf', 250 )
3856
3857          nc_stat = NF90_DEF_VAR( id_set_ts, 'time', NF90_DOUBLE, &
3858                                  id_dim_time_ts, id_var_time_ts )
3859          CALL handle_netcdf_error( 'netcdf', 251 )
3860
3861          nc_stat = NF90_PUT_ATT( id_set_ts, id_var_time_ts, 'units', 'seconds')
3862          CALL handle_netcdf_error( 'netcdf', 252 )
3863
3864!
3865!--       Define the variables
3866          var_list = ';'
3867          DO  i = 1, dots_num
3868
3869             IF ( statistic_regions == 0 )  THEN
3870
3871                nc_stat = NF90_DEF_VAR( id_set_ts, dots_label(i),              &
3872                                        nc_precision(6), (/ id_dim_time_ts /), &
3873                                        id_var_dots(i,0) )
3874                CALL handle_netcdf_error( 'netcdf', 253 )
3875
3876                nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,0), &
3877                                        'long_name', TRIM( dots_label(i) ) )
3878                CALL handle_netcdf_error( 'netcdf', 254 )
3879
3880                nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,0), &
3881                                        'units', TRIM( dots_unit(i) ) )
3882                CALL handle_netcdf_error( 'netcdf', 255 )
3883
3884                var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // ';'
3885
3886             ELSE
3887!
3888!--             If statistic regions are defined, add suffix _SR+#SR to the
3889!--             names
3890                DO  j = 0, statistic_regions
3891                   WRITE ( suffix, '(''_'',I1)' )  j
3892
3893                   nc_stat = NF90_DEF_VAR( id_set_ts,                         &
3894                                           TRIM( dots_label(i) ) // suffix,   &
3895                                           nc_precision(6),                   &
3896                                           (/ id_dim_time_ts /),              &
3897                                           id_var_dots(i,j) )
3898                   CALL handle_netcdf_error( 'netcdf', 256 )
3899
3900                   nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,j),       &
3901                                           'long_name',                       &
3902                                           TRIM( dots_label(i) ) // ' SR ' // &
3903                                           suffix(2:2) )
3904                   CALL handle_netcdf_error( 'netcdf', 257 )
3905
3906                   nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,j), &
3907                                           'units', TRIM( dots_unit(i) ) )
3908                   CALL handle_netcdf_error( 'netcdf', 347 )
3909
3910                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // &
3911                              suffix // ';'
3912
3913                ENDDO
3914
3915             ENDIF
3916
3917          ENDDO
3918
3919!
3920!--       Write the list of variables as global attribute (this is used by
3921!--       restart runs)
3922          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', var_list )
3923          CALL handle_netcdf_error( 'netcdf', 258 )
3924
3925!
3926!--       Leave netCDF define mode
3927          nc_stat = NF90_ENDDEF( id_set_ts )
3928          CALL handle_netcdf_error( 'netcdf', 259 )
3929
3930
3931       CASE ( 'ts_ext' )
3932
3933!
3934!--       Get the list of variables and compare with the actual run.
3935!--       First var_list_old has to be reset, since GET_ATT does not assign
3936!--       trailing blanks.
3937          var_list_old = ' '
3938          nc_stat = NF90_GET_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', &
3939                                  var_list_old )
3940          CALL handle_netcdf_error( 'netcdf', 260 )
3941
3942          var_list = ';'
3943          i = 1
3944          DO  i = 1, dots_num
3945
3946             IF ( statistic_regions == 0 )  THEN
3947                var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // ';'
3948             ELSE
3949                DO  j = 0, statistic_regions
3950                   WRITE ( suffix, '(''_'',I1)' )  j
3951                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // &
3952                              suffix // ';'
3953                ENDDO
3954             ENDIF
3955
3956          ENDDO
3957
3958          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
3959             message_string = 'netCDF file for time series ' //              &
3960                              'from previous run found,' //                  &
3961                              '& but this file cannot be extended due to' // &
3962                              ' variable mismatch.' //                       &
3963                              '&New file is created instead.'
3964             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
3965             extend = .FALSE.
3966             RETURN
3967          ENDIF
3968
3969!
3970!--       Get the id of the time coordinate (unlimited coordinate) and its
3971!--       last index on the file. The next time level is dots..count+1.
3972!--       The current time must be larger than the last output time
3973!--       on the file.
3974          nc_stat = NF90_INQ_VARID( id_set_ts, 'time', id_var_time_ts )
3975          CALL handle_netcdf_error( 'netcdf', 261 )
3976
3977          nc_stat = NF90_INQUIRE_VARIABLE( id_set_ts, id_var_time_ts, &
3978                                           dimids = id_dim_time_old )
3979          CALL handle_netcdf_error( 'netcdf', 262 )
3980          id_dim_time_ts = id_dim_time_old(1)
3981
3982          nc_stat = NF90_INQUIRE_DIMENSION( id_set_ts, id_dim_time_ts, &
3983                                            len = dots_time_count )
3984          CALL handle_netcdf_error( 'netcdf', 263 )
3985
3986          nc_stat = NF90_GET_VAR( id_set_ts, id_var_time_ts,        &
3987                                  last_time_coordinate,             &
3988                                  start = (/ dots_time_count /), &
3989                                  count = (/ 1 /) )
3990          CALL handle_netcdf_error( 'netcdf', 264 )
3991
3992          IF ( last_time_coordinate(1) >= simulated_time )  THEN
3993             message_string = 'netCDF file for time series ' //             &
3994                              'from previous run found,' //                 &
3995                              '&but this file cannot be extended becaus' // &
3996                              'e the current output time' //                &
3997                              '&is less or equal than the last output t' // &
3998                              'ime on this file.' //                        &
3999                              '&New file is created instead.'
4000             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
4001             dots_time_count = 0
4002             extend = .FALSE.
4003             RETURN
4004          ENDIF
4005
4006!
4007!--       Dataset seems to be extendable.
4008!--       Now get the variable ids
4009          i = 1
4010          DO  i = 1, dots_num
4011 
4012             IF ( statistic_regions == 0 )  THEN
4013                nc_stat = NF90_INQ_VARID( id_set_ts, dots_label(i), &
4014                                          id_var_dots(i,0) )
4015                CALL handle_netcdf_error( 'netcdf', 265 )
4016             ELSE
4017                DO  j = 0, statistic_regions
4018                   WRITE ( suffix, '(''_'',I1)' )  j
4019                   netcdf_var_name = TRIM( dots_label(i) ) // suffix
4020                   nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, &
4021                                             id_var_dots(i,j) )
4022                   CALL handle_netcdf_error( 'netcdf', 266 )
4023                ENDDO
4024             ENDIF
4025
4026          ENDDO
4027
4028!
4029!--       Update the title attribute on file
4030!--       In order to avoid 'data mode' errors if updated attributes are larger
4031!--       than their original size, NF90_PUT_ATT is called in 'define mode'
4032!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
4033!--       performance loss due to data copying; an alternative strategy would be
4034!--       to ensure equal attribute size in a job chain. Maybe revise later.
4035          nc_stat = NF90_REDEF( id_set_ts )
4036          CALL handle_netcdf_error( 'netcdf', 439 )
4037          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', &
4038                                  TRIM( run_description_header ) )
4039          CALL handle_netcdf_error( 'netcdf', 267 )
4040          nc_stat = NF90_ENDDEF( id_set_ts )
4041          CALL handle_netcdf_error( 'netcdf', 440 )
4042          message_string = 'netCDF file for time series ' // &
4043                           'from previous run found.' //     &
4044                           '&This file will be extended.'
4045          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
4046
4047
4048       CASE ( 'sp_new' )
4049
4050!
4051!--       Define some global attributes of the dataset
4052          IF ( averaging_interval_sp /= 0.0 )  THEN
4053             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
4054                                                            averaging_interval_sp
4055             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',  &
4056                                     TRIM( run_description_header ) // &
4057                                     TRIM( time_average_text ) )
4058             CALL handle_netcdf_error( 'netcdf', 268 )
4059
4060             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
4061             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', &
4062                                     TRIM( time_average_text ) )
4063          ELSE
4064             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title', &
4065                                     TRIM( run_description_header ) )
4066          ENDIF
4067          CALL handle_netcdf_error( 'netcdf', 269 )
4068
4069!
4070!--       Define time coordinate for spectra (unlimited dimension)
4071          nc_stat = NF90_DEF_DIM( id_set_sp, 'time', NF90_UNLIMITED, &
4072                                  id_dim_time_sp )
4073          CALL handle_netcdf_error( 'netcdf', 270 )
4074
4075          nc_stat = NF90_DEF_VAR( id_set_sp, 'time', NF90_DOUBLE, &
4076                                  id_dim_time_sp, id_var_time_sp )
4077          CALL handle_netcdf_error( 'netcdf', 271 )
4078
4079          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_time_sp, 'units', 'seconds')
4080          CALL handle_netcdf_error( 'netcdf', 272 )
4081
4082!
4083!--       Define the spatial dimensions and coordinates for spectra.
4084!--       First, determine the number of vertical levels for which spectra
4085!--       are to be output.
4086          ns = 1
4087          DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
4088             ns = ns + 1
4089          ENDDO
4090          ns = ns - 1
4091
4092!
4093!--       Define vertical coordinate grid (zu grid)
4094          nc_stat = NF90_DEF_DIM( id_set_sp, 'zu_sp', ns, id_dim_zu_sp )
4095          CALL handle_netcdf_error( 'netcdf', 273 )
4096
4097          nc_stat = NF90_DEF_VAR( id_set_sp, 'zu_sp', NF90_DOUBLE, &
4098                                  id_dim_zu_sp, id_var_zu_sp )
4099          CALL handle_netcdf_error( 'netcdf', 274 )
4100
4101          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_zu_sp, 'units', 'meters' )
4102          CALL handle_netcdf_error( 'netcdf', 275 )
4103
4104!
4105!--       Define vertical coordinate grid (zw grid)
4106          nc_stat = NF90_DEF_DIM( id_set_sp, 'zw_sp', ns, id_dim_zw_sp )
4107          CALL handle_netcdf_error( 'netcdf', 276 )
4108
4109          nc_stat = NF90_DEF_VAR( id_set_sp, 'zw_sp', NF90_DOUBLE, &
4110                                  id_dim_zw_sp, id_var_zw_sp )
4111          CALL handle_netcdf_error( 'netcdf', 277 )
4112
4113          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_zw_sp, 'units', 'meters' )
4114          CALL handle_netcdf_error( 'netcdf', 278 )
4115
4116!
4117!--       Define x-axis
4118          nc_stat = NF90_DEF_DIM( id_set_sp, 'k_x', nx/2, id_dim_x_sp )
4119          CALL handle_netcdf_error( 'netcdf', 279 )
4120
4121          nc_stat = NF90_DEF_VAR( id_set_sp, 'k_x', NF90_DOUBLE, id_dim_x_sp, &
4122                                  id_var_x_sp )
4123          CALL handle_netcdf_error( 'netcdf', 280 )
4124
4125          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_x_sp, 'units', 'm-1' )
4126          CALL handle_netcdf_error( 'netcdf', 281 )
4127
4128!
4129!--       Define y-axis
4130          nc_stat = NF90_DEF_DIM( id_set_sp, 'k_y', ny/2, id_dim_y_sp )
4131          CALL handle_netcdf_error( 'netcdf', 282 )
4132
4133          nc_stat = NF90_DEF_VAR( id_set_sp, 'k_y', NF90_DOUBLE, id_dim_y_sp, &
4134                                  id_var_y_sp )
4135          CALL handle_netcdf_error( 'netcdf', 283 )
4136
4137          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_y_sp, 'units', 'm-1' )
4138          CALL handle_netcdf_error( 'netcdf', 284 )
4139
4140!
4141!--       Define the variables
4142          var_list = ';'
4143          i = 1
4144          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
4145!
4146!--          First check for the vertical grid
4147             found = .TRUE.
4148             SELECT CASE ( data_output_sp(i) )
4149!
4150!--             Most variables are defined on the zu levels
4151                CASE ( 'e', 'lpt', 'nr', 'p', 'pc', 'pr', 'prr', 'pt', 'q',   &
4152                       'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv', 'rho',&
4153                       's', 'sa', 'u', 'v', 'vpt' )
4154
4155                   grid_z = 'zu'
4156!
4157!--             zw levels
4158                CASE ( 'w' )
4159
4160                   grid_z = 'zw'
4161
4162                CASE DEFAULT
4163!
4164!--                Check for user-defined quantities (found, grid_x and grid_y
4165!--                are dummies)
4166                   CALL user_define_netcdf_grid( data_output_sp(i), found,  &
4167                                                 grid_x, grid_y, grid_z )
4168
4169             END SELECT
4170
4171             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
4172
4173!
4174!--             Define the variable
4175                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
4176                IF ( TRIM( grid_z ) == 'zw' )  THEN
4177                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
4178                                           nc_precision(7), (/ id_dim_x_sp, &
4179                                           id_dim_zw_sp, id_dim_time_sp /), &
4180                                           id_var_dospx(i) )
4181                ELSE
4182                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
4183                                           nc_precision(7), (/ id_dim_x_sp, &
4184                                           id_dim_zu_sp, id_dim_time_sp /), &
4185                                           id_var_dospx(i) )
4186                ENDIF
4187                CALL handle_netcdf_error( 'netcdf', 285 )
4188
4189                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospx(i), &
4190                                        'long_name', netcdf_var_name )
4191                CALL handle_netcdf_error( 'netcdf', 286 )
4192
4193                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospx(i), &
4194                                        'units', 'unknown' )
4195                CALL handle_netcdf_error( 'netcdf', 287 )
4196
4197                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
4198
4199             ENDIF
4200
4201             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
4202
4203!
4204!--             Define the variable
4205                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
4206                IF ( TRIM( grid_z ) == 'zw' )  THEN
4207                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
4208                                           nc_precision(7), (/ id_dim_y_sp, &
4209                                           id_dim_zw_sp, id_dim_time_sp /), &
4210                                           id_var_dospy(i) )
4211                ELSE
4212                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
4213                                           nc_precision(7), (/ id_dim_y_sp, &
4214                                           id_dim_zu_sp, id_dim_time_sp /), &
4215                                           id_var_dospy(i) )
4216                ENDIF
4217                CALL handle_netcdf_error( 'netcdf', 288 )
4218
4219                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospy(i), &
4220                                        'long_name', netcdf_var_name )
4221                CALL handle_netcdf_error( 'netcdf', 289 )
4222
4223                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospy(i), &
4224                                        'units', 'unknown' )
4225                CALL handle_netcdf_error( 'netcdf', 290 )
4226
4227                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
4228
4229             ENDIF
4230
4231             i = i + 1
4232
4233          ENDDO
4234
4235!
4236!--       Write the list of variables as global attribute (this is used by
4237!--       restart runs)
4238          nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', var_list )
4239          CALL handle_netcdf_error( 'netcdf', 291 )
4240
4241!
4242!--       Leave netCDF define mode
4243          nc_stat = NF90_ENDDEF( id_set_sp )
4244          CALL handle_netcdf_error( 'netcdf', 292 )
4245
4246!
4247!--       Write axis data: zu_sp, zw_sp, k_x, k_y
4248          ALLOCATE( netcdf_data(1:ns) )
4249
4250!
4251!--       Write zu data
4252          netcdf_data(1:ns) = zu( comp_spectra_level(1:ns) )
4253          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zu_sp, netcdf_data, &
4254                                  start = (/ 1 /), count = (/ ns /) )
4255          CALL handle_netcdf_error( 'netcdf', 293 )
4256
4257!
4258!--       Write zw data
4259          netcdf_data(1:ns) = zw( comp_spectra_level(1:ns) )
4260          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zw_sp, netcdf_data, &
4261                                  start = (/ 1 /), count = (/ ns /) )
4262          CALL handle_netcdf_error( 'netcdf', 294 )
4263
4264          DEALLOCATE( netcdf_data )
4265
4266!
4267!--       Write data for x and y axis (wavenumbers)
4268          ALLOCATE( netcdf_data(nx/2) )
4269          DO  i = 1, nx/2
4270             netcdf_data(i) = 2.0 * pi * i / ( dx * ( nx + 1 ) )
4271          ENDDO
4272
4273          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_x_sp, netcdf_data, &
4274                                  start = (/ 1 /), count = (/ nx/2 /) )
4275          CALL handle_netcdf_error( 'netcdf', 295 )
4276
4277          DEALLOCATE( netcdf_data )
4278
4279          ALLOCATE( netcdf_data(ny/2) )
4280          DO  i = 1, ny/2
4281             netcdf_data(i) = 2.0 * pi * i / ( dy * ( ny + 1 ) )
4282          ENDDO
4283
4284          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_y_sp, netcdf_data, &
4285                                  start = (/ 1 /), count = (/ ny/2 /) )
4286          CALL handle_netcdf_error( 'netcdf', 296 )
4287
4288          DEALLOCATE( netcdf_data )
4289
4290
4291       CASE ( 'sp_ext' )
4292
4293!
4294!--       Get the list of variables and compare with the actual run.
4295!--       First var_list_old has to be reset, since GET_ATT does not assign
4296!--       trailing blanks.
4297          var_list_old = ' '
4298          nc_stat = NF90_GET_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', &
4299                                  var_list_old )
4300          CALL handle_netcdf_error( 'netcdf', 297 )
4301          var_list = ';'
4302          i = 1
4303          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
4304
4305             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
4306                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
4307                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
4308             ENDIF
4309
4310             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
4311                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
4312                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
4313             ENDIF
4314
4315             i = i + 1
4316
4317          ENDDO
4318
4319          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
4320             message_string = 'netCDF file for spectra  ' //                 &
4321                              'from previous run found,' //                  &
4322                              '& but this file cannot be extended due to' // &
4323                              ' variable mismatch.' //                       &
4324                              '&New file is created instead.'
4325             CALL message( 'define_netcdf_header', 'PA0260', 0, 1, 0, 6, 0 )
4326             extend = .FALSE.
4327             RETURN
4328          ENDIF
4329
4330!
4331!--       Determine the number of current vertical levels for which spectra
4332!--       shall be output
4333          ns = 1
4334          DO WHILE ( comp_spectra_level(ns) /= 999999  .AND.  ns <= 100 )
4335             ns = ns + 1
4336          ENDDO
4337          ns = ns - 1
4338
4339!
4340!--       Get and compare the number of vertical levels
4341          nc_stat = NF90_INQ_VARID( id_set_sp, 'zu_sp', id_var_zu_sp )
4342          CALL handle_netcdf_error( 'netcdf', 298 )
4343
4344          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_zu_sp, &
4345                                           dimids = id_dim_zu_sp_old )
4346          CALL handle_netcdf_error( 'netcdf', 299 )
4347          id_dim_zu_sp = id_dim_zu_sp_old(1)
4348
4349          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_zu_sp, &
4350                                            len = ns_old )
4351          CALL handle_netcdf_error( 'netcdf', 300 )
4352
4353          IF ( ns /= ns_old )  THEN
4354             message_string = 'netCDF file for spectra ' //                 &
4355                              ' from previous run found,' //                &
4356                              '&but this file cannot be extended due to' // &
4357                              ' mismatch in number of' //                   &
4358                              '&vertical levels.' //                        &
4359                              '&New file is created instead.'
4360             CALL message( 'define_netcdf_header', 'PA0261', 0, 1, 0, 6, 0 )
4361             extend = .FALSE.
4362             RETURN
4363          ENDIF
4364
4365!
4366!--       Get and compare the heights of the cross sections
4367          ALLOCATE( netcdf_data(1:ns_old) )
4368
4369          nc_stat = NF90_GET_VAR( id_set_sp, id_var_zu_sp, netcdf_data )
4370          CALL handle_netcdf_error( 'netcdf', 301 )
4371
4372          DO  i = 1, ns
4373             IF ( zu(comp_spectra_level(i)) /= netcdf_data(i) )  THEN
4374                message_string = 'netCDF file for spectra ' //                 &
4375                                 ' from previous run found,' //                &
4376                                 '&but this file cannot be extended due to' // &
4377                                 ' mismatch in heights of' //                  &
4378                                 '&vertical levels.' //                        &
4379                                 '&New file is created instead.'
4380                CALL message( 'define_netcdf_header', 'PA0262', 0, 1, 0, 6, 0 )
4381                extend = .FALSE.
4382                RETURN
4383             ENDIF
4384          ENDDO
4385
4386          DEALLOCATE( netcdf_data )
4387
4388!
4389!--       Get the id of the time coordinate (unlimited coordinate) and its
4390!--       last index on the file. The next time level is plsp..count+1.
4391!--       The current time must be larger than the last output time
4392!--       on the file.
4393          nc_stat = NF90_INQ_VARID( id_set_sp, 'time', id_var_time_sp )
4394          CALL handle_netcdf_error( 'netcdf', 302 )
4395
4396          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_time_sp, &
4397                                           dimids = id_dim_time_old )
4398          CALL handle_netcdf_error( 'netcdf', 303 )
4399          id_dim_time_sp = id_dim_time_old(1)
4400
4401          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_time_sp, &
4402                                            len = dosp_time_count )
4403          CALL handle_netcdf_error( 'netcdf', 304 )
4404
4405          nc_stat = NF90_GET_VAR( id_set_sp, id_var_time_sp,        &
4406                                  last_time_coordinate,             &
4407                                  start = (/ dosp_time_count /), &
4408                                  count = (/ 1 /) )
4409          CALL handle_netcdf_error( 'netcdf', 305 )
4410
4411          IF ( last_time_coordinate(1) >= simulated_time )  THEN
4412             message_string = 'netCDF file for spectra ' //                 &
4413                              'from previous run found,' //                 &
4414                              '&but this file cannot be extended becaus' // &
4415                              'e the current output time' //                & 
4416                              '&is less or equal than the last output t' // &
4417                              'ime on this file.' //                        &
4418                              '&New file is created instead.'
4419             CALL message( 'define_netcdf_header', 'PA0263', 0, 1, 0, 6, 0 )
4420             dosp_time_count = 0
4421             extend = .FALSE.
4422             RETURN
4423          ENDIF
4424
4425!
4426!--       Dataset seems to be extendable.
4427!--       Now get the variable ids.
4428          i = 1
4429          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
4430
4431             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
4432                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
4433                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
4434                                          id_var_dospx(i) )
4435                CALL handle_netcdf_error( 'netcdf', 306 )
4436             ENDIF
4437
4438             IF ( INDEX( spectra_direction(i), 'y' ) /= 0 )  THEN
4439                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
4440                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
4441                                          id_var_dospy(i) )
4442                CALL handle_netcdf_error( 'netcdf', 307 )
4443             ENDIF
4444
4445             i = i + 1
4446
4447          ENDDO
4448
4449!
4450!--       Update the title attribute on file
4451!--       In order to avoid 'data mode' errors if updated attributes are larger
4452!--       than their original size, NF90_PUT_ATT is called in 'define mode'
4453!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
4454!--       performance loss due to data copying; an alternative strategy would be
4455!--       to ensure equal attribute size in a job chain. Maybe revise later.
4456          nc_stat = NF90_REDEF( id_set_sp )
4457          CALL handle_netcdf_error( 'netcdf', 441 )
4458          IF ( averaging_interval_sp /= 0.0 )  THEN
4459             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
4460                                                           averaging_interval_sp
4461             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title',  &
4462                                     TRIM( run_description_header ) // &
4463                                     TRIM( time_average_text ) )
4464             CALL handle_netcdf_error( 'netcdf', 308 )
4465
4466             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
4467             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'time_avg', &
4468                                     TRIM( time_average_text ) )
4469          ELSE
4470             nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'title', &
4471                                     TRIM( run_description_header ) )
4472          ENDIF
4473          CALL handle_netcdf_error( 'netcdf', 309 )
4474          nc_stat = NF90_ENDDEF( id_set_sp )
4475          CALL handle_netcdf_error( 'netcdf', 442 )
4476          message_string = 'netCDF file for spectra ' //     &
4477                           'from previous run found.' //     &
4478                           '&This file will be extended.'
4479          CALL message( 'define_netcdf_header', 'PA0264', 0, 0, 0, 6, 0 )
4480
4481
4482       CASE ( 'pt_new' )
4483
4484!
4485!--       Define some global attributes of the dataset
4486          nc_stat = NF90_PUT_ATT( id_set_prt, NF90_GLOBAL, 'title', &
4487                                  TRIM( run_description_header ) )
4488          CALL handle_netcdf_error( 'netcdf', 310 )
4489
4490!
4491!--       Define time coordinate for particles (unlimited dimension)
4492          nc_stat = NF90_DEF_DIM( id_set_prt, 'time', NF90_UNLIMITED, &
4493                                  id_dim_time_prt )
4494          CALL handle_netcdf_error( 'netcdf', 311 )
4495
4496          nc_stat = NF90_DEF_VAR( id_set_prt, 'time', NF90_DOUBLE, &
4497                                  id_dim_time_prt, id_var_time_prt )
4498          CALL handle_netcdf_error( 'netcdf', 312 )
4499
4500          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_time_prt, 'units', &
4501                                  'seconds' )
4502          CALL handle_netcdf_error( 'netcdf', 313 )
4503
4504!
4505!--       Define particle coordinate (maximum particle number)
4506          IF ( netcdf_data_format < 3 )  THEN
4507             nc_stat = NF90_DEF_DIM( id_set_prt, 'particle_number', &
4508                                     maximum_number_of_particles, id_dim_prtnum)
4509          ELSE
4510!
4511!--          netCDF4 allows more than one unlimited dimension
4512             nc_stat = NF90_DEF_DIM( id_set_prt, 'particle_number', &
4513                                     NF90_UNLIMITED, id_dim_prtnum)
4514          ENDIF
4515          CALL handle_netcdf_error( 'netcdf', 314 )
4516
4517          nc_stat = NF90_DEF_VAR( id_set_prt, 'particle_number', NF90_DOUBLE, &
4518                                  id_dim_prtnum, id_var_prtnum )
4519          CALL handle_netcdf_error( 'netcdf', 315 )
4520
4521          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prtnum, 'units', &
4522                                  'particle number' )
4523          CALL handle_netcdf_error( 'netcdf', 316 )
4524
4525!
4526!--       Define variable which contains the real number of particles in use
4527          nc_stat = NF90_DEF_VAR( id_set_prt, 'real_num_of_prt', NF90_INT, &
4528                                  id_dim_time_prt, id_var_rnop_prt )
4529          CALL handle_netcdf_error( 'netcdf', 317 )
4530
4531          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_rnop_prt, 'units', &
4532                                  'particle number' )
4533          CALL handle_netcdf_error( 'netcdf', 318 )
4534
4535!
4536!--       Define the variables
4537          DO  i = 1, 17
4538
4539             nc_stat = NF90_DEF_VAR( id_set_prt, prt_var_names(i),         &
4540                                     nc_precision(8),                      &
4541                                     (/ id_dim_prtnum, id_dim_time_prt /), &
4542                                     id_var_prt(i) )
4543             CALL handle_netcdf_error( 'netcdf', 319 )
4544
4545             nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prt(i), &
4546                                     'long_name', TRIM( prt_var_names(i) ) )
4547             CALL handle_netcdf_error( 'netcdf', 320 )
4548
4549             nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prt(i), &
4550                                     'units', TRIM( prt_var_units(i) ) )
4551             CALL handle_netcdf_error( 'netcdf', 321 )
4552
4553          ENDDO
4554
4555!
4556!--       Leave netCDF define mode
4557          nc_stat = NF90_ENDDEF( id_set_prt )
4558          CALL handle_netcdf_error( 'netcdf', 322 )
4559
4560
4561       CASE ( 'pt_ext' )
4562
4563!
4564!--       Get the id of the time coordinate (unlimited coordinate) and its
4565!--       last index on the file. The next time level is prt..count+1.
4566!--       The current time must be larger than the last output time
4567!--       on the file.
4568          nc_stat = NF90_INQ_VARID( id_set_prt, 'time', id_var_time_prt )
4569          CALL handle_netcdf_error( 'netcdf', 323 )
4570
4571          nc_stat = NF90_INQUIRE_VARIABLE( id_set_prt, id_var_time_prt, &
4572                                           dimids = id_dim_time_old )
4573          CALL handle_netcdf_error( 'netcdf', 324 )
4574          id_dim_time_prt = id_dim_time_old(1)
4575
4576          nc_stat = NF90_INQUIRE_DIMENSION( id_set_prt, id_dim_time_prt, &
4577                                            len = prt_time_count )
4578          CALL handle_netcdf_error( 'netcdf', 325 )
4579
4580          nc_stat = NF90_GET_VAR( id_set_prt, id_var_time_prt,  &
4581                                  last_time_coordinate,         &
4582                                  start = (/ prt_time_count /), &
4583                                  count = (/ 1 /) )
4584          CALL handle_netcdf_error( 'netcdf', 326 )
4585
4586          IF ( last_time_coordinate(1) >= simulated_time )  THEN
4587             message_string = 'netCDF file for particles ' //               &
4588                              'from previous run found,' //                 &
4589                              '&but this file cannot be extended becaus' // &
4590                              'e the current output time' //                &
4591                              '&is less or equal than the last output t' // &
4592                              'ime on this file.' //                        &
4593                              '&New file is created instead.'
4594             CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
4595             prt_time_count = 0
4596             extend = .FALSE.
4597             RETURN
4598          ENDIF
4599
4600!
4601!--       Dataset seems to be extendable.
4602!--       Now get the variable ids.
4603          nc_stat = NF90_INQ_VARID( id_set_prt, 'real_num_of_prt', &
4604                                    id_var_rnop_prt )
4605          CALL handle_netcdf_error( 'netcdf', 327 )
4606
4607          DO  i = 1, 17
4608
4609             nc_stat = NF90_INQ_VARID( id_set_prt, prt_var_names(i), &
4610                                       id_var_prt(i) )
4611             CALL handle_netcdf_error( 'netcdf', 328 )
4612
4613          ENDDO
4614
4615          message_string = 'netCDF file for particles ' // &
4616                           'from previous run found.' //   &
4617                           '&This file will be extended.'
4618          CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
4619       
4620
4621
4622       CASE ( 'ps_new' )
4623
4624!
4625!--       Define some global attributes of the dataset
4626          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', &
4627                                  TRIM( run_description_header ) )
4628          CALL handle_netcdf_error( 'netcdf', 396 )
4629
4630!
4631!--       Define time coordinate for particle time series (unlimited dimension)
4632          nc_stat = NF90_DEF_DIM( id_set_pts, 'time', NF90_UNLIMITED, &
4633                                  id_dim_time_pts )
4634          CALL handle_netcdf_error( 'netcdf', 397 )
4635
4636          nc_stat = NF90_DEF_VAR( id_set_pts, 'time', NF90_DOUBLE, &
4637                                  id_dim_time_pts, id_var_time_pts )
4638          CALL handle_netcdf_error( 'netcdf', 398 )
4639
4640          nc_stat = NF90_PUT_ATT( id_set_pts, id_var_time_pts, 'units', &
4641                                  'seconds')
4642          CALL handle_netcdf_error( 'netcdf', 399 )
4643
4644!
4645!--       Define the variables. If more than one particle group is defined,
4646!--       define seperate variables for each group
4647          var_list = ';'
4648          DO  i = 1, dopts_num
4649
4650             DO  j = 0, number_of_particle_groups
4651
4652                IF ( j == 0 )  THEN
4653                   suffix1 = ''
4654                ELSE
4655                   WRITE ( suffix1, '(''_'',I2.2)' )  j
4656                ENDIF
4657
4658                nc_stat = NF90_DEF_VAR( id_set_pts,                         &
4659                                        TRIM( dopts_label(i) ) // suffix1,  &
4660                                        nc_precision(6),                    &
4661                                        (/ id_dim_time_pts /),              &
4662                                        id_var_dopts(i,j) )
4663                CALL handle_netcdf_error( 'netcdf', 400 )
4664
4665                IF ( j == 0 )  THEN
4666                   nc_stat = NF90_PUT_ATT( id_set_pts, id_var_dopts(i,j), &
4667                                           'long_name', &
4668                                           TRIM( dopts_label(i) ) )
4669                ELSE
4670                   nc_stat = NF90_PUT_ATT( id_set_pts, id_var_dopts(i,j), &
4671                                           'long_name', &
4672                                           TRIM( dopts_label(i) ) // ' PG ' // &
4673                                           suffix1(2:3) )
4674                ENDIF
4675                CALL handle_netcdf_error( 'netcdf', 401 )
4676
4677                nc_stat = NF90_PUT_ATT( id_set_pts, id_var_dopts(i,j), &
4678                                        'units', TRIM( dopts_unit(i) ) )
4679                CALL handle_netcdf_error( 'netcdf', 402 )
4680
4681                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
4682                           suffix1 // ';'
4683
4684                IF ( number_of_particle_groups == 1 )  EXIT
4685
4686             ENDDO
4687
4688          ENDDO
4689
4690!
4691!--       Write the list of variables as global attribute (this is used by
4692!--       restart runs)
4693          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
4694                                  var_list )
4695          CALL handle_netcdf_error( 'netcdf', 403 )
4696
4697
4698!
4699!--       Leave netCDF define mode
4700          nc_stat = NF90_ENDDEF( id_set_pts )
4701          CALL handle_netcdf_error( 'netcdf', 404 )
4702
4703
4704       CASE ( 'ps_ext' )
4705
4706!
4707!--       Get the list of variables and compare with the actual run.
4708!--       First var_list_old has to be reset, since GET_ATT does not assign
4709!--       trailing blanks.
4710          var_list_old = ' '
4711          nc_stat = NF90_GET_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
4712                                  var_list_old )
4713          CALL handle_netcdf_error( 'netcdf', 405 )
4714
4715          var_list = ';'
4716          i = 1
4717          DO  i = 1, dopts_num
4718
4719             DO  j = 0, number_of_particle_groups
4720
4721                IF ( j == 0 )  THEN
4722                   suffix1 = ''
4723                ELSE
4724                   WRITE ( suffix1, '(''_'',I2.2)' )  j
4725                ENDIF
4726
4727                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
4728                           suffix1 // ';'
4729
4730                IF ( number_of_particle_groups == 1 )  EXIT
4731
4732             ENDDO
4733
4734          ENDDO
4735
4736          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
4737             message_string = 'netCDF file for particle time series ' //     &
4738                              'from previous run found,' //                  &
4739                              '& but this file cannot be extended due to' // &
4740                              ' variable mismatch.' //                       &
4741                              '&New file is created instead.'
4742             CALL message( 'define_netcdf_header', 'PA0267', 0, 1, 0, 6, 0 )
4743             extend = .FALSE.
4744             RETURN
4745          ENDIF
4746
4747!
4748!--       Get the id of the time coordinate (unlimited coordinate) and its
4749!--       last index on the file. The next time level is dots..count+1.
4750!--       The current time must be larger than the last output time
4751!--       on the file.
4752          nc_stat = NF90_INQ_VARID( id_set_pts, 'time', id_var_time_pts )
4753          CALL handle_netcdf_error( 'netcdf', 406 )
4754
4755          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pts, id_var_time_pts, &
4756                                           dimids = id_dim_time_old )
4757          CALL handle_netcdf_error( 'netcdf', 407 )
4758          id_dim_time_pts = id_dim_time_old(1)
4759
4760          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pts, id_dim_time_pts, &
4761                                            len = dopts_time_count )
4762          CALL handle_netcdf_error( 'netcdf', 408 )
4763
4764          nc_stat = NF90_GET_VAR( id_set_pts, id_var_time_pts,    &
4765                                  last_time_coordinate,           &
4766                                  start = (/ dopts_time_count /), &
4767                                  count = (/ 1 /) )
4768          CALL handle_netcdf_error( 'netcdf', 409 )
4769
4770          IF ( last_time_coordinate(1) >= simulated_time )  THEN
4771             message_string = 'netCDF file for particle time series ' //    &
4772                              'from previous run found,' //                 &
4773                              '&but this file cannot be extended becaus' // &
4774                              'e the current output time' //                &
4775                              '&is less or equal than the last output t' // &
4776                              'ime on this file.' //                        &
4777                              '&New file is created instead.'
4778             CALL message( 'define_netcdf_header', 'PA0268', 0, 1, 0, 6, 0 )
4779             dopts_time_count = 0
4780             extend = .FALSE.
4781             RETURN
4782          ENDIF
4783
4784!
4785!--       Dataset seems to be extendable.
4786!--       Now get the variable ids
4787          i = 1
4788          DO  i = 1, dopts_num
4789 
4790             DO  j = 0, number_of_particle_groups
4791
4792                IF ( j == 0 )  THEN
4793                   suffix1 = ''
4794                ELSE
4795                   WRITE ( suffix1, '(''_'',I2.2)' )  j
4796                ENDIF
4797
4798                netcdf_var_name = TRIM( dopts_label(i) ) // suffix1
4799
4800                nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, &
4801                                          id_var_dopts(i,j) )
4802                CALL handle_netcdf_error( 'netcdf', 410 )
4803
4804                IF ( number_of_particle_groups == 1 )  EXIT
4805
4806             ENDDO
4807
4808          ENDDO
4809
4810!
4811!--       Update the title attribute on file
4812!--       In order to avoid 'data mode' errors if updated attributes are larger
4813!--       than their original size, NF90_PUT_ATT is called in 'define mode'
4814!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
4815!--       performance loss due to data copying; an alternative strategy would be
4816!--       to ensure equal attribute size in a job chain. Maybe revise later.
4817          nc_stat = NF90_REDEF( id_set_pts )
4818          CALL handle_netcdf_error( 'netcdf', 443 )
4819          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', &
4820                                  TRIM( run_description_header ) )
4821          CALL handle_netcdf_error( 'netcdf', 411 )
4822          nc_stat = NF90_ENDDEF( id_set_pts )
4823          CALL handle_netcdf_error( 'netcdf', 444 )
4824          message_string = 'netCDF file for particle time series ' // &
4825                           'from previous run found.' //              &
4826                           '&This file will be extended.'
4827          CALL message( 'define_netcdf_header', 'PA0269', 0, 0, 0, 6, 0 )
4828
4829
4830       CASE DEFAULT
4831
4832          message_string = 'mode "' // TRIM( mode) // '" not supported'
4833          CALL message( 'define_netcdf_header', 'PA0270', 0, 0, 0, 6, 0 )
4834
4835    END SELECT
4836
4837#endif
4838 END SUBROUTINE define_netcdf_header
4839
4840
4841 SUBROUTINE create_netcdf_file( filename , id, parallel, errno )
4842#if defined( __netcdf )
4843
4844!------------------------------------------------------------------------------!
4845! Description:
4846! ------------
4847! Creates a netCDF file and give back the id. The parallel flag has to be TRUE
4848! for parallel netCDF output support.
4849!------------------------------------------------------------------------------!
4850
4851    USE control_parameters
4852    USE netcdf
4853    USE netcdf_control
4854    USE pegrid
4855
4856    IMPLICIT NONE
4857
4858    CHARACTER (LEN=*), INTENT(IN) :: filename
4859    INTEGER, INTENT(IN)           :: errno
4860    INTEGER, INTENT(OUT)          :: id
4861    LOGICAL, INTENT(IN)           :: parallel
4862
4863
4864!
4865!-- Create a new netCDF output file with requested netCDF format
4866    IF ( netcdf_data_format == 1 )  THEN
4867!
4868!-- Classic netCDF format
4869    nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id )
4870
4871    ELSEIF ( netcdf_data_format == 2 )  THEN
4872!
4873!--    64bit-offset format
4874       nc_stat = NF90_CREATE( filename,                                        &
4875                              IOR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ), id )
4876
4877#if defined( __netcdf4 )
4878    ELSEIF ( netcdf_data_format == 3  .OR.                                     &
4879             ( .NOT. parallel  .AND.  netcdf_data_format == 5 ) )  THEN
4880!
4881!--    netCDF4/HDF5 format
4882       nc_stat = NF90_CREATE( filename, IOR( NF90_NOCLOBBER, NF90_NETCDF4 ), id )
4883
4884    ELSEIF ( netcdf_data_format == 4  .OR.                                     &
4885             ( .NOT. parallel  .AND.  netcdf_data_format == 6 ) )  THEN
4886!
4887!--    netCDF4/HDF5 format with classic model flag
4888       nc_stat = NF90_CREATE( filename,                                        &
4889                              IOR( NF90_NOCLOBBER,                              &
4890                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), id )
4891
4892#if defined( __netcdf4_parallel )
4893    ELSEIF ( netcdf_data_format == 5  .AND.  parallel )  THEN
4894!
4895!--    netCDF4/HDF5 format, parallel
4896       nc_stat = NF90_CREATE( filename,                                        &
4897                              IOR( NF90_NOCLOBBER,                              &
4898                              IOR( NF90_NETCDF4, NF90_MPIIO ) ),                &
4899                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
4900
4901    ELSEIF ( netcdf_data_format == 6  .AND.  parallel )  THEN
4902!
4903!--    netCDF4/HDF5 format with classic model flag, parallel
4904       nc_stat = NF90_CREATE( filename,                                        &
4905                              IOR( NF90_NOCLOBBER,                              &
4906                              IOR( NF90_MPIIO,                                  &
4907                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),         &
4908                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
4909
4910#endif
4911#endif
4912    ENDIF
4913
4914    CALL handle_netcdf_error( 'create_netcdf_file', errno )
4915#endif
4916 END SUBROUTINE create_netcdf_file
4917
4918
4919 SUBROUTINE open_write_netcdf_file( filename, id, parallel, errno )
4920#if defined( __netcdf )
4921
4922!------------------------------------------------------------------------------!
4923! Description:
4924! ------------
4925! Opens an existing netCDF file for writing and gives back the id.
4926! The parallel flag has to be TRUE for parallel netCDF output support.
4927!------------------------------------------------------------------------------!
4928
4929    USE control_parameters,                                                    &
4930        ONLY:  netcdf_data_format
4931
4932    USE netcdf
4933
4934    USE netcdf_control
4935
4936    USE pegrid
4937
4938    IMPLICIT NONE
4939
4940    CHARACTER (LEN=*), INTENT(IN) :: filename
4941    INTEGER, INTENT(IN)           :: errno
4942    INTEGER, INTENT(OUT)          :: id
4943    LOGICAL, INTENT(IN)           :: parallel
4944
4945
4946    IF ( netcdf_data_format < 5  .OR.  .NOT. parallel )  THEN
4947       nc_stat = NF90_OPEN( filename, NF90_WRITE, id )
4948#if defined( __netcdf4 )
4949#if defined( __netcdf4_parallel )
4950    ELSEIF ( netcdf_data_format > 4  .AND.  parallel )  THEN
4951       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id,  &
4952                            COMM = comm2d, INFO = MPI_INFO_NULL )
4953#endif
4954#endif
4955    ENDIF
4956
4957    CALL handle_netcdf_error( 'open_write_netcdf_file', errno )
4958#endif
4959 END SUBROUTINE open_write_netcdf_file
4960
4961
4962 SUBROUTINE handle_netcdf_error( routine_name, errno )
4963#if defined( __netcdf )
4964
4965!------------------------------------------------------------------------------!
4966! Description:
4967! ------------
4968! Prints out a text message corresponding to the current status.
4969!------------------------------------------------------------------------------!
4970
4971    USE control_parameters,                                                    &
4972        ONLY:  message_string
4973
4974    USE netcdf
4975
4976    USE netcdf_control
4977
4978    USE pegrid
4979
4980    IMPLICIT NONE
4981
4982    CHARACTER(LEN=6) ::  message_identifier
4983    CHARACTER(LEN=*) ::  routine_name
4984
4985    INTEGER(iwp) ::  errno
4986
4987    IF ( nc_stat /= NF90_NOERR )  THEN
4988
4989       WRITE( message_identifier, '(''NC'',I4.4)' )  errno
4990       message_string = TRIM( NF90_STRERROR( nc_stat ) )
4991
4992       CALL message( routine_name, message_identifier, 2, 2, 0, 6, 1 )
4993
4994    ENDIF
4995
4996#endif
4997 END SUBROUTINE handle_netcdf_error
Note: See TracBrowser for help on using the repository browser.