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

Last change on this file since 766 was 766, checked in by raasch, 12 years ago

last commit documented

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