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

Last change on this file since 2515 was 2514, checked in by suehring, 7 years ago

Remove tabs from code, causing problems during merging

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