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

Last change on this file since 809 was 809, checked in by maronga, 12 years ago

Bugfix: cpp directives .NOT., .AND. replaced by !,&&. Minor bugfixes in mrungui

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