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

Last change on this file since 807 was 807, checked in by maronga, 13 years ago

new utility check_namelist_files implemented

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