source: palm/trunk/SOURCE/check_open.f90 @ 3704

Last change on this file since 3704 was 3704, checked in by suehring, 5 years ago

Revision of virtual-measurement module and data output enabled. Further, post-processing tool added to merge distributed virtually sampled data and to output it into NetCDF files.

  • Property svn:keywords set to Id
File size: 45.0 KB
Line 
1!> @file check_open.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! Open binary files for virtual measurements
23!
24! Former revisions:
25! -----------------
26! $Id: check_open.f90 3704 2019-01-29 19:51:41Z suehring $
27! Open files for surface data
28!
29! 3399 2018-10-22 20:13:45Z gronemeier
30! unused variables and format statements removed
31!
32! 3159 2018-07-20 11:20:01Z sward
33! Added multi agent system
34!
35! 3045 2018-05-28 07:55:41Z Giersch
36! Output case 108 disabled
37!
38! 2964 2018-04-12 16:04:03Z Giersch
39! Error message moved to radiation_model_mod
40!
41! 2957 2018-04-11 08:48:06Z Giersch
42! Error message has been corrected in case of writing sky view factors
43!
44! 2906 2018-03-19 08:56:40Z Giersch
45! CASE 88 and 89 has been added for the input/output of sky view factors
46!
47! 2718 2018-01-02 08:49:38Z maronga
48! Corrected "Former revisions" section
49!
50! 2696 2017-12-14 17:12:51Z kanani
51! Change in file header (GPL part)
52!
53! 2669 2017-12-06 16:03:27Z raasch
54! file name extension for masked data files is changed to "_M##" and is now
55! appended at the end of the filename,
56! file ids not used any more have been removed
57!
58! 2516 2017-10-04 11:03:04Z suehring
59! Remove tabs
60!
61! 2514 2017-10-04 09:52:37Z suehring
62! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
63! no output of ghost layer data
64! iso2d-related parts removed
65!
66! 2300 2017-06-29 13:31:14Z raasch
67! -host
68!
69! 2298 2017-06-29 09:28:18Z raasch
70! -return_addres, return_username, avs_coor_file_..., avs_data_file_...,
71! cross_ts_numbers, cross_ts_number_count
72!
73! 2101 2017-01-05 16:42:31Z suehring
74!
75! 2063 2016-11-10 17:14:35Z raasch
76! bugfix: opening of PROGRESS file moved out of the NetCDF block
77!
78! 2040 2016-10-26 16:58:09Z gronemeier
79! Removed open of file 'PLOTTS_DATA' ( CASE(50:59) ) as it is no longer needed
80!
81! 2000 2016-08-20 18:09:15Z knoop
82! Forced header and separation lines into 80 columns
83!
84! 1988 2016-08-10 14:49:06Z gronemeier
85! informative message added if files cannot be opened in newly created directory
86!
87! 1986 2016-08-10 14:07:17Z gronemeier
88! Bugfix: check if output can be opened in newly created directory. If not
89! wait one second and try again.
90!
91! 1974 2016-07-26 08:43:25Z gronemeier
92! Bugfix: MPI barriers after deleting non-extendable files must only be called
93! in case of parallel I/O
94!
95! 1957 2016-07-07 10:43:48Z suehring
96! flight module added
97!
98! 1804 2016-04-05 16:30:18Z maronga
99! Removed code for parameter file check (__check)
100!
101! 1783 2016-03-06 18:36:17Z raasch
102! name change of netcdf routines and module + related changes
103!
104! 1779 2016-03-03 08:01:28Z raasch
105! coupling_char is trimmed at every place it occurs, because it can have
106! different length now
107!
108! 1745 2016-02-05 13:06:51Z gronemeier
109! Bugfix: added MPI barrier after deleting existing non-extendable file by PE0
110!
111! 1682 2015-10-07 23:56:08Z knoop
112! Code annotations made doxygen readable
113!
114! 1551 2015-03-03 14:18:16Z maronga
115! Removed redundant output for combine_plot_fields
116!
117! 1468 2014-09-24 14:06:57Z maronga
118! Adapted for use on up to 6-digit processor cores
119! Added file unit 117 (PROGRESS)
120!
121! 1359 2014-04-11 17:15:14Z hoffmann
122! Format of particle exchange statistics extended to reasonable numbers of     
123! particles.
124!
125! 1353 2014-04-08 15:21:23Z heinze
126! REAL constants provided with KIND-attribute,
127! declaration for unused variables xkoor, ykoor, zkoor removed
128!
129! 1327 2014-03-21 11:00:16Z raasch
130! parts concerning iso2d and avs output removed
131!
132! 1320 2014-03-20 08:40:49Z raasch
133! ONLY-attribute added to USE-statements,
134! kind-parameters added to all INTEGER and REAL declaration statements,
135! kinds are defined in new module kinds,
136! old module precision_kind is removed,
137! revision history before 2012 removed,
138! comment fields (!:) to be used for variable explanations added to
139! all variable declaration statements
140!
141! 1106 2013-03-04 05:31:38Z raasch
142! array_kind renamed precision_kind
143!
144! 1092 2013-02-02 11:24:22Z raasch
145! unused variables removed
146!
147! 1036 2012-10-22 13:43:42Z raasch
148! code put under GPL (PALM 3.9)
149!
150! 1031 2012-10-19 14:35:30Z raasch
151! netCDF4 without parallel file support implemented,
152! opening of netCDF files are done by new routines create_netcdf_file and
153! open_write_netcdf_file
154!
155! 964 2012-07-26 09:14:24Z raasch
156! old profil-units (40:49) removed,
157! append feature removed from unit 14
158!
159! 849 2012-03-15 10:35:09Z raasch
160! comment changed
161!
162! 809 2012-01-30 13:32:58Z maronga
163! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives
164!
165! 807 2012-01-25 11:53:51Z maronga
166! New cpp directive "__check" implemented which is used by check_namelist_files
167!
168! Revision 1.1  1997/08/11 06:10:55  raasch
169! Initial revision
170!
171!
172! Description:
173! ------------
174!> Check if file unit is open. If not, open file and, if necessary, write a
175!> header or start other initializing actions, respectively.
176!------------------------------------------------------------------------------!
177SUBROUTINE check_open( file_id )
178 
179
180    USE control_parameters,                                                    &
181        ONLY:  coupling_char, data_output_2d_on_each_pe,                       &
182               max_masks, message_string, mid, nz_do3d, openfile,              &
183               run_description_header
184
185    USE indices,                                                               &
186        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nz, nzb, nzt
187
188    USE kinds
189
190#if defined( __netcdf )
191    USE NETCDF
192#endif
193
194    USE netcdf_interface,                                                      &
195        ONLY:  id_set_agt, id_set_fl, id_set_mask, id_set_pr,                  &
196               id_set_pts, id_set_sp, id_set_ts, id_set_xy, id_set_xz,         &
197               id_set_yz, id_set_3d, nc_stat, netcdf_create_file,              &
198               netcdf_data_format, netcdf_define_header, netcdf_handle_error,  &
199               netcdf_open_write_file
200
201    USE particle_attributes,                                                   &
202        ONLY:  max_number_of_particle_groups, number_of_particle_groups,       &
203               particle_groups
204
205    USE pegrid
206
207    USE posix_calls_from_fortran,                                              &
208        ONLY:  fortran_sleep
209
210
211    IMPLICIT NONE
212
213    CHARACTER (LEN=4)   ::  mask_char               !<
214    CHARACTER (LEN=30)  ::  filename                !<
215    CHARACTER (LEN=80)  ::  rtext                   !<
216
217    INTEGER(iwp) ::  av          !<
218    INTEGER(iwp) ::  file_id     !<
219    INTEGER(iwp) ::  ioerr       !< IOSTAT flag for IO-commands ( 0 = no error )
220   
221    LOGICAL ::  netcdf_extend    !<
222
223!
224!-- Immediate return if file already open
225    IF ( openfile(file_id)%opened )  RETURN
226
227!
228!-- Only certain files are allowed to be re-opened
229!-- NOTE: some of the other files perhaps also could be re-opened, but it
230!--       has not been checked so far, if it works!
231    IF ( openfile(file_id)%opened_before )  THEN
232       SELECT CASE ( file_id )
233          CASE ( 13, 14, 21, 22, 23, 80, 85, 117 )
234             IF ( file_id == 14 .AND. openfile(file_id)%opened_before )  THEN
235                message_string = 're-open of unit ' //                         &
236                                 '14 is not verified. Please check results!'
237                CALL message( 'check_open', 'PA0165', 0, 1, 0, 6, 0 )       
238             ENDIF
239
240          CASE DEFAULT
241             WRITE( message_string, * ) 're-opening of file-id ', file_id,     &
242                                        ' is not allowed'
243             CALL message( 'check_open', 'PA0166', 0, 1, 0, 6, 0 )   
244               
245             RETURN
246
247       END SELECT
248    ENDIF
249
250!
251!-- Check if file may be opened on the relevant PE
252    SELECT CASE ( file_id )
253
254       CASE ( 15, 16, 17, 18, 19, 50:59, 104:105, 107, 109, 117 )
255     
256          IF ( myid /= 0 )  THEN
257             WRITE( message_string, * ) 'opening file-id ',file_id,            &
258                                        ' not allowed for PE ',myid
259             CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
260          ENDIF
261
262       CASE ( 101:103, 106, 111:113, 116, 201:200+2*max_masks )
263
264          IF ( netcdf_data_format < 5 )  THEN
265         
266             IF ( myid /= 0 )  THEN
267                WRITE( message_string, * ) 'opening file-id ',file_id,         &
268                                           ' not allowed for PE ',myid
269                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
270             ENDIF
271     
272          ENDIF
273
274       CASE ( 21, 22, 23 )
275
276          IF ( .NOT.  data_output_2d_on_each_pe )  THEN
277             IF ( myid /= 0 )  THEN
278                WRITE( message_string, * ) 'opening file-id ',file_id,         &
279                                           ' not allowed for PE ',myid
280                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
281             END IF
282          ENDIF
283
284       CASE ( 90:99 )
285
286!
287!--       File-ids that are used temporarily in other routines
288          WRITE( message_string, * ) 'opening file-id ',file_id,               &
289                                    ' is not allowed since it is used otherwise'
290          CALL message( 'check_open', 'PA0168', 0, 1, 0, 6, 0 ) 
291         
292    END SELECT
293
294!
295!-- Open relevant files
296    SELECT CASE ( file_id )
297
298       CASE ( 11 )
299
300          OPEN ( 11, FILE='PARIN'//TRIM( coupling_char ), FORM='FORMATTED',    &
301                     STATUS='OLD' )
302
303       CASE ( 13 )
304
305          IF ( myid_char == '' )  THEN
306             OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//myid_char,        &
307                        FORM='UNFORMATTED', STATUS='OLD' )
308          ELSE
309!
310!--          First opening of unit 13 openes file _000000 on all PEs because
311!--          only this file contains the global variables
312             IF ( .NOT. openfile(file_id)%opened_before )  THEN
313                OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/_000000',    &
314                           FORM='UNFORMATTED', STATUS='OLD' )
315             ELSE
316                OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/'//          &
317                           myid_char, FORM='UNFORMATTED', STATUS='OLD' )
318             ENDIF
319          ENDIF
320
321       CASE ( 14 )
322
323          IF ( myid_char == '' )  THEN
324             OPEN ( 14, FILE='BINOUT'//TRIM( coupling_char )//myid_char,       &
325                        FORM='UNFORMATTED', POSITION='APPEND' )
326          ELSE
327             IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  THEN
328                CALL local_system( 'mkdir  BINOUT' // TRIM( coupling_char ) )
329             ENDIF
330#if defined( __parallel )
331!
332!--          Set a barrier in order to allow that all other processors in the
333!--          directory created by PE0 can open their file
334             CALL MPI_BARRIER( comm2d, ierr )
335#endif
336             ioerr = 1
337             DO WHILE ( ioerr /= 0 )
338                OPEN ( 14, FILE='BINOUT'//TRIM(coupling_char)//'/'//myid_char, &
339                           FORM='UNFORMATTED', IOSTAT=ioerr )
340                IF ( ioerr /= 0 )  THEN
341                   WRITE( 9, * )  '*** could not open "BINOUT'//         &
342                                  TRIM(coupling_char)//'/'//myid_char//  &
343                                  '"! Trying again in 1 sec.'
344                   CALL fortran_sleep( 1 )
345                ENDIF
346             ENDDO
347
348          ENDIF
349
350       CASE ( 15 )
351
352          OPEN ( 15, FILE='RUN_CONTROL'//TRIM( coupling_char ),                &
353                     FORM='FORMATTED' )
354
355       CASE ( 16 )
356
357          OPEN ( 16, FILE='LIST_PROFIL'//TRIM( coupling_char ),                &
358                     FORM='FORMATTED' )
359
360       CASE ( 17 )
361
362          OPEN ( 17, FILE='LIST_PROFIL_1D'//TRIM( coupling_char ),             &
363                     FORM='FORMATTED' )
364
365       CASE ( 18 )
366
367          OPEN ( 18, FILE='CPU_MEASURES'//TRIM( coupling_char ),               &
368                     FORM='FORMATTED' )
369
370       CASE ( 19 )
371
372          OPEN ( 19, FILE='HEADER'//TRIM( coupling_char ), FORM='FORMATTED' )
373
374       CASE ( 20 )
375
376          IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  THEN
377             CALL local_system( 'mkdir  DATA_LOG' // TRIM( coupling_char ) )
378          ENDIF
379          IF ( myid_char == '' )  THEN
380             OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/_000000',    &
381                        FORM='UNFORMATTED', POSITION='APPEND' )
382          ELSE
383#if defined( __parallel )
384!
385!--          Set a barrier in order to allow that all other processors in the
386!--          directory created by PE0 can open their file
387             CALL MPI_BARRIER( comm2d, ierr )
388#endif
389             ioerr = 1
390             DO WHILE ( ioerr /= 0 )
391                OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/'//       &
392                           myid_char, FORM='UNFORMATTED', POSITION='APPEND',   &
393                           IOSTAT=ioerr )
394                IF ( ioerr /= 0 )  THEN
395                   WRITE( 9, * )  '*** could not open "DATA_LOG'//         &
396                                  TRIM( coupling_char )//'/'//myid_char//  &
397                                  '"! Trying again in 1 sec.'
398                   CALL fortran_sleep( 1 )
399                ENDIF
400             ENDDO
401
402          ENDIF
403
404       CASE ( 21 )
405
406          IF ( data_output_2d_on_each_pe )  THEN
407             OPEN ( 21, FILE='PLOT2D_XY'//TRIM( coupling_char )//myid_char,    &
408                        FORM='UNFORMATTED', POSITION='APPEND' )
409          ELSE
410             OPEN ( 21, FILE='PLOT2D_XY'//TRIM( coupling_char ),                       &
411                        FORM='UNFORMATTED', POSITION='APPEND' )
412          ENDIF
413
414          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
415!
416!--          Write index bounds of total domain for combine_plot_fields
417             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
418                WRITE (21)   0, nx,  0, ny
419             ENDIF
420
421          ENDIF
422
423       CASE ( 22 )
424
425          IF ( data_output_2d_on_each_pe )  THEN
426             OPEN ( 22, FILE='PLOT2D_XZ'//TRIM( coupling_char )//myid_char,    &
427                        FORM='UNFORMATTED', POSITION='APPEND' )
428          ELSE
429             OPEN ( 22, FILE='PLOT2D_XZ'//TRIM( coupling_char ),               &
430                        FORM='UNFORMATTED', POSITION='APPEND' )
431          ENDIF
432
433          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
434!
435!--          Write index bounds of total domain for combine_plot_fields
436             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
437                WRITE (22)   0, nx, 0, nz+1    ! output part
438             ENDIF
439
440          ENDIF
441
442       CASE ( 23 )
443
444          IF ( data_output_2d_on_each_pe )  THEN
445             OPEN ( 23, FILE='PLOT2D_YZ'//TRIM( coupling_char )//myid_char,    &
446                        FORM='UNFORMATTED', POSITION='APPEND' )
447          ELSE
448             OPEN ( 23, FILE='PLOT2D_YZ'//TRIM( coupling_char ),               &
449                        FORM='UNFORMATTED', POSITION='APPEND' )
450          ENDIF
451
452          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
453!
454!--          Write index bounds of total domain for combine_plot_fields
455             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
456                WRITE (23)   0, ny, 0, nz+1    ! output part
457             ENDIF
458
459          ENDIF
460         
461       CASE ( 25 )
462!
463!--       Binary files for surface data
464          OPEN ( 25, FILE='SURFACE_DATA_BIN'//TRIM( coupling_char )//myid_char,  &
465                 FORM='UNFORMATTED', POSITION='APPEND' )
466
467       CASE ( 26 )
468!
469!--       Binary files for averaged surface data
470          OPEN ( 26, FILE='SURFACE_DATA_AV_BIN'//TRIM( coupling_char )//myid_char,  &
471                 FORM='UNFORMATTED', POSITION='APPEND' )
472                 
473       CASE ( 27 )
474!
475!--       Binary files for virtual measurement data
476          OPEN ( 27, FILE='VIRTUAL_MEAS_BIN'//TRIM( coupling_char )//myid_char,&
477                 FORM='UNFORMATTED', POSITION='APPEND' )
478
479       CASE ( 30 )
480
481          OPEN ( 30, FILE='PLOT3D_DATA'//TRIM( coupling_char )//myid_char,     &
482                     FORM='UNFORMATTED' )
483!
484!--       Specifications for combine_plot_fields
485          IF ( myid == 0 )  THEN
486#if defined( __parallel )
487             WRITE ( 30 )  0, nx, 0, ny, 0, nz_do3d
488#endif
489          ENDIF
490
491       CASE ( 80 )
492
493          IF ( myid_char == '' )  THEN
494             OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM(coupling_char)//myid_char, &
495                        FORM='FORMATTED', POSITION='APPEND' )
496          ELSE
497             IF ( myid == 0  .AND.  .NOT. openfile(80)%opened_before )  THEN
498                CALL local_system( 'mkdir  PARTICLE_INFOS' //                  &
499                                   TRIM( coupling_char ) )
500             ENDIF
501#if defined( __parallel )
502!
503!--          Set a barrier in order to allow that thereafter all other
504!--          processors in the directory created by PE0 can open their file.
505!--          WARNING: The following barrier will lead to hanging jobs, if
506!--                   check_open is first called from routine
507!--                   allocate_prt_memory!
508             IF ( .NOT. openfile(80)%opened_before )  THEN
509                CALL MPI_BARRIER( comm2d, ierr )
510             ENDIF
511#endif
512             OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM( coupling_char )//'/'//    &
513                             myid_char,                                        &
514                        FORM='FORMATTED', POSITION='APPEND' )
515          ENDIF
516
517          IF ( .NOT. openfile(80)%opened_before )  THEN
518             WRITE ( 80, 8000 )  TRIM( run_description_header )
519          ENDIF
520
521       CASE ( 85 )
522
523          IF ( myid_char == '' )  THEN
524             OPEN ( 85, FILE='PARTICLE_DATA'//TRIM(coupling_char)//myid_char,  &
525                        FORM='UNFORMATTED', POSITION='APPEND' )
526          ELSE
527             IF ( myid == 0  .AND.  .NOT. openfile(85)%opened_before )  THEN
528                CALL local_system( 'mkdir  PARTICLE_DATA' //                   &
529                                   TRIM( coupling_char ) )
530             ENDIF
531#if defined( __parallel )
532!
533!--          Set a barrier in order to allow that thereafter all other
534!--          processors in the directory created by PE0 can open their file
535             CALL MPI_BARRIER( comm2d, ierr )
536#endif
537             ioerr = 1
538             DO WHILE ( ioerr /= 0 )
539                OPEN ( 85, FILE='PARTICLE_DATA'//TRIM( coupling_char )//'/'//  &
540                           myid_char,                                          &
541                           FORM='UNFORMATTED', POSITION='APPEND', IOSTAT=ioerr )
542                IF ( ioerr /= 0 )  THEN
543                   WRITE( 9, * )  '*** could not open "PARTICLE_DATA'//        &
544                                  TRIM( coupling_char )//'/'//myid_char//      &
545                                  '"! Trying again in 1 sec.'
546                   CALL fortran_sleep( 1 )
547                ENDIF
548             ENDDO
549
550          ENDIF
551
552          IF ( .NOT. openfile(85)%opened_before )  THEN
553             WRITE ( 85 )  run_description_header
554!
555!--          Attention: change version number whenever the output format on
556!--                     unit 85 is changed (see also in routine
557!--                     lpm_data_output_particles)
558             rtext = 'data format version 3.1'
559             WRITE ( 85 )  rtext
560             WRITE ( 85 )  number_of_particle_groups,                          &
561                           max_number_of_particle_groups
562             WRITE ( 85 )  particle_groups
563             WRITE ( 85 )  nxl, nxr, nys, nyn, nzb, nzt, nbgp
564          ENDIF
565
566!
567!--    File where sky-view factors and further required data is stored will be
568!--    read
569       CASE ( 88 )
570
571          IF ( myid_char == '' )  THEN
572             OPEN ( 88, FILE='SVFIN'//TRIM( coupling_char )//myid_char,        &
573                        FORM='UNFORMATTED', STATUS='OLD', IOSTAT=ioerr )
574          ELSE
575
576             OPEN ( 88, FILE='SVFIN'//TRIM( coupling_char )//'/'//myid_char,   &
577                        FORM='UNFORMATTED', STATUS='OLD', IOSTAT=ioerr )
578          ENDIF
579
580!
581!--    File where sky-view factors and further required data is stored will be
582!--    created
583       CASE ( 89 )
584
585          IF ( myid_char == '' )  THEN
586             OPEN ( 89, FILE='SVFOUT'//TRIM( coupling_char )//myid_char,       &
587                        FORM='UNFORMATTED', STATUS='NEW' )
588          ELSE
589             IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  THEN
590                CALL local_system( 'mkdir  SVFOUT' // TRIM( coupling_char ) )
591             ENDIF
592#if defined( __parallel )
593!
594!--          Set a barrier in order to allow that all other processors in the
595!--          directory created by PE0 can open their file
596             CALL MPI_BARRIER( comm2d, ierr )
597#endif
598             ioerr = 1
599             DO WHILE ( ioerr /= 0 )
600                OPEN ( 89, FILE='SVFOUT'//TRIM(coupling_char)//'/'//myid_char, &
601                           FORM='UNFORMATTED', STATUS='NEW', IOSTAT=ioerr )
602                IF ( ioerr /= 0 )  THEN
603                   WRITE( 9, * )  '*** could not open "SVFOUT'//               &
604                                  TRIM(coupling_char)//'/'//myid_char//        &
605                                  '"! Trying again in 1 sec.'
606                   CALL fortran_sleep( 1 )
607                ENDIF
608             ENDDO
609
610          ENDIF
611
612!
613!--    Progress file that is used by the PALM watchdog
614       CASE ( 117 )
615
616          OPEN ( 117, FILE='PROGRESS'//TRIM( coupling_char ),                  &
617                      STATUS='REPLACE', FORM='FORMATTED' )
618
619#if defined( __netcdf )
620       CASE ( 101, 111 )
621!
622!--       Set filename depending on unit number
623          IF ( file_id == 101 )  THEN
624             filename = 'DATA_2D_XY_NETCDF' // TRIM( coupling_char )
625             av = 0
626          ELSE
627             filename = 'DATA_2D_XY_AV_NETCDF' // TRIM( coupling_char )
628             av = 1
629          ENDIF
630!
631!--       Inquire, if there is a netCDF file from a previuos run. This should
632!--       be opened for extension, if its dimensions and variables match the
633!--       actual run.
634          INQUIRE( FILE=filename, EXIST=netcdf_extend )
635          IF ( netcdf_extend )  THEN
636!
637!--          Open an existing netCDF file for output
638             CALL netcdf_open_write_file( filename, id_set_xy(av), .TRUE., 20 )
639!
640!--          Read header information and set all ids. If there is a mismatch
641!--          between the previuos and the actual run, netcdf_extend is returned
642!--          as .FALSE.
643             CALL netcdf_define_header( 'xy', netcdf_extend, av )
644
645!
646!--          Remove the local file, if it can not be extended
647             IF ( .NOT. netcdf_extend )  THEN
648                nc_stat = NF90_CLOSE( id_set_xy(av) )
649                CALL netcdf_handle_error( 'check_open', 21 )
650                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
651#if defined( __parallel )
652!
653!--             Set a barrier in order to assure that PE0 deleted the old file
654!--             before any other processor tries to open a new file.
655!--             Barrier is only needed in case of parallel I/O
656                IF ( netcdf_data_format > 4 )  CALL MPI_BARRIER( comm2d, ierr )
657#endif
658             ENDIF
659
660          ENDIF
661
662          IF ( .NOT. netcdf_extend )  THEN
663!
664!--          Create a new netCDF output file with requested netCDF format
665             CALL netcdf_create_file( filename, id_set_xy(av), .TRUE., 22 )
666
667!
668!--          Define the header
669             CALL netcdf_define_header( 'xy', netcdf_extend, av )
670
671!
672!--          In case of parallel netCDF output, create flag file which tells
673!--          combine_plot_fields that nothing is to do.
674             IF ( myid == 0  .AND.  netcdf_data_format > 4 )  THEN
675                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_XY' )
676                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
677                CLOSE( 99 )
678             ENDIF
679
680          ENDIF
681
682       CASE ( 102, 112 )
683!
684!--       Set filename depending on unit number
685          IF ( file_id == 102 )  THEN
686             filename = 'DATA_2D_XZ_NETCDF' // TRIM( coupling_char )
687             av = 0
688          ELSE
689             filename = 'DATA_2D_XZ_AV_NETCDF' // TRIM( coupling_char )
690             av = 1
691          ENDIF
692!
693!--       Inquire, if there is a netCDF file from a previuos run. This should
694!--       be opened for extension, if its dimensions and variables match the
695!--       actual run.
696          INQUIRE( FILE=filename, EXIST=netcdf_extend )
697
698          IF ( netcdf_extend )  THEN
699!
700!--          Open an existing netCDF file for output
701             CALL netcdf_open_write_file( filename, id_set_xz(av), .TRUE., 23 )
702!
703!--          Read header information and set all ids. If there is a mismatch
704!--          between the previuos and the actual run, netcdf_extend is returned
705!--          as .FALSE.
706             CALL netcdf_define_header( 'xz', netcdf_extend, av )
707
708!
709!--          Remove the local file, if it can not be extended
710             IF ( .NOT. netcdf_extend )  THEN
711                nc_stat = NF90_CLOSE( id_set_xz(av) )
712                CALL netcdf_handle_error( 'check_open', 24 )
713                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
714#if defined( __parallel )
715!
716!--             Set a barrier in order to assure that PE0 deleted the old file
717!--             before any other processor tries to open a new file
718!--             Barrier is only needed in case of parallel I/O
719                IF ( netcdf_data_format > 4 )  CALL MPI_BARRIER( comm2d, ierr )
720#endif
721             ENDIF
722
723          ENDIF
724
725          IF ( .NOT. netcdf_extend )  THEN
726!
727!--          Create a new netCDF output file with requested netCDF format
728             CALL netcdf_create_file( filename, id_set_xz(av), .TRUE., 25 )
729
730!
731!--          Define the header
732             CALL netcdf_define_header( 'xz', netcdf_extend, av )
733
734!
735!--          In case of parallel netCDF output, create flag file which tells
736!--          combine_plot_fields that nothing is to do.
737             IF ( myid == 0  .AND.  netcdf_data_format > 4 )  THEN
738                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_XZ' )
739                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
740                CLOSE( 99 )
741             ENDIF
742
743          ENDIF
744
745       CASE ( 103, 113 )
746!
747!--       Set filename depending on unit number
748          IF ( file_id == 103 )  THEN
749             filename = 'DATA_2D_YZ_NETCDF' // TRIM( coupling_char )
750             av = 0
751          ELSE
752             filename = 'DATA_2D_YZ_AV_NETCDF' // TRIM( coupling_char )
753             av = 1
754          ENDIF
755!
756!--       Inquire, if there is a netCDF file from a previuos run. This should
757!--       be opened for extension, if its dimensions and variables match the
758!--       actual run.
759          INQUIRE( FILE=filename, EXIST=netcdf_extend )
760
761          IF ( netcdf_extend )  THEN
762!
763!--          Open an existing netCDF file for output
764             CALL netcdf_open_write_file( filename, id_set_yz(av), .TRUE., 26 )
765!
766!--          Read header information and set all ids. If there is a mismatch
767!--          between the previuos and the actual run, netcdf_extend is returned
768!--          as .FALSE.
769             CALL netcdf_define_header( 'yz', netcdf_extend, av )
770
771!
772!--          Remove the local file, if it can not be extended
773             IF ( .NOT. netcdf_extend )  THEN
774                nc_stat = NF90_CLOSE( id_set_yz(av) )
775                CALL netcdf_handle_error( 'check_open', 27 )
776                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
777#if defined( __parallel )
778!
779!--             Set a barrier in order to assure that PE0 deleted the old file
780!--             before any other processor tries to open a new file
781!--             Barrier is only needed in case of parallel I/O
782                IF ( netcdf_data_format > 4 )  CALL MPI_BARRIER( comm2d, ierr )
783#endif
784             ENDIF
785
786          ENDIF
787
788          IF ( .NOT. netcdf_extend )  THEN
789!
790!--          Create a new netCDF output file with requested netCDF format
791             CALL netcdf_create_file( filename, id_set_yz(av), .TRUE., 28 )
792
793!
794!--          Define the header
795             CALL netcdf_define_header( 'yz', netcdf_extend, av )
796
797!
798!--          In case of parallel netCDF output, create flag file which tells
799!--          combine_plot_fields that nothing is to do.
800             IF ( myid == 0  .AND.  netcdf_data_format > 4 )  THEN
801                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_YZ' )
802                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
803                CLOSE( 99 )
804             ENDIF
805
806          ENDIF
807
808       CASE ( 104 )
809!
810!--       Set filename
811          filename = 'DATA_1D_PR_NETCDF' // TRIM( coupling_char )
812
813!
814!--       Inquire, if there is a netCDF file from a previuos run. This should
815!--       be opened for extension, if its variables match the actual run.
816          INQUIRE( FILE=filename, EXIST=netcdf_extend )
817
818          IF ( netcdf_extend )  THEN
819!
820!--          Open an existing netCDF file for output
821             CALL netcdf_open_write_file( filename, id_set_pr, .FALSE., 29 )
822!
823!--          Read header information and set all ids. If there is a mismatch
824!--          between the previuos and the actual run, netcdf_extend is returned
825!--          as .FALSE.
826             CALL netcdf_define_header( 'pr', netcdf_extend, 0 )
827
828!
829!--          Remove the local file, if it can not be extended
830             IF ( .NOT. netcdf_extend )  THEN
831                nc_stat = NF90_CLOSE( id_set_pr )
832                CALL netcdf_handle_error( 'check_open', 30 )
833                CALL local_system( 'rm ' // TRIM( filename ) )
834             ENDIF
835
836          ENDIF         
837
838          IF ( .NOT. netcdf_extend )  THEN
839!
840!--          Create a new netCDF output file with requested netCDF format
841             CALL netcdf_create_file( filename, id_set_pr, .FALSE., 31 )
842!
843!--          Define the header
844             CALL netcdf_define_header( 'pr', netcdf_extend, 0 )
845
846          ENDIF
847
848       CASE ( 105 )
849!
850!--       Set filename
851          filename = 'DATA_1D_TS_NETCDF' // TRIM( coupling_char )
852
853!
854!--       Inquire, if there is a netCDF file from a previuos run. This should
855!--       be opened for extension, if its variables match the actual run.
856          INQUIRE( FILE=filename, EXIST=netcdf_extend )
857
858          IF ( netcdf_extend )  THEN
859!
860!--          Open an existing netCDF file for output
861             CALL netcdf_open_write_file( filename, id_set_ts, .FALSE., 32 )
862!
863!--          Read header information and set all ids. If there is a mismatch
864!--          between the previuos and the actual run, netcdf_extend is returned
865!--          as .FALSE.
866             CALL netcdf_define_header( 'ts', netcdf_extend, 0 )
867
868!
869!--          Remove the local file, if it can not be extended
870             IF ( .NOT. netcdf_extend )  THEN
871                nc_stat = NF90_CLOSE( id_set_ts )
872                CALL netcdf_handle_error( 'check_open', 33 )
873                CALL local_system( 'rm ' // TRIM( filename ) )
874             ENDIF
875
876          ENDIF         
877
878          IF ( .NOT. netcdf_extend )  THEN
879!
880!--          Create a new netCDF output file with requested netCDF format
881             CALL netcdf_create_file( filename, id_set_ts, .FALSE., 34 )
882!
883!--          Define the header
884             CALL netcdf_define_header( 'ts', netcdf_extend, 0 )
885
886          ENDIF
887
888
889       CASE ( 106, 116 )
890!
891!--       Set filename depending on unit number
892          IF ( file_id == 106 )  THEN
893             filename = 'DATA_3D_NETCDF' // TRIM( coupling_char )
894             av = 0
895          ELSE
896             filename = 'DATA_3D_AV_NETCDF' // TRIM( coupling_char )
897             av = 1
898          ENDIF
899!
900!--       Inquire, if there is a netCDF file from a previous run. This should
901!--       be opened for extension, if its dimensions and variables match the
902!--       actual run.
903          INQUIRE( FILE=filename, EXIST=netcdf_extend )
904          IF ( netcdf_extend )  THEN
905!
906!--          Open an existing netCDF file for output
907             CALL netcdf_open_write_file( filename, id_set_3d(av), .TRUE., 35 )
908!
909!--          Read header information and set all ids. If there is a mismatch
910!--          between the previuos and the actual run, netcdf_extend is returned
911!--          as .FALSE.
912             CALL netcdf_define_header( '3d', netcdf_extend, av )
913
914!
915!--          Remove the local file, if it can not be extended
916             IF ( .NOT. netcdf_extend )  THEN
917                nc_stat = NF90_CLOSE( id_set_3d(av) )
918                CALL netcdf_handle_error( 'check_open', 36 )
919                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
920#if defined( __parallel )
921!
922!--             Set a barrier in order to assure that PE0 deleted the old file
923!--             before any other processor tries to open a new file
924!--             Barrier is only needed in case of parallel I/O
925                IF ( netcdf_data_format > 4 )  CALL MPI_BARRIER( comm2d, ierr )
926#endif
927             ENDIF
928
929          ENDIF
930
931          IF ( .NOT. netcdf_extend )  THEN
932!
933!--          Create a new netCDF output file with requested netCDF format
934             CALL netcdf_create_file( filename, id_set_3d(av), .TRUE., 37 )
935
936!
937!--          Define the header
938             CALL netcdf_define_header( '3d', netcdf_extend, av )
939
940!
941!--          In case of parallel netCDF output, create flag file which tells
942!--          combine_plot_fields that nothing is to do.
943             IF ( myid == 0  .AND.  netcdf_data_format > 4 )  THEN
944                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_3D' )
945                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
946                CLOSE( 99 )
947             ENDIF
948
949          ENDIF
950
951
952       CASE ( 107 )
953!
954!--       Set filename
955          filename = 'DATA_1D_SP_NETCDF' // TRIM( coupling_char )
956
957!
958!--       Inquire, if there is a netCDF file from a previuos run. This should
959!--       be opened for extension, if its variables match the actual run.
960          INQUIRE( FILE=filename, EXIST=netcdf_extend )
961
962          IF ( netcdf_extend )  THEN
963!
964!--          Open an existing netCDF file for output
965             CALL netcdf_open_write_file( filename, id_set_sp, .FALSE., 38 )
966
967!
968!--          Read header information and set all ids. If there is a mismatch
969!--          between the previuos and the actual run, netcdf_extend is returned
970!--          as .FALSE.
971             CALL netcdf_define_header( 'sp', netcdf_extend, 0 )
972
973!
974!--          Remove the local file, if it can not be extended
975             IF ( .NOT. netcdf_extend )  THEN
976                nc_stat = NF90_CLOSE( id_set_sp )
977                CALL netcdf_handle_error( 'check_open', 39 )
978                CALL local_system( 'rm ' // TRIM( filename ) )
979             ENDIF
980
981          ENDIF         
982
983          IF ( .NOT. netcdf_extend )  THEN
984!
985!--          Create a new netCDF output file with requested netCDF format
986             CALL netcdf_create_file( filename, id_set_sp, .FALSE., 40 )
987!
988!--          Define the header
989             CALL netcdf_define_header( 'sp', netcdf_extend, 0 )
990
991          ENDIF
992
993!
994!--     Currently disabled
995!       CASE ( 108 )
996
997!          IF ( myid_char == '' )  THEN
998!             filename = 'DATA_PRT_NETCDF' // TRIM( coupling_char )
999!          ELSE
1000!             filename = 'DATA_PRT_NETCDF' // TRIM( coupling_char ) // '/' //   &
1001!                        myid_char
1002!          ENDIF
1003!
1004!--       Inquire, if there is a netCDF file from a previuos run. This should
1005!--       be opened for extension, if its variables match the actual run.
1006!          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1007
1008!          IF ( netcdf_extend )  THEN
1009!
1010!--          Open an existing netCDF file for output
1011!             CALL netcdf_open_write_file( filename, id_set_prt, .FALSE., 41 )
1012!
1013!--          Read header information and set all ids. If there is a mismatch
1014!--          between the previuos and the actual run, netcdf_extend is returned
1015!--          as .FALSE.
1016!             CALL netcdf_define_header( 'pt', netcdf_extend, 0 )
1017
1018!
1019!--          Remove the local file, if it can not be extended
1020!             IF ( .NOT. netcdf_extend )  THEN
1021!                nc_stat = NF90_CLOSE( id_set_prt )
1022!                CALL netcdf_handle_error( 'check_open', 42 )
1023!                CALL local_system( 'rm ' // TRIM( filename ) )
1024!             ENDIF
1025
1026!          ENDIF         
1027
1028!          IF ( .NOT. netcdf_extend )  THEN
1029
1030!
1031!--          For runs on multiple processors create the subdirectory
1032!             IF ( myid_char /= '' )  THEN
1033!                IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  &
1034!                THEN    ! needs modification in case of non-extendable sets
1035!                   CALL local_system( 'mkdir  DATA_PRT_NETCDF' //              &
1036!                                       TRIM( coupling_char ) // '/' )
1037!                ENDIF
1038#if defined( __parallel )
1039!
1040!--             Set a barrier in order to allow that all other processors in the
1041!--             directory created by PE0 can open their file
1042!                CALL MPI_BARRIER( comm2d, ierr )
1043#endif
1044!             ENDIF
1045
1046!
1047!--          Create a new netCDF output file with requested netCDF format
1048!             CALL netcdf_create_file( filename, id_set_prt, .FALSE., 43 )
1049
1050!
1051!--          Define the header
1052!             CALL netcdf_define_header( 'pt', netcdf_extend, 0 )
1053
1054!          ENDIF
1055
1056       CASE ( 109 )
1057!
1058!--       Set filename
1059          filename = 'DATA_1D_PTS_NETCDF' // TRIM( coupling_char )
1060
1061!
1062!--       Inquire, if there is a netCDF file from a previuos run. This should
1063!--       be opened for extension, if its variables match the actual run.
1064          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1065
1066          IF ( netcdf_extend )  THEN
1067!
1068!--          Open an existing netCDF file for output
1069             CALL netcdf_open_write_file( filename, id_set_pts, .FALSE., 393 )
1070!
1071!--          Read header information and set all ids. If there is a mismatch
1072!--          between the previuos and the actual run, netcdf_extend is returned
1073!--          as .FALSE.
1074             CALL netcdf_define_header( 'ps', netcdf_extend, 0 )
1075
1076!
1077!--          Remove the local file, if it can not be extended
1078             IF ( .NOT. netcdf_extend )  THEN
1079                nc_stat = NF90_CLOSE( id_set_pts )
1080                CALL netcdf_handle_error( 'check_open', 394 )
1081                CALL local_system( 'rm ' // TRIM( filename ) )
1082             ENDIF
1083
1084          ENDIF         
1085
1086          IF ( .NOT. netcdf_extend )  THEN
1087!
1088!--          Create a new netCDF output file with requested netCDF format
1089             CALL netcdf_create_file( filename, id_set_pts, .FALSE., 395 )
1090!
1091!--          Define the header
1092             CALL netcdf_define_header( 'ps', netcdf_extend, 0 )
1093
1094          ENDIF
1095
1096       CASE ( 118 )
1097
1098          IF ( myid == 0 )  THEN
1099             filename = 'DATA_AGT_NETCDF'
1100!
1101!--       Inquire, if there is a netCDF file from a previuos run. This should
1102!--       be opened for extension, if its variables match the actual run.
1103          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1104
1105!
1106!--          Create a new netCDF output file with requested netCDF format
1107             CALL netcdf_create_file( filename, id_set_agt, .FALSE., 43 )
1108
1109!
1110!--          Define the header
1111             CALL netcdf_define_header( 'ag', netcdf_extend, 0 )
1112          ENDIF
1113
1114!           IF ( netcdf_extend )  THEN
1115! !
1116! !--          Open an existing netCDF file for output
1117!              CALL netcdf_open_write_file( filename, id_set_agt, .FALSE., 41 )
1118! !
1119! !--          Read header information and set all ids. If there is a mismatch
1120! !--          between the previuos and the actual run, netcdf_extend is returned
1121! !--          as .FALSE.
1122!              CALL netcdf_define_header( 'ag', netcdf_extend, 0 )
1123!
1124! !
1125! !--          Remove the local file, if it can not be extended
1126!              IF ( .NOT. netcdf_extend )  THEN
1127!                 nc_stat = NF90_CLOSE( id_set_agt )
1128!                 CALL netcdf_handle_error( 'check_open', 42 )
1129!                 CALL local_system( 'rm ' // TRIM( filename ) )
1130!              ENDIF
1131!
1132!           ENDIF
1133
1134          IF ( .NOT. netcdf_extend )  THEN
1135
1136!
1137! !--          For runs on multiple processors create the subdirectory
1138!              IF ( myid_char /= '' )  THEN
1139!                 IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  &
1140!                 THEN    ! needs modification in case of non-extendable sets
1141!                    CALL local_system( 'mkdir  DATA_PRT_NETCDF' //              &
1142!                                        TRIM( coupling_char ) // '/' )
1143!                 ENDIF
1144! #if defined( __parallel )
1145! !
1146! !--             Set a barrier in order to allow that all other processors in the
1147! !--             directory created by PE0 can open their file
1148!                 CALL MPI_BARRIER( comm2d, ierr )
1149! #endif
1150!              ENDIF
1151
1152          ENDIF
1153
1154
1155!
1156!--    nc-file for virtual flight measurements
1157       CASE ( 199 )
1158!
1159!--       Set filename
1160          filename = 'DATA_1D_FL_NETCDF' // TRIM( coupling_char )
1161
1162!
1163!--       Inquire, if there is a netCDF file from a previuos run. This should
1164!--       be opened for extension, if its variables match the actual run.
1165          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1166
1167          IF ( netcdf_extend )  THEN
1168!
1169!--          Open an existing netCDF file for output
1170             CALL netcdf_open_write_file( filename, id_set_fl, .FALSE., 532 )
1171!
1172!--          Read header information and set all ids. If there is a mismatch
1173!--          between the previuos and the actual run, netcdf_extend is returned
1174!--          as .FALSE.
1175             CALL netcdf_define_header( 'fl', netcdf_extend, 0 )
1176
1177!
1178!--          Remove the local file, if it can not be extended
1179             IF ( .NOT. netcdf_extend )  THEN
1180                nc_stat = NF90_CLOSE( id_set_fl )
1181                CALL netcdf_handle_error( 'check_open', 533 )
1182                CALL local_system( 'rm ' // TRIM( filename ) )
1183             ENDIF
1184
1185          ENDIF         
1186
1187          IF ( .NOT. netcdf_extend )  THEN
1188!
1189!--          Create a new netCDF output file with requested netCDF format
1190             CALL netcdf_create_file( filename, id_set_fl, .FALSE., 534 )
1191!
1192!--          Define the header
1193             CALL netcdf_define_header( 'fl', netcdf_extend, 0 )
1194
1195          ENDIF
1196
1197
1198       CASE ( 201:200+2*max_masks )
1199!
1200!--       Set filename depending on unit number
1201          IF ( file_id <= 200+max_masks )  THEN
1202             mid = file_id - 200
1203             WRITE ( mask_char,'(A2,I2.2)')  '_M', mid
1204             filename = 'DATA_MASK_NETCDF' // TRIM( coupling_char ) //         &
1205                        mask_char
1206             av = 0
1207          ELSE
1208             mid = file_id - (200+max_masks)
1209             WRITE ( mask_char,'(A2,I2.2)')  '_M', mid
1210             filename = 'DATA_MASK_AV_NETCDF' // TRIM( coupling_char ) //      &
1211                        mask_char
1212             av = 1
1213          ENDIF
1214!
1215!--       Inquire, if there is a netCDF file from a previuos run. This should
1216!--       be opened for extension, if its dimensions and variables match the
1217!--       actual run.
1218          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1219
1220          IF ( netcdf_extend )  THEN
1221!
1222!--          Open an existing netCDF file for output
1223             CALL netcdf_open_write_file( filename, id_set_mask(mid,av),       &
1224                                          .TRUE., 456 )
1225!
1226!--          Read header information and set all ids. If there is a mismatch
1227!--          between the previuos and the actual run, netcdf_extend is returned
1228!--          as .FALSE.
1229             CALL netcdf_define_header( 'ma', netcdf_extend, file_id )
1230
1231!
1232!--          Remove the local file, if it can not be extended
1233             IF ( .NOT. netcdf_extend )  THEN
1234                nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
1235                CALL netcdf_handle_error( 'check_open', 457 )
1236                CALL local_system('rm ' // TRIM( filename ) )
1237             ENDIF
1238
1239          ENDIF         
1240
1241          IF ( .NOT. netcdf_extend )  THEN
1242!
1243!--          Create a new netCDF output file with requested netCDF format
1244             CALL netcdf_create_file( filename, id_set_mask(mid,av), .TRUE., 458 )
1245!
1246!--          Define the header
1247             CALL netcdf_define_header( 'ma', netcdf_extend, file_id )
1248
1249          ENDIF
1250
1251
1252#else
1253
1254       CASE ( 101:109, 111:113, 116, 201:200+2*max_masks )
1255
1256!
1257!--       Nothing is done in case of missing netcdf support
1258          RETURN
1259
1260#endif
1261
1262       CASE DEFAULT
1263
1264          WRITE( message_string, * ) 'no OPEN-statement for file-id ',file_id
1265          CALL message( 'check_open', 'PA0172', 2, 2, -1, 6, 1 )
1266
1267    END SELECT
1268
1269!
1270!-- Set open flag
1271    openfile(file_id)%opened = .TRUE.
1272
1273!
1274!-- Formats
12758000 FORMAT (A/                                                                &
1276             '  step    time    # of parts     lPE sent/recv  rPE sent/recv  ',&
1277             'sPE sent/recv  nPE sent/recv    max # of parts  '/               &
1278             109('-'))
1279
1280 END SUBROUTINE check_open
Note: See TracBrowser for help on using the repository browser.