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

Last change on this file since 600 was 600, checked in by raasch, 14 years ago

New:
---

Changed:


Parameters moved from d3par to inipar: call_psolver_at_all_substeps,
cfl_factor, cycle_mg, mg_cycles,mg_switch_to_pe0_level, ngsrb, nsor,
omega_sor, prandtl_number, psolver, rayleigh_damping_factor,
rayleigh_damping_height, residual_limit (parin, read_var_list, write_var_list)

Due to this change, in routine skip_var_list (end of file read_var_list.f90),
variable ldum is replaced by cdum(LEN=1), because otherwise read errors (too
few data on file) would appear due to one of the additional parameters
(cycle_mg, which is a string of one single character) which are now stored
on the restart file.

Weblink to error message database changed to new trac server (message)

Errors:


Bugfix concerning check of cross-section levels on netcdf-files to be
extended (xz,yz) (netcdf)

Bugfix in opening of cross section netcdf-files (parallel opening with
netcdf4 only works for netcdf_data_format > 2) (check_open)

Default values of surface_scalarflux and surface_waterflux changed from 0.0
to 9999999.9. Giving the parameter the default values means, that the
respective surface fluxes are calculated by the MO-relations, so the old default
value did not allow to set the surface fluxes to zero explicitly.

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