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

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

New:
---

particle reflection from vertical walls implemented, particle SGS model adjusted to walls

Wall functions for vertical walls now include diabatic conditions. New subroutines wall_fluxes, wall_fluxes_e. New 4D-array rif_wall.

new d3par-parameter netcdf_64bit_3d to switch on 64bit offset only for 3D files

new d3par-parameter dt_max to define the maximum value for the allowed timestep

new inipar-parameter loop_optimization to control the loop optimization method

new inipar-parameter pt_refrence. If given, this value is used as the reference that in buoyancy terms (otherwise, the instantaneous horizontally averaged temperature is used).

new user interface user_advec_particles

new initializing action "by_user" calls user_init_3d_model and allows the initial setting of all 3d arrays

topography height informations are stored on arrays zu_s_inner and zw_w_inner and output to the 2d/3d NetCDF files

samples added to the user interface which show how to add user-define time series quantities.

calculation/output of precipitation amount, precipitation rate and z0 (by setting "pra*", "prr*", "z0*" with data_output). The time interval on which the precipitation amount is defined is set by new d3par-parameter precipitation_amount_interval

unit 9 opened for debug output (file DEBUG_<pe#>)

Makefile, advec_particles, average_3d_data, buoyancy, calc_precipitation, check_open, check_parameters, data_output_2d, diffusion_e, diffusion_u, diffusion_v, diffusion_w, diffusivities, header, impact_of_latent_heat, init_particles, init_3d_model, modules, netcdf, parin, production_e, read_var_list, read_3d_binary, sum_up_3d_data, user_interface, write_var_list, write_3d_binary

New: wall_fluxes

Changed:


General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, volume flow control is added for the outflow boundary (currently only for the north boundary!!), additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d

The FFT-method for solving the Poisson-equation is now working with Neumann boundary conditions both at the bottom and the top. This requires adjustments of the tridiagonal coefficients and subtracting the horizontally averaged mean from the vertical velocity field.

+age_m in particle_type

Particles-package is now part of the default code ("-p particles" is not needed any more).

Move call of user_actions( 'after_integration' ) below increment of times
and counters. user_actions is now called for each statistic region and has as an argument the number of the respective region (sr)

d3par-parameter data_output_ts removed. Timeseries output for "profil" removed. Timeseries are now switched on by dt_dots. Timeseries data is collected in flow_statistics.

Initial velocities at nzb+1 are regarded for volume flow control in case they have been set zero before (to avoid small timesteps); see new internal parameters u/v_nzb_p1_for_vfc.

q is not allowed to become negative (prognostic_equations).

poisfft_init is only called if fft-solver is switched on (init_pegrid).

d3par-parameter moisture renamed to humidity.

Subversion global revision number is read from mrun and added to the run description header and to the run control (_rc) file.

vtk directives removed from main program.

The uitility routine interpret_config reads PALM environment variables from NAMELIST instead using the system call GETENV.

advec_u_pw, advec_u_up, advec_v_pw, advec_v_up, asselin_filter, check_parameters, coriolis, data_output_dvrp, data_output_ptseries, data_output_ts, data_output_2d, data_output_3d, diffusion_u, diffusion_v, exchange_horiz, exchange_horiz_2d, flow_statistics, header, init_grid, init_particles, init_pegrid, init_rankine, init_pt_anomaly, init_1d_model, init_3d_model, modules, palm, package_parin, parin, poisfft, poismg, prandtl_fluxes, pres, production_e, prognostic_equations, read_var_list, read_3d_binary, sor, swap_timelevel, time_integration, write_var_list, write_3d_binary

Errors:


Bugfix: preset of tendencies te_em, te_um, te_vm in init_1d_model

Bugfix in sample for reading user defined data from restart file (user_init)

Bugfix in setting diffusivities for cases with the outflow damping layer extending over more than one subdomain (init_3d_model)

Check for possible negative humidities in the initial humidity profile.

in Makefile, default suffixes removed from the suffix list to avoid calling of m2c in
# case of .mod files

Makefile
check_parameters, init_1d_model, init_3d_model, user_interface

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