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

Last change on this file since 4598 was 4577, checked in by raasch, 4 years ago

further re-formatting to follow the PALM coding standard

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