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

Last change on this file since 601 was 601, checked in by raasch, 13 years ago

last commit documented

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