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

Last change on this file since 82 was 82, checked in by raasch, 17 years ago

vorlaeufige Standalone-Version fuer Linux-Cluster

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