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

Last change on this file since 564 was 564, checked in by helmke, 14 years ago

several changes for an unlimited output of mask data and message IDs changed

  • Property svn:keywords set to Id
File size: 55.1 KB
Line 
1SUBROUTINE check_open( file_id )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! start number of mask output files changed to 201, netcdf message identifiers
7! of masked output changed
8!
9! Former revisions:
10! -----------------
11! $Id: check_open.f90 564 2010-09-30 13:18:59Z helmke $
12!
13! 519 2010-03-19 05:30:02Z raasch
14! NetCDF4 support for particle data
15!
16! 493 2010-03-01 08:30:24Z raasch
17! NetCDF4 support (parallel output)
18!
19! 410 2009-12-04 17:05:40Z letzel
20! masked data output
21!
22! 277 2009-03-31 09:13:47Z heinze
23! Output of NetCDF messages with aid of message handling routine.
24! Output of messages replaced by message handling routine
25!
26! 146 2008-01-17 13:08:34Z raasch
27! First opening of unit 13 openes file _0000 on all PEs (parallel version)
28! because only this file contains the global variables,
29! myid_char_14 removed
30!
31! 120 2007-10-17 11:54:43Z raasch
32! Status of 3D-volume NetCDF data file only depends on switch netcdf_64bit_3d
33!
34! 105 2007-08-08 07:12:55Z raasch
35! Different filenames are used in case of a coupled simulation,
36! coupling_char added to all relevant filenames
37!
38! 82 2007-04-16 15:40:52Z raasch
39! Call of local_getenv removed, preprocessor directives for old systems removed
40!
41! 46 2007-03-05 06:00:47Z raasch
42! +netcdf_64bit_3d to switch on 64bit offset only for 3D files
43!
44! RCS Log replace by Id keyword, revision history cleaned up
45!
46! Revision 1.44  2006/08/22 13:48:34  raasch
47! xz and yz cross sections now up to nzt+1
48!
49! Revision 1.1  1997/08/11 06:10:55  raasch
50! Initial revision
51!
52!
53! Description:
54! ------------
55! Check if file unit is open. If not, open file and, if necessary, write a
56! header or start other initializing actions, respectively.
57!------------------------------------------------------------------------------!
58
59    USE array_kind
60    USE arrays_3d
61    USE control_parameters
62    USE grid_variables
63    USE indices
64    USE netcdf_control
65    USE particle_attributes
66    USE pegrid
67    USE profil_parameter
68    USE statistics
69
70    IMPLICIT NONE
71
72    CHARACTER (LEN=2)   ::  mask_char, suffix
73    CHARACTER (LEN=20)  ::  xtext = 'time in s'
74    CHARACTER (LEN=30)  ::  filename
75    CHARACTER (LEN=40)  ::  avs_coor_file, avs_coor_file_localname, &
76                            avs_data_file_localname
77    CHARACTER (LEN=80)  ::  rtext
78    CHARACTER (LEN=100) ::  avs_coor_file_catalog, avs_data_file_catalog, &
79                            batch_scp, zeile
80    CHARACTER (LEN=400) ::  command
81
82    INTEGER ::  av, anzzeile = 1, cranz, file_id, i, iaddres, ierr1, iusern, &
83                j, k, legpos = 1, timodex = 1
84    INTEGER, DIMENSION(10) ::  cucol, klist, lstyle
85
86    LOGICAL ::  avs_coor_file_found = .FALSE., avs_data_file_found = .FALSE., &
87                datleg = .TRUE., get_filenames, grid = .TRUE., netcdf_extend, &
88                rand = .TRUE., swap = .TRUE., twoxa = .TRUE., twoya = .TRUE.
89
90    REAL ::  ansx = -999.999, ansy = -999.999, gwid = 0.1, rlegfak = 1.5, &
91             sizex = 250.0, sizey = 40.0, texfac = 1.5
92
93    REAL, DIMENSION(:), ALLOCATABLE      ::  eta, ho, hu
94    REAL(spk), DIMENSION(:), ALLOCATABLE ::  xkoor, ykoor, zkoor 
95
96
97    NAMELIST /RAHMEN/  anzzeile, cranz, datleg, rtext, swap
98    NAMELIST /CROSS/   ansx, ansy, cucol, grid, gwid, klist, legpos, lstyle, &
99                       rand, rlegfak, sizex, sizey, texfac, &
100                       timodex, twoxa, twoya, xtext
101                       
102
103!
104!-- Immediate return if file already open
105    IF ( openfile(file_id)%opened )  RETURN
106
107!
108!-- Only certain files are allowed to be re-opened
109!-- NOTE: some of the other files perhaps also could be re-opened, but it
110!--       has not been checked so far, if it works!
111    IF ( openfile(file_id)%opened_before )  THEN
112       SELECT CASE ( file_id )
113          CASE ( 13, 14, 21, 22, 23, 80:85 )
114             IF ( file_id == 14 .AND. openfile(file_id)%opened_before )  THEN
115                message_string = 're-open of unit ' // &
116                                 '14 is not verified. Please check results!'
117                CALL message( 'check_open', 'PA0165', 0, 1, 0, 6, 0 )       
118             ENDIF
119
120          CASE DEFAULT
121             WRITE( message_string, * ) 're-opening of file-id ', file_id, &
122                                        ' is not allowed'
123             CALL message( 'check_open', 'PA0166', 0, 1, 0, 6, 0 )   
124               
125             RETURN
126
127       END SELECT
128    ENDIF
129
130!
131!-- Check if file may be opened on the relevant PE
132    SELECT CASE ( file_id )
133
134       CASE ( 15, 16, 17, 18, 19, 40:49, 50:59, 81:84, 104:105, 107, 109 )
135             
136          IF ( myid /= 0 )  THEN
137             WRITE( message_string, * ) 'opening file-id ',file_id, &
138                                        ' not allowed for PE ',myid
139             CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
140          ENDIF
141
142       CASE ( 101:103, 106, 111:113, 116, 201:200+2*max_masks )
143
144          IF ( netcdf_data_format < 3 )  THEN
145         
146             IF ( myid /= 0 )  THEN
147                WRITE( message_string, * ) 'opening file-id ',file_id, &
148                                           ' not allowed for PE ',myid
149                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
150             ENDIF
151             
152          ENDIF
153
154       CASE ( 21, 22, 23 )
155
156          IF ( .NOT.  data_output_2d_on_each_pe )  THEN
157             IF ( myid /= 0 )  THEN
158                WRITE( message_string, * ) 'opening file-id ',file_id, &
159                                           ' not allowed for PE ',myid
160                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
161             END IF
162          ENDIF
163
164       CASE ( 27, 28, 29, 31, 32, 33, 71:73, 90:99 )
165
166!
167!--       File-ids that are used temporarily in other routines
168          WRITE( message_string, * ) 'opening file-id ',file_id, &
169                                    ' is not allowed since it is used otherwise'
170          CALL message( 'check_open', 'PA0168', 0, 1, 0, 6, 0 ) 
171         
172    END SELECT
173
174!
175!-- Open relevant files
176    SELECT CASE ( file_id )
177
178       CASE ( 11 )
179
180          OPEN ( 11, FILE='PARIN'//coupling_char, FORM='FORMATTED', &
181                     STATUS='OLD' )
182
183       CASE ( 13 )
184
185          IF ( myid_char == '' )  THEN
186             OPEN ( 13, FILE='BININ'//coupling_char//myid_char, &
187                        FORM='UNFORMATTED', STATUS='OLD' )
188          ELSE
189!
190!--          First opening of unit 13 openes file _0000 on all PEs because only
191!--          this file contains the global variables
192             IF ( .NOT. openfile(file_id)%opened_before )  THEN
193                OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/_0000',&
194                           FORM='UNFORMATTED', STATUS='OLD' )
195             ELSE
196                OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/'//myid_char,&
197                           FORM='UNFORMATTED', STATUS='OLD' )
198             ENDIF
199          ENDIF
200
201       CASE ( 14 )
202
203          IF ( myid_char == '' )  THEN
204             OPEN ( 14, FILE='BINOUT'//coupling_char//myid_char, &
205                        FORM='UNFORMATTED', POSITION='APPEND' )
206          ELSE
207             IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  THEN
208                CALL local_system( 'mkdir  BINOUT' // coupling_char )
209             ENDIF
210#if defined( __parallel )
211!
212!--          Set a barrier in order to allow that all other processors in the
213!--          directory created by PE0 can open their file
214             CALL MPI_BARRIER( comm2d, ierr )
215#endif
216             OPEN ( 14, FILE='BINOUT'//TRIM(coupling_char)//'/'//myid_char, &
217                        FORM='UNFORMATTED', POSITION='APPEND' )
218          ENDIF
219
220       CASE ( 15 )
221
222          OPEN ( 15, FILE='RUN_CONTROL'//coupling_char, FORM='FORMATTED' )
223
224       CASE ( 16 )
225
226          OPEN ( 16, FILE='LIST_PROFIL'//coupling_char, FORM='FORMATTED' )
227
228       CASE ( 17 )
229
230          OPEN ( 17, FILE='LIST_PROFIL_1D'//coupling_char, FORM='FORMATTED' )
231
232       CASE ( 18 )
233
234          OPEN ( 18, FILE='CPU_MEASURES'//coupling_char, FORM='FORMATTED' )
235
236       CASE ( 19 )
237
238          OPEN ( 19, FILE='HEADER'//coupling_char, FORM='FORMATTED' )
239
240       CASE ( 20 )
241
242          IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  THEN
243             CALL local_system( 'mkdir  DATA_LOG' // coupling_char )
244          ENDIF
245          IF ( myid_char == '' )  THEN
246             OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/_0000', &
247                        FORM='UNFORMATTED', POSITION='APPEND' )
248          ELSE
249#if defined( __parallel )
250!
251!--          Set a barrier in order to allow that all other processors in the
252!--          directory created by PE0 can open their file
253             CALL MPI_BARRIER( comm2d, ierr )
254#endif
255             OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/'//myid_char,&
256                        FORM='UNFORMATTED', POSITION='APPEND' )
257          ENDIF
258
259       CASE ( 21 )
260
261          IF ( data_output_2d_on_each_pe )  THEN
262             OPEN ( 21, FILE='PLOT2D_XY'//TRIM( coupling_char )//myid_char, &
263                        FORM='UNFORMATTED', POSITION='APPEND' )
264          ELSE
265             OPEN ( 21, FILE='PLOT2D_XY'//coupling_char, &
266                        FORM='UNFORMATTED', POSITION='APPEND' )
267          ENDIF
268
269          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
270!
271!--          Output for combine_plot_fields
272             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
273                WRITE (21)  -1, nx+1, -1, ny+1    ! total array size
274                WRITE (21)   0, nx+1,  0, ny+1    ! output part
275             ENDIF
276!
277!--          Determine and write ISO2D coordiante header
278             ALLOCATE( eta(0:ny+1), ho(0:nx+1), hu(0:nx+1) )
279             hu = 0.0
280             ho = (ny+1) * dy
281             DO  i = 1, ny
282                eta(i) = REAL( i ) / ( ny + 1.0 )
283             ENDDO
284             eta(0)    = 0.0
285             eta(ny+1) = 1.0
286
287             WRITE (21)  dx,eta,hu,ho
288             DEALLOCATE( eta, ho, hu )
289
290!
291!--          Create output file for local parameters
292             IF ( iso2d_output )  THEN
293                OPEN ( 27, FILE='PLOT2D_XY_LOCAL'//coupling_char, &
294                           FORM='FORMATTED', DELIM='APOSTROPHE' )
295                openfile(27)%opened = .TRUE.
296             ENDIF
297
298          ENDIF
299
300       CASE ( 22 )
301
302          IF ( data_output_2d_on_each_pe )  THEN
303             OPEN ( 22, FILE='PLOT2D_XZ'//TRIM( coupling_char )//myid_char, &
304                        FORM='UNFORMATTED', POSITION='APPEND' )
305          ELSE
306             OPEN ( 22, FILE='PLOT2D_XZ'//coupling_char, FORM='UNFORMATTED', &
307                        POSITION='APPEND' )
308          ENDIF
309
310          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
311!
312!--          Output for combine_plot_fields
313             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
314                WRITE (22)  -1, nx+1, 0, nz+1    ! total array size
315                WRITE (22)   0, nx+1, 0, nz+1    ! output part
316             ENDIF
317!
318!--          Determine and write ISO2D coordiante header
319             ALLOCATE( eta(0:nz+1), ho(0:nx+1), hu(0:nx+1) )
320             hu = 0.0
321             ho = zu(nz+1)
322             DO  i = 1, nz
323                eta(i) = REAL( zu(i) ) / zu(nz+1)
324             ENDDO
325             eta(0)    = 0.0
326             eta(nz+1) = 1.0
327
328             WRITE (22)  dx,eta,hu,ho
329             DEALLOCATE( eta, ho, hu )
330!
331!--          Create output file for local parameters
332             OPEN ( 28, FILE='PLOT2D_XZ_LOCAL'//coupling_char, &
333                        FORM='FORMATTED', DELIM='APOSTROPHE' )
334             openfile(28)%opened = .TRUE.
335
336          ENDIF
337
338       CASE ( 23 )
339
340          IF ( data_output_2d_on_each_pe )  THEN
341             OPEN ( 23, FILE='PLOT2D_YZ'//TRIM( coupling_char )//myid_char, &
342                        FORM='UNFORMATTED', POSITION='APPEND' )
343          ELSE
344             OPEN ( 23, FILE='PLOT2D_YZ'//coupling_char, FORM='UNFORMATTED', &
345                        POSITION='APPEND' )
346          ENDIF
347
348          IF ( myid == 0  .AND.  .NOT. openfile(file_id)%opened_before )  THEN
349!
350!--          Output for combine_plot_fields
351             IF ( data_output_2d_on_each_pe  .AND.  myid_char /= '' )  THEN
352                WRITE (23)  -1, ny+1, 0, nz+1    ! total array size
353                WRITE (23)   0, ny+1, 0, nz+1    ! output part
354             ENDIF
355!
356!--          Determine and write ISO2D coordiante header
357             ALLOCATE( eta(0:nz+1), ho(0:ny+1), hu(0:ny+1) )
358             hu = 0.0
359             ho = zu(nz+1)
360             DO  i = 1, nz
361                eta(i) = REAL( zu(i) ) / zu(nz+1)
362             ENDDO
363             eta(0)    = 0.0
364             eta(nz+1) = 1.0
365
366             WRITE (23)  dx,eta,hu,ho
367             DEALLOCATE( eta, ho, hu )
368!
369!--          Create output file for local parameters
370             OPEN ( 29, FILE='PLOT2D_YZ_LOCAL'//coupling_char, &
371                        FORM='FORMATTED', DELIM='APOSTROPHE' )
372             openfile(29)%opened = .TRUE.
373
374          ENDIF
375
376       CASE ( 30 )
377
378          OPEN ( 30, FILE='PLOT3D_DATA'//TRIM( coupling_char )//myid_char, &
379                     FORM='UNFORMATTED' )
380!
381!--       Write coordinate file for AVS
382          IF ( myid == 0 )  THEN
383#if defined( __parallel )
384!
385!--          Specifications for combine_plot_fields
386             IF ( .NOT. do3d_compress )  THEN
387                WRITE ( 30 )  -1,nx+1,-1,ny+1,0,nz_do3d
388                WRITE ( 30 )  0,nx+1,0,ny+1,0,nz_do3d
389             ENDIF
390#endif
391!
392!--          Write coordinate file for AVS:
393!--          First determine file names (including cyle numbers) of AVS files on
394!--          target machine (to which the files are to be transferred).
395!--          Therefore path information has to be obtained first.
396             IF ( avs_output )  THEN
397                iaddres = LEN_TRIM( return_addres )
398                iusern  = LEN_TRIM( return_username )
399
400                OPEN ( 3, FILE='OUTPUT_FILE_CONNECTIONS', FORM='FORMATTED' )
401                DO  WHILE ( .NOT. avs_coor_file_found  .OR. &
402                            .NOT. avs_data_file_found )
403
404                   READ ( 3, '(A)', END=1 )  zeile
405
406                   SELECT CASE ( zeile(1:11) )
407
408                      CASE ( 'PLOT3D_COOR' )
409                         READ ( 3, '(A/A)' )  avs_coor_file_catalog, &
410                                              avs_coor_file_localname
411                         avs_coor_file_found = .TRUE.
412
413                      CASE ( 'PLOT3D_DATA' )
414                         READ ( 3, '(A/A)' )  avs_data_file_catalog, &
415                                              avs_data_file_localname
416                         avs_data_file_found = .TRUE.
417
418                      CASE DEFAULT
419                         READ ( 3, '(A/A)' )  zeile, zeile
420
421                   END SELECT
422
423                ENDDO
424!
425!--             Now the cycle numbers on the remote machine must be obtained
426!--             using batch_scp
427       1        CLOSE ( 3 )
428                IF ( .NOT. avs_coor_file_found  .OR. &
429                     .NOT. avs_data_file_found )  THEN
430                   message_string= 'no filename for AVS-data-file ' //       &
431                                   'found in MRUN-config-file' //            &
432                                   ' &filename in FLD-file set to "unknown"'
433                   CALL message( 'check_open', 'PA0169', 0, 1, 0, 6, 0 )
434
435                   avs_coor_file = 'unknown'
436                   avs_data_file = 'unknown'
437                ELSE
438                   get_filenames = .TRUE.
439                   IF ( TRIM( host ) == 'hpmuk'  .OR.  &
440                        TRIM( host ) == 'lcmuk' )  THEN
441                      batch_scp = '/home/raasch/pub/batch_scp'
442                   ELSEIF ( TRIM( host ) == 'nech' )  THEN
443                      batch_scp = '/ipf/b/b323011/pub/batch_scp'
444                   ELSEIF ( TRIM( host ) == 'ibmh'  .OR.  &
445                            TRIM( host ) == 'ibmb' )  THEN
446                      batch_scp = '/home/h/niksiraa/pub/batch_scp'
447                   ELSEIF ( TRIM( host ) == 't3eb' )  THEN
448                      batch_scp = '/home/nhbksira/pub/batch_scp'
449                   ELSE
450                      message_string= 'no path for batch_scp on host "' // &
451                                       TRIM( host ) // '"'
452                      CALL message( 'check_open', 'PA0170', 0, 1, 0, 6, 0 )
453                      get_filenames = .FALSE.
454                   ENDIF
455
456                   IF ( get_filenames )  THEN
457!
458!--                   Determine the coordinate file name.
459!--                   /etc/passwd serves as Dummy-Datei, because it is not
460!--                   really transferred.
461                      command = TRIM( batch_scp ) // ' -n -u ' // &
462                         return_username(1:iusern) // ' ' // &
463                         return_addres(1:iaddres) // ' /etc/passwd "' // &
464                         TRIM( avs_coor_file_catalog ) // '" ' // &
465                         TRIM( avs_coor_file_localname ) // ' > REMOTE_FILENAME'
466
467                      CALL local_system( command )
468                      OPEN ( 3, FILE='REMOTE_FILENAME', FORM='FORMATTED' )
469                      READ ( 3, '(A)' )  avs_coor_file
470                      CLOSE ( 3 )
471!
472!--                   Determine the data file name
473                      command = TRIM( batch_scp ) // ' -n -u ' // &
474                         return_username(1:iusern) // ' ' // &
475                         return_addres(1:iaddres) // ' /etc/passwd "' // &
476                         TRIM( avs_data_file_catalog ) // '" ' // &
477                         TRIM( avs_data_file_localname ) // ' > REMOTE_FILENAME'
478
479                      CALL local_system( command )
480                      OPEN ( 3, FILE='REMOTE_FILENAME', FORM='FORMATTED' )
481                      READ ( 3, '(A)' )  avs_data_file
482                      CLOSE ( 3 )
483
484                   ELSE
485
486                      avs_coor_file = 'unknown'
487                      avs_data_file = 'unknown'
488
489                   ENDIF
490
491                ENDIF
492
493!
494!--             Output of the coordinate file description for FLD-file
495                OPEN ( 33, FILE='PLOT3D_FLD_COOR', FORM='FORMATTED' )
496                openfile(33)%opened = .TRUE.
497                WRITE ( 33, 3300 )  TRIM( avs_coor_file ), &
498                                    TRIM( avs_coor_file ), (nx+2)*4, &
499                                    TRIM( avs_coor_file ), (nx+2)*4+(ny+2)*4
500           
501
502                ALLOCATE( xkoor(0:nx+1), ykoor(0:ny+1), zkoor(0:nz_do3d) )
503                DO  i = 0, nx+1
504                   xkoor(i) = i * dx
505                ENDDO
506                DO  j = 0, ny+1
507                   ykoor(j) = j * dy
508                ENDDO
509                DO  k = 0, nz_do3d
510                   zkoor(k) = zu(k)
511                ENDDO
512
513!
514!--             Create and write on AVS coordinate file
515                OPEN ( 31, FILE='PLOT3D_COOR', FORM='UNFORMATTED' )
516                openfile(31)%opened = .TRUE.
517
518                WRITE (31)  xkoor, ykoor, zkoor
519                DEALLOCATE( xkoor, ykoor, zkoor )
520
521!
522!--             Create FLD file (being written on in close_file)
523                OPEN ( 32, FILE='PLOT3D_FLD', FORM='FORMATTED' )
524                openfile(32)%opened = .TRUE.
525
526!
527!--             Create flag file for compressed 3D output,
528!--             influences output commands in mrun
529                IF ( do3d_compress )  THEN
530                   OPEN ( 3, FILE='PLOT3D_COMPRESSED', FORM='FORMATTED' )
531                   WRITE ( 3, '(1X)' )
532                   CLOSE ( 3 )
533                ENDIF
534
535             ENDIF
536
537          ENDIF
538
539!
540!--       In case of data compression output of the coordinates of the
541!--       corresponding partial array of a PE only once at the top of the file
542          IF ( avs_output  .AND.  do3d_compress )  THEN
543             WRITE ( 30 )  nxl-1, nxr+1, nys-1, nyn+1, nzb, nz_do3d
544          ENDIF
545
546       CASE ( 40:49 )
547
548          IF ( statistic_regions == 0  .AND.  file_id == 40 )  THEN
549             suffix = ''
550          ELSE
551             WRITE ( suffix, '(''_'',I1)' )  file_id - 40
552          ENDIF
553          OPEN ( file_id, FILE='PLOT1D_DATA'//TRIM( coupling_char )// &
554                               TRIM( suffix ),                        &
555                          FORM='FORMATTED' )
556!
557!--       Write contents comments at the top of the file
558          WRITE ( file_id, 4000 )  TRIM( run_description_header ) // '    ' // &
559                                   TRIM( region( file_id - 40 ) )
560
561       CASE ( 50:59 )
562
563          IF ( statistic_regions == 0  .AND.  file_id == 50 )  THEN
564             suffix = ''
565          ELSE
566             WRITE ( suffix, '(''_'',I1)' )  file_id - 50
567          ENDIF
568          OPEN ( file_id, FILE='PLOTTS_DATA'//TRIM( coupling_char )// &
569                               TRIM( suffix ),                        &
570                          FORM='FORMATTED', RECL=496 )
571!
572!--       Write PROFIL parameter file for output of time series
573!--       NOTE: To be on the safe side, this output is done at the beginning of
574!--             the model run (in case of collapse) and it is repeated in
575!--             close_file, then, however, with value ranges for the coordinate
576!--             systems
577!
578!--       Firstly determine the number of the coordinate systems to be drawn
579          cranz = 0
580          DO  j = 1, 10
581             IF ( cross_ts_number_count(j) /= 0 )  cranz = cranz+1
582          ENDDO
583          rtext = '\1.0 ' // TRIM( run_description_header ) // '    ' // &
584                  TRIM( region( file_id - 50 ) )
585!
586!--       Write RAHMEN parameter
587          OPEN ( 90, FILE='PLOTTS_PAR'//TRIM( coupling_char )// &
588                           TRIM( suffix ),                      &
589                     FORM='FORMATTED', DELIM='APOSTROPHE' )
590          WRITE ( 90, RAHMEN )
591!
592!--       Determine and write CROSS parameters for the individual coordinate
593!--       systems
594          DO  j = 1, 10
595             k = cross_ts_number_count(j)
596             IF ( k /= 0 )  THEN
597!
598!--             Store curve numbers, colours and line style
599                klist(1:k) = cross_ts_numbers(1:k,j)
600                klist(k+1:10) = 999999
601                cucol(1:k) = linecolors(1:k)
602                lstyle(1:k) = linestyles(1:k)
603!
604!--             Write CROSS parameter
605                WRITE ( 90, CROSS )
606
607             ENDIF
608          ENDDO
609
610          CLOSE ( 90 )
611!
612!--       Write all labels at the top of the data file, but only during the
613!--       first run of a sequence of jobs. The following jobs copy the time
614!--       series data to the bottom of that file.
615          IF ( runnr == 0 )  THEN
616             WRITE ( file_id, 5000 )  TRIM( run_description_header ) // &
617                                      '    ' // TRIM( region( file_id - 50 ) )
618          ENDIF
619
620
621       CASE ( 80 )
622
623          IF ( myid_char == '' )  THEN
624             OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM(coupling_char)//myid_char, &
625                        FORM='FORMATTED', POSITION='APPEND' )
626          ELSE
627             IF ( myid == 0  .AND.  .NOT. openfile(80)%opened_before )  THEN
628                CALL local_system( 'mkdir  PARTICLE_INFOS' // coupling_char )
629             ENDIF
630#if defined( __parallel )
631!
632!--          Set a barrier in order to allow that thereafter all other
633!--          processors in the directory created by PE0 can open their file.
634!--          WARNING: The following barrier will lead to hanging jobs, if
635!--                   check_open is first called from routine
636!--                   allocate_prt_memory!
637             IF ( .NOT. openfile(80)%opened_before )  THEN
638                CALL MPI_BARRIER( comm2d, ierr )
639             ENDIF
640#endif
641             OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM( coupling_char )//'/'// &
642                             myid_char,                                     &
643                        FORM='FORMATTED', POSITION='APPEND' )
644          ENDIF
645
646          IF ( .NOT. openfile(80)%opened_before )  THEN
647             WRITE ( 80, 8000 )  TRIM( run_description_header )
648          ENDIF
649
650       CASE ( 81 )
651
652             OPEN ( 81, FILE='PLOTSP_X_PAR'//coupling_char, FORM='FORMATTED', &
653                        DELIM='APOSTROPHE', RECL=1500, POSITION='APPEND' )
654
655       CASE ( 82 )
656
657             OPEN ( 82, FILE='PLOTSP_X_DATA'//coupling_char, FORM='FORMATTED', &
658                        POSITION = 'APPEND' )
659
660       CASE ( 83 )
661
662             OPEN ( 83, FILE='PLOTSP_Y_PAR'//coupling_char, FORM='FORMATTED', &
663                        DELIM='APOSTROPHE', RECL=1500, POSITION='APPEND' )
664
665       CASE ( 84 )
666
667             OPEN ( 84, FILE='PLOTSP_Y_DATA'//coupling_char, FORM='FORMATTED', &
668                        POSITION='APPEND' )
669
670       CASE ( 85 )
671
672          IF ( myid_char == '' )  THEN
673             OPEN ( 85, FILE='PARTICLE_DATA'//TRIM(coupling_char)//myid_char, &
674                        FORM='UNFORMATTED', POSITION='APPEND' )
675          ELSE
676             IF ( myid == 0  .AND.  .NOT. openfile(85)%opened_before )  THEN
677                CALL local_system( 'mkdir  PARTICLE_DATA' // coupling_char )
678             ENDIF
679#if defined( __parallel )
680!
681!--          Set a barrier in order to allow that thereafter all other
682!--          processors in the directory created by PE0 can open their file
683             CALL MPI_BARRIER( comm2d, ierr )
684#endif
685             OPEN ( 85, FILE='PARTICLE_DATA'//TRIM( coupling_char )//'/'// &
686                        myid_char,                                         &
687                        FORM='UNFORMATTED', POSITION='APPEND' )
688          ENDIF
689
690          IF ( .NOT. openfile(85)%opened_before )  THEN
691             WRITE ( 85 )  run_description_header
692!
693!--          Attention: change version number whenever the output format on
694!--                     unit 85 is changed (see also in routine advec_particles)
695             rtext = 'data format version 3.0'
696             WRITE ( 85 )  rtext
697             WRITE ( 85 )  number_of_particle_groups, &
698                           max_number_of_particle_groups
699             WRITE ( 85 )  particle_groups
700          ENDIF
701
702#if defined( __netcdf )
703       CASE ( 101, 111 )
704!
705!--       Set filename depending on unit number
706          IF ( file_id == 101 )  THEN
707             filename = 'DATA_2D_XY_NETCDF' // coupling_char
708             av = 0
709          ELSE
710             filename = 'DATA_2D_XY_AV_NETCDF' // coupling_char
711             av = 1
712          ENDIF
713!
714!--       Inquire, if there is a NetCDF file from a previuos run. This should
715!--       be opened for extension, if its dimensions and variables match the
716!--       actual run.
717          INQUIRE( FILE=filename, EXIST=netcdf_extend )
718
719          IF ( netcdf_extend )  THEN
720!
721!--          Open an existing NetCDF file for output
722#if defined( __netcdf4 )
723             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_xy(av), &
724                                  COMM = comm2d, INFO = MPI_INFO_NULL )
725#else
726             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_xy(av) )
727#endif
728
729             CALL handle_netcdf_error( 'check_open', 20 )
730!
731!--          Read header information and set all ids. If there is a mismatch
732!--          between the previuos and the actual run, netcdf_extend is returned
733!--          as .FALSE.
734             CALL define_netcdf_header( 'xy', netcdf_extend, av )
735
736!
737!--          Remove the local file, if it can not be extended
738             IF ( .NOT. netcdf_extend )  THEN
739                nc_stat = NF90_CLOSE( id_set_xy(av) )
740                CALL handle_netcdf_error( 'check_open', 21 )
741                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
742             ENDIF
743
744          ENDIF         
745
746          IF ( .NOT. netcdf_extend )  THEN
747!
748!--          Create a new NetCDF output file with requested NetCDF format
749             IF ( netcdf_data_format == 1 )  THEN
750!
751!--             Classic NetCDF format
752                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_xy(av) )
753
754             ELSEIF ( netcdf_data_format == 2 )  THEN
755!
756!--             64bit-offset format
757                nc_stat = NF90_CREATE( filename,                               &
758                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
759                                       id_set_xy(av) )
760
761#if defined( __netcdf4 )
762             ELSEIF ( netcdf_data_format == 3 )  THEN
763!
764!--             NetCDF4/HDF5 format
765                nc_stat = NF90_CREATE( filename,                               &
766                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
767                                       id_set_xy(av), COMM = comm2d,           &
768                                       INFO = MPI_INFO_NULL )
769
770             ELSEIF ( netcdf_data_format == 4 )  THEN
771!
772!--             NetCDF4/HDF5 format with classic model flag
773                nc_stat = NF90_CREATE( filename,                               &
774                                       OR( NF90_NOCLOBBER,                     &
775                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
776                                       id_set_xy(av), COMM = comm2d,           &
777                                       INFO = MPI_INFO_NULL )
778#endif
779             ENDIF
780
781             CALL handle_netcdf_error( 'check_open', 22 )
782
783!
784!--          Define the header
785             CALL define_netcdf_header( 'xy', netcdf_extend, av )
786
787!
788!--          In case of parallel NetCDF output, create flag file which tells
789!--          combine_plot_fields that nothing is to do.
790             IF ( myid == 0  .AND.  netcdf_data_format > 2 )  THEN
791                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_XY' )
792                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
793                CLOSE( 99 )
794             ENDIF
795
796          ENDIF
797
798       CASE ( 102, 112 )
799!
800!--       Set filename depending on unit number
801          IF ( file_id == 102 )  THEN
802             filename = 'DATA_2D_XZ_NETCDF' // coupling_char
803             av = 0
804          ELSE
805             filename = 'DATA_2D_XZ_AV_NETCDF' // coupling_char
806             av = 1
807          ENDIF
808!
809!--       Inquire, if there is a NetCDF file from a previuos run. This should
810!--       be opened for extension, if its dimensions and variables match the
811!--       actual run.
812          INQUIRE( FILE=filename, EXIST=netcdf_extend )
813
814          IF ( netcdf_extend )  THEN
815!
816!--          Open an existing NetCDF file for output
817#if defined( __netcdf4 )
818             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_xz(av), &
819                                  COMM = comm2d, INFO = MPI_INFO_NULL )
820#else
821             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_xz(av) )
822#endif
823             CALL handle_netcdf_error( 'check_open', 23 )
824!
825!--          Read header information and set all ids. If there is a mismatch
826!--          between the previuos and the actual run, netcdf_extend is returned
827!--          as .FALSE.
828             CALL define_netcdf_header( 'xz', netcdf_extend, av )
829
830!
831!--          Remove the local file, if it can not be extended
832             IF ( .NOT. netcdf_extend )  THEN
833                nc_stat = NF90_CLOSE( id_set_xz(av) )
834                CALL handle_netcdf_error( 'check_open', 24 )
835                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
836             ENDIF
837
838          ENDIF         
839
840          IF ( .NOT. netcdf_extend )  THEN
841!
842!--          Create a new NetCDF output file with requested NetCDF format
843             IF ( netcdf_data_format == 1 )  THEN
844!
845!--             Classic NetCDF format
846                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_xz(av) )
847
848             ELSEIF ( netcdf_data_format == 2 )  THEN
849!
850!--             64bit-offset format
851                nc_stat = NF90_CREATE( filename,                               &
852                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
853                                       id_set_xz(av) )
854
855#if defined( __netcdf4 )
856             ELSEIF ( netcdf_data_format == 3 )  THEN
857!
858!--             NetCDF4/HDF5 format
859                nc_stat = NF90_CREATE( filename,                               &
860                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
861                                       id_set_xz(av), COMM = comm2d,           &
862                                       INFO = MPI_INFO_NULL )
863
864             ELSEIF ( netcdf_data_format == 4 )  THEN
865!
866!--             NetCDF4/HDF5 format with classic model flag
867                nc_stat = NF90_CREATE( filename,                               &
868                                       OR( NF90_NOCLOBBER,                     &
869                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
870                                       id_set_xz(av), COMM = comm2d,           &
871                                       INFO = MPI_INFO_NULL )
872#endif
873             ENDIF
874
875             CALL handle_netcdf_error( 'check_open', 25 )
876
877!
878!--          Define the header
879             CALL define_netcdf_header( 'xz', netcdf_extend, av )
880
881!
882!--          In case of parallel NetCDF output, create flag file which tells
883!--          combine_plot_fields that nothing is to do.
884             IF ( myid == 0  .AND.  netcdf_data_format > 2 )  THEN
885                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_XZ' )
886                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
887                CLOSE( 99 )
888             ENDIF
889
890          ENDIF
891
892       CASE ( 103, 113 )
893!
894!--       Set filename depending on unit number
895          IF ( file_id == 103 )  THEN
896             filename = 'DATA_2D_YZ_NETCDF' // coupling_char
897             av = 0
898          ELSE
899             filename = 'DATA_2D_YZ_AV_NETCDF' // coupling_char
900             av = 1
901          ENDIF
902!
903!--       Inquire, if there is a NetCDF file from a previuos run. This should
904!--       be opened for extension, if its dimensions and variables match the
905!--       actual run.
906          INQUIRE( FILE=filename, EXIST=netcdf_extend )
907
908          IF ( netcdf_extend )  THEN
909!
910!--          Open an existing NetCDF file for output
911#if defined( __netcdf4 )
912             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_yz(av), &
913                                  COMM = comm2d, INFO = MPI_INFO_NULL )
914#else
915             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_yz(av) )
916#endif
917             CALL handle_netcdf_error( 'check_open', 26 )
918!
919!--          Read header information and set all ids. If there is a mismatch
920!--          between the previuos and the actual run, netcdf_extend is returned
921!--          as .FALSE.
922             CALL define_netcdf_header( 'yz', netcdf_extend, av )
923
924!
925!--          Remove the local file, if it can not be extended
926             IF ( .NOT. netcdf_extend )  THEN
927                nc_stat = NF90_CLOSE( id_set_yz(av) )
928                CALL handle_netcdf_error( 'check_open', 27 )
929                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
930             ENDIF
931
932          ENDIF         
933
934          IF ( .NOT. netcdf_extend )  THEN
935!
936!--          Create a new NetCDF output file with requested NetCDF format
937             IF ( netcdf_data_format == 1 )  THEN
938!
939!--             Classic NetCDF format
940                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_yz(av) )
941
942             ELSEIF ( netcdf_data_format == 2 )  THEN
943!
944!--             64bit-offset format
945                nc_stat = NF90_CREATE( filename,                               &
946                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
947                                       id_set_yz(av) )
948
949#if defined( __netcdf4 )
950             ELSEIF ( netcdf_data_format == 3 )  THEN
951!
952!--             NetCDF4/HDF5 format
953                nc_stat = NF90_CREATE( filename,                               &
954                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
955                                       id_set_yz(av), COMM = comm2d,           &
956                                       INFO = MPI_INFO_NULL )
957
958             ELSEIF ( netcdf_data_format == 4 )  THEN
959!
960!--             NetCDF4/HDF5 format with classic model flag
961                nc_stat = NF90_CREATE( filename,                               &
962                                       OR( NF90_NOCLOBBER,                     &
963                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
964                                       id_set_yz(av), COMM = comm2d,           &
965                                       INFO = MPI_INFO_NULL )
966#endif
967             ENDIF
968
969             CALL handle_netcdf_error( 'check_open', 28 )
970
971!
972!--          Define the header
973             CALL define_netcdf_header( 'yz', netcdf_extend, av )
974
975!
976!--          In case of parallel NetCDF output, create flag file which tells
977!--          combine_plot_fields that nothing is to do.
978             IF ( myid == 0  .AND.  netcdf_data_format > 2 )  THEN
979                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_YZ' )
980                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
981                CLOSE( 99 )
982             ENDIF
983
984          ENDIF
985
986       CASE ( 104 )
987!
988!--       Set filename
989          filename = 'DATA_1D_PR_NETCDF' // coupling_char
990
991!
992!--       Inquire, if there is a NetCDF file from a previuos run. This should
993!--       be opened for extension, if its variables match the actual run.
994          INQUIRE( FILE=filename, EXIST=netcdf_extend )
995
996          IF ( netcdf_extend )  THEN
997!
998!--          Open an existing NetCDF file for output
999             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_pr )
1000             CALL handle_netcdf_error( 'check_open', 29 )
1001!
1002!--          Read header information and set all ids. If there is a mismatch
1003!--          between the previuos and the actual run, netcdf_extend is returned
1004!--          as .FALSE.
1005             CALL define_netcdf_header( 'pr', netcdf_extend, 0 )
1006
1007!
1008!--          Remove the local file, if it can not be extended
1009             IF ( .NOT. netcdf_extend )  THEN
1010                nc_stat = NF90_CLOSE( id_set_pr )
1011                CALL handle_netcdf_error( 'check_open', 30 )
1012                CALL local_system( 'rm ' // TRIM( filename ) )
1013             ENDIF
1014
1015          ENDIF         
1016
1017          IF ( .NOT. netcdf_extend )  THEN
1018!
1019!--          Create a new NetCDF output file
1020             IF ( netcdf_data_format > 1 )  THEN
1021                nc_stat = NF90_CREATE( filename,                               &
1022                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1023                                       id_set_pr )
1024             ELSE
1025                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_pr )
1026             ENDIF
1027             CALL handle_netcdf_error( 'check_open', 31 )
1028!
1029!--          Define the header
1030             CALL define_netcdf_header( 'pr', netcdf_extend, 0 )
1031
1032          ENDIF
1033
1034       CASE ( 105 )
1035!
1036!--       Set filename
1037          filename = 'DATA_1D_TS_NETCDF' // coupling_char
1038
1039!
1040!--       Inquire, if there is a NetCDF file from a previuos run. This should
1041!--       be opened for extension, if its variables match the actual run.
1042          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1043
1044          IF ( netcdf_extend )  THEN
1045!
1046!--          Open an existing NetCDF file for output
1047             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_ts )
1048             CALL handle_netcdf_error( 'check_open', 32 )
1049!
1050!--          Read header information and set all ids. If there is a mismatch
1051!--          between the previuos and the actual run, netcdf_extend is returned
1052!--          as .FALSE.
1053             CALL define_netcdf_header( 'ts', netcdf_extend, 0 )
1054
1055!
1056!--          Remove the local file, if it can not be extended
1057             IF ( .NOT. netcdf_extend )  THEN
1058                nc_stat = NF90_CLOSE( id_set_ts )
1059                CALL handle_netcdf_error( 'check_open', 33 )
1060                CALL local_system( 'rm ' // TRIM( filename ) )
1061             ENDIF
1062
1063          ENDIF         
1064
1065          IF ( .NOT. netcdf_extend )  THEN
1066!
1067!--          Create a new NetCDF output file
1068             IF ( netcdf_data_format > 1 )  THEN
1069                nc_stat = NF90_CREATE( filename,                               &
1070                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1071                                       id_set_ts )
1072             ELSE
1073                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_ts )
1074             ENDIF
1075             CALL handle_netcdf_error( 'check_open', 34 )
1076!
1077!--          Define the header
1078             CALL define_netcdf_header( 'ts', netcdf_extend, 0 )
1079
1080          ENDIF
1081
1082
1083       CASE ( 106, 116 )
1084!
1085!--       Set filename depending on unit number
1086          IF ( file_id == 106 )  THEN
1087             filename = 'DATA_3D_NETCDF' // coupling_char
1088             av = 0
1089          ELSE
1090             filename = 'DATA_3D_AV_NETCDF' // coupling_char
1091             av = 1
1092          ENDIF
1093!
1094!--       Inquire, if there is a NetCDF file from a previous run. This should
1095!--       be opened for extension, if its dimensions and variables match the
1096!--       actual run.
1097          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1098
1099          IF ( netcdf_extend )  THEN
1100!
1101!--          Open an existing NetCDF file for output
1102#if defined( __netcdf4 )
1103             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_3d(av), &
1104                                  COMM = comm2d, INFO = MPI_INFO_NULL )
1105#else
1106             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_3d(av) )
1107#endif
1108             CALL handle_netcdf_error( 'check_open', 35 )
1109!
1110!--          Read header information and set all ids. If there is a mismatch
1111!--          between the previuos and the actual run, netcdf_extend is returned
1112!--          as .FALSE.
1113             CALL define_netcdf_header( '3d', netcdf_extend, av )
1114
1115!
1116!--          Remove the local file, if it can not be extended
1117             IF ( .NOT. netcdf_extend )  THEN
1118                nc_stat = NF90_CLOSE( id_set_3d(av) )
1119                CALL handle_netcdf_error( 'check_open', 36 )
1120                CALL local_system('rm ' // TRIM( filename ) )
1121             ENDIF
1122
1123          ENDIF         
1124
1125          IF ( .NOT. netcdf_extend )  THEN
1126!
1127!--          Create a new NetCDF output file with requested NetCDF format
1128             IF ( netcdf_data_format == 1 )  THEN
1129!
1130!--             Classic NetCDF format
1131                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_3d(av) )
1132
1133             ELSEIF ( netcdf_data_format == 2 )  THEN
1134!
1135!--             64bit-offset format
1136                nc_stat = NF90_CREATE( filename,                               &
1137                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1138                                       id_set_3d(av) )
1139
1140#if defined( __netcdf4 )
1141             ELSEIF ( netcdf_data_format == 3 )  THEN
1142!
1143!--             NetCDF4/HDF5 format
1144                nc_stat = NF90_CREATE( filename,                               &
1145                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
1146                                       id_set_3d(av), COMM = comm2d,           &
1147                                       INFO = MPI_INFO_NULL )
1148
1149             ELSEIF ( netcdf_data_format == 4 )  THEN
1150!
1151!--             NetCDF4/HDF5 format with classic model flag
1152                nc_stat = NF90_CREATE( filename,                               &
1153                                       OR( NF90_NOCLOBBER,                     &
1154                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
1155                                       id_set_3d(av), COMM = comm2d,           &
1156                                       INFO = MPI_INFO_NULL )
1157#endif
1158             ENDIF
1159
1160             CALL handle_netcdf_error( 'check_open', 37 )
1161
1162!
1163!--          Define the header
1164             CALL define_netcdf_header( '3d', netcdf_extend, av )
1165
1166!
1167!--          In case of parallel NetCDF output, create flag file which tells
1168!--          combine_plot_fields that nothing is to do.
1169             IF ( myid == 0  .AND.  netcdf_data_format > 2 )  THEN
1170                OPEN( 99, FILE='NO_COMBINE_PLOT_FIELDS_3D' )
1171                WRITE ( 99, '(A)' )  'no combine_plot_fields.x neccessary'
1172                CLOSE( 99 )
1173             ENDIF
1174
1175          ENDIF
1176
1177
1178       CASE ( 107 )
1179!
1180!--       Set filename
1181          filename = 'DATA_1D_SP_NETCDF' // coupling_char
1182
1183!
1184!--       Inquire, if there is a NetCDF file from a previuos run. This should
1185!--       be opened for extension, if its variables match the actual run.
1186          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1187
1188          IF ( netcdf_extend )  THEN
1189!
1190!--          Open an existing NetCDF file for output
1191             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_sp )
1192             CALL handle_netcdf_error( 'check_open', 38 )
1193
1194!
1195!--          Read header information and set all ids. If there is a mismatch
1196!--          between the previuos and the actual run, netcdf_extend is returned
1197!--          as .FALSE.
1198             CALL define_netcdf_header( 'sp', netcdf_extend, 0 )
1199
1200!
1201!--          Remove the local file, if it can not be extended
1202             IF ( .NOT. netcdf_extend )  THEN
1203                nc_stat = NF90_CLOSE( id_set_sp )
1204                CALL handle_netcdf_error( 'check_open', 39 )
1205                CALL local_system( 'rm ' // TRIM( filename ) )
1206             ENDIF
1207
1208          ENDIF         
1209
1210          IF ( .NOT. netcdf_extend )  THEN
1211!
1212!--          Create a new NetCDF output file
1213             IF ( netcdf_data_format > 1 )  THEN
1214                nc_stat = NF90_CREATE( filename,                               &
1215                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1216                                       id_set_sp )
1217             ELSE
1218                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_sp )
1219             ENDIF
1220             CALL handle_netcdf_error( 'check_open', 40 )
1221!
1222!--          Define the header
1223             CALL define_netcdf_header( 'sp', netcdf_extend, 0 )
1224
1225          ENDIF
1226
1227
1228       CASE ( 108 )
1229
1230          IF ( myid_char == '' )  THEN
1231             filename = 'DATA_PRT_NETCDF' // coupling_char
1232          ELSE
1233             filename = 'DATA_PRT_NETCDF' // TRIM( coupling_char ) // '/' // &
1234                        myid_char
1235          ENDIF
1236!
1237!--       Inquire, if there is a NetCDF file from a previuos run. This should
1238!--       be opened for extension, if its variables match the actual run.
1239          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1240
1241          IF ( netcdf_extend )  THEN
1242!
1243!--          Open an existing NetCDF file for output
1244             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_prt )
1245             CALL handle_netcdf_error( 'check_open', 41 )
1246!
1247!--          Read header information and set all ids. If there is a mismatch
1248!--          between the previuos and the actual run, netcdf_extend is returned
1249!--          as .FALSE.
1250             CALL define_netcdf_header( 'pt', netcdf_extend, 0 )
1251
1252!
1253!--          Remove the local file, if it can not be extended
1254             IF ( .NOT. netcdf_extend )  THEN
1255                nc_stat = NF90_CLOSE( id_set_prt )
1256                CALL handle_netcdf_error( 'check_open', 42 )
1257                CALL local_system( 'rm ' // filename )
1258             ENDIF
1259
1260          ENDIF         
1261
1262          IF ( .NOT. netcdf_extend )  THEN
1263
1264!
1265!--          For runs on multiple processors create the subdirectory
1266             IF ( myid_char /= '' )  THEN
1267                IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before ) &
1268                THEN    ! needs modification in case of non-extendable sets
1269                   CALL local_system( 'mkdir  DATA_PRT_NETCDF' // &
1270                                       TRIM( coupling_char ) // '/' )
1271                ENDIF
1272#if defined( __parallel )
1273!
1274!--             Set a barrier in order to allow that all other processors in the
1275!--             directory created by PE0 can open their file
1276                CALL MPI_BARRIER( comm2d, ierr )
1277#endif
1278             ENDIF
1279
1280!
1281!--          Create a new NetCDF output file with requested NetCDF format
1282             IF ( netcdf_data_format == 1 )  THEN
1283!
1284!--             Classic NetCDF format
1285                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_prt )
1286
1287             ELSEIF ( netcdf_data_format == 2 )  THEN
1288!
1289!--             64bit-offset format
1290                nc_stat = NF90_CREATE( filename,                               &
1291                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1292                                       id_set_prt )
1293
1294#if defined( __netcdf4 )
1295             ELSEIF ( netcdf_data_format == 3 )  THEN
1296!
1297!--             NetCDF4/HDF5 format, but no parallel output into a single file!
1298                nc_stat = NF90_CREATE( filename,                               &
1299                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
1300                                       id_set_prt )
1301
1302             ELSEIF ( netcdf_data_format == 4 )  THEN
1303!
1304!--             NetCDF4/HDF5 format with classic model flag, but no parallel
1305!--             output into a single file!
1306                nc_stat = NF90_CREATE( filename,                               &
1307                                       OR( NF90_NOCLOBBER,                     &
1308                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
1309                                       id_set_prt )
1310#endif
1311             ENDIF
1312
1313             CALL handle_netcdf_error( 'check_open', 43 ) 
1314
1315!
1316!--          Define the header
1317             CALL define_netcdf_header( 'pt', netcdf_extend, 0 )
1318
1319          ENDIF
1320
1321       CASE ( 109 )
1322!
1323!--       Set filename
1324          filename = 'DATA_1D_PTS_NETCDF' // coupling_char
1325
1326!
1327!--       Inquire, if there is a NetCDF file from a previuos run. This should
1328!--       be opened for extension, if its variables match the actual run.
1329          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1330
1331          IF ( netcdf_extend )  THEN
1332!
1333!--          Open an existing NetCDF file for output
1334             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_pts )
1335             CALL handle_netcdf_error( 'check_open', 393 )
1336!
1337!--          Read header information and set all ids. If there is a mismatch
1338!--          between the previuos and the actual run, netcdf_extend is returned
1339!--          as .FALSE.
1340             CALL define_netcdf_header( 'ps', netcdf_extend, 0 )
1341
1342!
1343!--          Remove the local file, if it can not be extended
1344             IF ( .NOT. netcdf_extend )  THEN
1345                nc_stat = NF90_CLOSE( id_set_pts )
1346                CALL handle_netcdf_error( 'check_open', 394 )
1347                CALL local_system( 'rm ' // TRIM( filename ) )
1348             ENDIF
1349
1350          ENDIF         
1351
1352          IF ( .NOT. netcdf_extend )  THEN
1353!
1354!--          Create a new NetCDF output file
1355             IF ( netcdf_data_format > 1 )  THEN
1356                nc_stat = NF90_CREATE( filename,                               &
1357                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1358                                       id_set_pts )
1359             ELSE
1360                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id_set_pts )
1361             ENDIF
1362             CALL handle_netcdf_error( 'check_open', 395 )
1363!
1364!--          Define the header
1365             CALL define_netcdf_header( 'ps', netcdf_extend, 0 )
1366
1367          ENDIF
1368
1369       CASE ( 201:200+2*max_masks )
1370!
1371!--       Set filename depending on unit number
1372          IF ( file_id <= 200+max_masks )  THEN
1373             mid = file_id - 200
1374             WRITE ( mask_char,'(I2.2)')  mid
1375             filename = 'DATA_MASK_' // mask_char // '_NETCDF' // coupling_char
1376             av = 0
1377          ELSE
1378             mid = file_id - (200+max_masks)
1379             WRITE ( mask_char,'(I2.2)')  mid
1380             filename = 'DATA_MASK_' // mask_char // '_AV_NETCDF' // &
1381                  coupling_char
1382             av = 1
1383          ENDIF
1384!
1385!--       Inquire, if there is a NetCDF file from a previuos run. This should
1386!--       be opened for extension, if its dimensions and variables match the
1387!--       actual run.
1388          INQUIRE( FILE=filename, EXIST=netcdf_extend )
1389
1390          IF ( netcdf_extend )  THEN
1391!
1392!--          Open an existing NetCDF file for output
1393#if defined( __netcdf4 )
1394             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_mask(mid,av), &
1395                                  COMM = comm2d, INFO = MPI_INFO_NULL )
1396#else
1397             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_mask(mid,av) )
1398#endif
1399             CALL handle_netcdf_error( 'check_open', 456 )
1400!
1401!--          Read header information and set all ids. If there is a mismatch
1402!--          between the previuos and the actual run, netcdf_extend is returned
1403!--          as .FALSE.
1404             CALL define_netcdf_header( 'ma', netcdf_extend, file_id )
1405
1406!
1407!--          Remove the local file, if it can not be extended
1408             IF ( .NOT. netcdf_extend )  THEN
1409                nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
1410                CALL handle_netcdf_error( 'check_open', 457 )
1411                CALL local_system('rm ' // TRIM( filename ) )
1412             ENDIF
1413
1414          ENDIF         
1415
1416          IF ( .NOT. netcdf_extend )  THEN
1417!
1418!--          Create a new NetCDF output file with requested NetCDF format
1419             IF ( netcdf_data_format == 1 )  THEN
1420!
1421!--             Classic NetCDF format
1422                nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, &
1423                                       id_set_mask(mid,av) )
1424
1425             ELSEIF ( netcdf_data_format == 2 )  THEN
1426!
1427!--             64bit-offset format
1428                nc_stat = NF90_CREATE( filename,                               &
1429                                       OR( NF90_NOCLOBBER, NF90_64BIT_OFFSET ),&
1430                                       id_set_mask(mid,av) )
1431
1432
1433#if defined( __netcdf4 )
1434             ELSEIF ( netcdf_data_format == 3 )  THEN
1435!
1436!--             NetCDF4/HDF5 format
1437                nc_stat = NF90_CREATE( filename,                               &
1438                                       OR( NF90_NOCLOBBER, NF90_NETCDF4 ),     &
1439                                       id_set_mask(mid,av), COMM = comm2d,     &
1440                                       INFO = MPI_INFO_NULL )
1441
1442             ELSEIF ( netcdf_data_format == 4 )  THEN
1443!
1444!--             NetCDF4/HDF5 format with classic model flag
1445                nc_stat = NF90_CREATE( filename,                               &
1446                                       OR( NF90_NOCLOBBER,                     &
1447                                        OR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), &
1448                                       id_set_mask(mid,av), COMM = comm2d,     &
1449                                       INFO = MPI_INFO_NULL )
1450#endif
1451             ENDIF
1452
1453             CALL handle_netcdf_error( 'check_open', 458 )
1454!
1455!--          Define the header
1456             CALL define_netcdf_header( 'ma', netcdf_extend, file_id )
1457
1458          ENDIF
1459
1460
1461#else
1462
1463       CASE ( 101:109, 111:113, 116, 201:200+2*max_masks )
1464
1465!
1466!--       Nothing is done in case of missing netcdf support
1467          RETURN
1468
1469#endif
1470
1471       CASE DEFAULT
1472
1473          WRITE( message_string, * ) 'no OPEN-statement for file-id ',file_id
1474          CALL message( 'check_open', 'PA0172', 2, 2, -1, 6, 1 )
1475
1476    END SELECT
1477
1478!
1479!-- Set open flag
1480    openfile(file_id)%opened = .TRUE.
1481
1482!
1483!-- Formats
14843300 FORMAT ('#'/                                                   &
1485             'coord 1  file=',A,'  filetype=unformatted'/           &
1486             'coord 2  file=',A,'  filetype=unformatted  skip=',I6/ &
1487             'coord 3  file=',A,'  filetype=unformatted  skip=',I6/ &
1488             '#')
14894000 FORMAT ('# ',A)
14905000 FORMAT ('# ',A/                                                          &
1491             '#1 E'/'#2 E*'/'#3 dt'/'#4 u*'/'#5 th*'/'#6 umax'/'#7 vmax'/     &
1492             '#8 wmax'/'#9 div_new'/'#10 div_old'/'#11 z_i_wpt'/'#12 z_i_pt'/ &
1493             '#13 w*'/'#14 w''pt''0'/'#15 w''pt'''/'#16 wpt'/'#17 pt(0)'/     &
1494             '#18 pt(zp)'/'#19 splptx'/'#20 splpty'/'#21 splptz')
14958000 FORMAT (A/                                                            &
1496             '  step    time  # of parts   lPE sent/recv  rPE sent/recv  ',&
1497             'sPE sent/recv  nPE sent/recv  max # of parts'/               &
1498             103('-'))
1499
1500 END SUBROUTINE check_open
Note: See TracBrowser for help on using the repository browser.