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

Last change on this file since 143 was 143, checked in by raasch, 16 years ago

first preliminary update for turbulent inflow

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