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

Last change on this file since 257 was 257, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine

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