source: palm/tags/release-3.7/SOURCE/close_file.f90 @ 4095

Last change on this file since 4095 was 392, checked in by raasch, 15 years ago

New:
---

Adapted for machine lck
(mrun, mbuild, subjob)

bc_lr/bc_ns in most subroutines replaced by LOGICAL variables bc_lr_cyc,
bc_ns_cyc for speed optimization
(check_parameters, diffusion_u, diffusion_v, diffusion_w, modules)

Additional timestep criterion in case of simulations with plant canopy (timestep)

Check for illegal entries in section_xy|xz|yz that exceed nz+1|ny+1|nx+1
(check_parameters)

Clipping of dvrp output implemented. Default colourtable for particles
implemented, particle attributes (color, dvrp_size) can be set with new
parameters particle_color, particle_dvrpsize, color_interval,
dvrpsize_interval (init_dvrp, data_output_dvrp, modules, user_data_output_dvrp).
Slicer attributes (dvrp) are set with new routine set_slicer_attributes_dvrp
and are controlled with existing parameters slicer_range_limits.
(set_slicer_attributes_dvrp)

Ocean atmosphere coupling allows to use independent precursor runs in order
to account for different spin-up times. The time when coupling has to be
started is given by new inipar parameter coupling_start_time. The precursor
ocean run has to be started using new mrun option "-y" in order to add
appendix "_O" to all output files.
(check_for_restart, check_parameters, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, header, init_coupling, modules, mrun,
parin, read_var_list, surface_coupler, time_integration, write_var_list)

Polygon reduction for topography and ground plate isosurface. Reduction level
for buildings can be chosen with parameter cluster_size. (init_dvrp)

External pressure gradient (check_parameters, header, init_3d_model, modules,
parin, prognostic_equations, read_var_list, write_var_list)

New topography case 'single_street_canyon' (header, init_grid, modules, parin,
read_var_list, user_check_parameters, user_header, user_init_grid, write_var_list)

Option to predefine a target bulk velocity for conserve_volume_flow
(check_parameters, header, init_3d_model, modules, parin, read_var_list,
write_var_list)

Option for user defined 2D data output in xy cross sections at z=nzb+1
(data_output_2d, user_data_output_2d)

xy cross section output of surface heatfluxes (latent, sensible)
(average_3d_data, check_parameters, data_output_2d, modules, read_3d_binary,
sum_up_3d_data, write_3d_binary)

average_3d_data, check_for_restart, check_parameters, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, init_coupling, init_dvrp, init_grid, init_3d_model, header, mbuild, modules, mrun, package_parin, parin, prognostic_equations, read_3d_binary, read_var_list, subjob, surface_coupler, timestep, time_integration, user_check_parameters, user_data_output_2d, user_data_output_dvrp, user_header, user_init_grid, write_3d_binary, write_var_list

New: set_particle_attributes, set_slicer_attributes_dvrp

Changed:


lcmuk changed to lc to avoid problems with Intel compiler on sgi-ice
(poisfft)

For extended NetCDF files, the updated title attribute includes an update of
time_average_text where appropriate. (netcdf)

In case of restart runs without extension, initial profiles are not written
to NetCDF-file anymore. (data_output_profiles, modules, read_var_list, write_var_list)

Small change in formatting of the message handling routine concering the output in the
job protocoll. (message)

initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now
independent of turbulent_inflow (check_parameters, header, init_3d_model)

2 NetCDF error numbers changed. (data_output_3d)

A Link to the website appendix_a.html is printed for further information
about the possible errors. (message)

Temperature gradient criterion for estimating the boundary layer height
replaced by the gradient criterion of Sullivan et al. (1998). (flow_statistics)

NetCDF unit attribute in timeseries output in case of statistic regions added
(netcdf)

Output of NetCDF messages with aid of message handling routine.
(check_open, close_file, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, netcdf, output_particles_netcdf)

Output of messages replaced by message handling routine.
(advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart,
check_open, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp,
data_output_profiles, data_output_spectra, fft_xy, flow_statistics, header,
init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid,
netcdf, parin, plant_canopy_model, poisfft_hybrid, poismg, read_3d_binary,
read_var_list, surface_coupler, temperton_fft, timestep, user_actions,
user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy,
user_parin, user_read_restart_data, user_spectra )

Maximum number of tails is calculated from maximum number of particles and
skip_particles_for_tail (init_particles)

Value of vertical_particle_advection may differ for each particle group
(advec_particles, header, modules)

First constant in array den also defined as type double. (eqn_state_seawater)

Parameter dvrp_psize moved from particles_par to dvrp_graphics_par. (package_parin)

topography_grid_convention moved from userpar to inipar (check_parameters,
header, parin, read_var_list, user_check_parameters, user_header,
user_init_grid, user_parin, write_var_list)

Default value of grid_matching changed to strict.

Adjustments for runs on lcxt4 (necessary due to an software update on CRAY) and
for coupled runs on ibmy (mrun, subjob)

advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart, check_open, check_parameters, close_file, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, eqn_state_seawater, fft_xy, flow_statistics, header, init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid, message, mrun, netcdf, output_particles_netcdf, package_parin, parin, plant_canopy_model, poisfft, poisfft_hybrid, poismg, read_3d_binary, read_var_list, sort_particles, subjob, user_check_parameters, user_header, user_init_grid, user_parin, surface_coupler, temperton_fft, timestep, user_actions, user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy, user_parin, user_read_restart_data, user_spectra, write_var_list

Errors:


Bugfix: Initial hydrostatic pressure profile in case of ocean runs is now
calculated in 5 iteration steps. (init_ocean)

Bugfix: wrong sign in buoyancy production of ocean part in case of not using
the reference density (only in 3D routine production_e) (production_e)

Bugfix: output of averaged 2d/3d quantities requires that an avaraging
interval has been set, respective error message is included (check_parameters)

Bugfix: Output on unit 14 only if requested by write_binary.
(user_last_actions)

Bugfix to avoid zero division by km_neutral (production_e)

Bugfix for extended NetCDF files: In order to avoid 'data mode' errors if
updated attributes are larger than their original size, NF90_PUT_ATT is called
in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a
possible performance loss; an alternative strategy would be to ensure equal
attribute size in a job chain. (netcdf)

Bugfix: correction of initial volume flow for non-flat topography (init_3d_model)
Bugfix: zero initialization of arrays within buildings for 'cyclic_fill' (init_3d_model)

Bugfix: to_be_resorted => s_av for time-averaged scalars (data_output_2d, data_output_3d)

Bugfix: error in formatting the output (message)

Bugfix: avoid that ngp_2dh_s_inner becomes zero (init_3_model)

Typographical error: unit of wpt in dots_unit (modules)

Bugfix: error in check, if particles moved further than one subdomain length.
This check must not be applied for newly released particles. (advec_particles)

Bugfix: several tail counters are initialized, particle_tail_coordinates is
only written to file if its third index is > 0, arrays for tails are allocated
with a minimum size of 10 tails if there is no tail initially (init_particles,
advec_particles)

Bugfix: pressure included for profile output (check_parameters)

Bugfix: Type of count and count_rate changed to default INTEGER on NEC machines
(cpu_log)

Bugfix: output if particle time series only if particle advection is switched
on. (time_integration)

Bugfix: qsws was calculated in case of constant heatflux = .FALSE. (prandtl_fluxes)

Bugfix: averaging along z is not allowed for 2d quantities (e.g. u* and z0) (data_output_2d)

Typographical errors (netcdf)

If the inversion height calculated by the prerun is zero, inflow_damping_height
must be explicitly specified (init_3d_model)

Small bugfix concerning 3d 64bit netcdf output format (header)

Bugfix: dt_fixed removed from the restart file, because otherwise, no change
from a fixed to a variable timestep would be possible in restart runs.
(read_var_list, write_var_list)

Bugfix: initial setting of time_coupling in coupled restart runs (time_integration)

advec_particles, check_parameters, cpu_log, data_output_2d, data_output_3d, header, init_3d_model, init_particles, init_ocean, modules, netcdf, prandtl_fluxes, production_e, read_var_list, time_integration, user_last_actions, write_var_list

  • Property svn:keywords set to Id
File size: 19.3 KB
Line 
1 SUBROUTINE close_file( file_id )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: close_file.f90 392 2009-09-24 10:39:14Z knoop $
11!
12! 263 2009-03-18 12:26:04Z heinze
13! Output of NetCDF messages with aid of message handling routine.
14!
15! Feb. 2007
16! RCS Log replace by Id keyword, revision history cleaned up
17!
18! Revision 1.10  2006/08/22 13:50:01  raasch
19! xz and yz cross sections now up to nzt+1
20!
21! Revision 1.1  2001/01/02 17:23:41  raasch
22! Initial revision
23!
24! Last revision before renaming subroutine  2001/01/01  raasch
25! Subroutine name changed from close_files to close_file. Closing of a single
26! file is allowed by passing its file-id as an argument. Variable openfile now
27! is of type file_status and contains a flag which indicates if a file has
28! been opened before. Old revision remarks deleted.
29!
30! Revision 1.13 (close_files) 2000/12/20 09:10:24  letzel
31! All comments translated into English.
32!
33! Revision 1.12 (close_files) 1999/03/02 09:22:46  raasch
34! FLD-Header fuer komprimierte 3D-Daten
35!
36! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
37! Initial revision
38!
39!
40! Description:
41! ------------
42! Close specified file or all open files, if "0" has been given as the
43! calling argument. In that case, execute last actions for certain unit
44! numbers, if required.
45!------------------------------------------------------------------------------!
46
47    USE control_parameters
48    USE grid_variables
49    USE indices
50    USE netcdf_control
51    USE pegrid
52    USE profil_parameter
53    USE statistics
54
55    IMPLICIT NONE
56
57    CHARACTER (LEN=2)   ::  suffix
58    CHARACTER (LEN=10)  ::  datform = 'lit_endian'
59    CHARACTER (LEN=80)  ::  rtext, title, utext = '', xtext = '', ytext = ''
60
61    INTEGER ::  anzzeile, cranz, cross_count, cross_numbers, dimx, dimy, &
62                fid, file_id, j, k, legpos = 1, planz, timodex = 1
63    INTEGER, DIMENSION(100) ::  klist, lstyle, cucol
64
65    LOGICAL ::  checkuf = .TRUE., datleg = .TRUE., dp = .FALSE., &
66                grid = .TRUE., rand = .TRUE., swap, twoxa = .TRUE., &
67                twoya = .TRUE.
68
69    REAL    ::  ansx = -999.999, ansy = -999.999, gwid = 0.1, rlegfak, &
70                sizex, sizey, texfac, utmove = 50.0, uxmax, uxmin, uymax, &
71                uymin, yright
72    REAL, DIMENSION(100) ::  lwid, normx, normy
73
74    NAMELIST /CROSS/   ansx, ansy, cucol, grid, gwid, klist, legpos, lstyle, &
75                       lwid, normx, normy, rand, rlegfak, sizex, sizey, &
76                       texfac, timodex, twoxa, twoya, utext, utmove, uxmax, &
77                       uxmin, uymax, uymin, xtext, ytext
78    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dp, planz, sizex, sizey, &
79                       title, yright
80    NAMELIST /RAHMEN/  anzzeile, cranz, datleg, rtext, swap
81
82!
83!-- Close specified unit number (if opened) and set a flag that it has
84!-- been opened one time at least
85    IF ( file_id /= 0 )  THEN
86       IF ( openfile(file_id)%opened )  THEN
87          CLOSE ( file_id )
88          openfile(file_id)%opened        = .FALSE.
89          openfile(file_id)%opened_before = .TRUE.
90       ENDIF
91       RETURN
92    ENDIF
93
94!
95!-- Close all open unit numbers
96    DO  fid = 1, 116
97
98       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
99!
100!--       Last actions for certain unit numbers
101          SELECT CASE ( fid )
102
103             CASE ( 21 )
104!
105!--             Write ISO2D global parameters
106                IF ( myid == 0  .AND.  iso2d_output )  THEN
107                   planz  = do2d_xy_n
108                   dimx   = nx + 2
109                   dimy   = ny + 2
110                   sizex  = 100.0
111                   sizey  = 100.0
112                   title  = run_description_header
113                   yright = ( ny + 1.0 ) * dy
114                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
115                      checkuf = .FALSE.; dp = .TRUE.
116                   ENDIF
117                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
118                      datform = 'big_endian'
119                   ENDIF
120                   OPEN ( 90, FILE='PLOT2D_XY_GLOBAL', FORM='FORMATTED', &
121                              DELIM='APOSTROPHE' )
122                   WRITE ( 90, GLOBAL )
123                   CLOSE ( 90 )
124                ENDIF
125
126             CASE ( 22 )
127!
128!--             Write ISO2D global parameters
129                IF ( myid == 0 )  THEN
130                   planz  = do2d_xz_n
131                   dimx   = nx + 2
132                   dimy   = nz + 2
133                   sizex  = 100.0
134                   sizey  =  65.0
135                   title  = run_description_header
136                   yright = z_max_do2d
137                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
138                      checkuf = .FALSE.; dp = .TRUE.
139                   ENDIF
140                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
141                      datform = 'big_endian'
142                   ENDIF
143                   OPEN ( 90, FILE='PLOT2D_XZ_GLOBAL', FORM='FORMATTED', &
144                              DELIM='APOSTROPHE' )
145                   WRITE ( 90, GLOBAL )
146                   CLOSE ( 90 )
147                ENDIF
148
149             CASE ( 23 )
150!
151!--             Write ISO2D global parameters
152                IF ( myid == 0 )  THEN
153                   planz  = do2d_yz_n
154                   dimx   = ny + 2
155                   dimy   = nz + 2
156                   sizex  = 100.0
157                   sizey  =  65.0
158                   title  = run_description_header
159                   yright = z_max_do2d
160                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
161                      checkuf = .FALSE.; dp = .TRUE.
162                   ENDIF
163                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
164                      datform = 'big_endian'
165                   ENDIF
166                   OPEN ( 90, FILE='PLOT2D_YZ_GLOBAL', FORM='FORMATTED', &
167                              DELIM='APOSTROPHE' )
168                   WRITE ( 90, GLOBAL )
169                   CLOSE ( 90 )
170                ENDIF
171
172             CASE ( 32 )
173!
174!--             Write header for FLD-file
175                IF ( do3d_compress )  THEN
176                   WRITE ( 32, 3200)  ' compressed ',                       &
177                                      TRIM( run_description_header ), nx+2, &
178                                      ny+2, nz_do3d+1, do3d_avs_n
179                ELSE
180                   WRITE ( 32, 3200)  ' ', TRIM( run_description_header ), &
181                                      nx+2, ny+2, nz_do3d+1, do3d_avs_n
182                ENDIF
183
184             CASE ( 40:49 )
185!
186!--             Write PROFIL namelist parameters for 1D profiles.
187!--             First determine, how many crosses are to be drawn.
188                IF ( myid == 0 )  THEN
189                   cross_numbers = 0
190                   DO  j = 1, crmax
191                      IF ( cross_profile_number_count(j) /= 0 )  THEN
192                         cross_numbers = cross_numbers + 1
193                      ENDIF
194                   ENDDO
195
196                   IF ( cross_numbers /= 0 )  THEN
197!
198!--                   Determine remaining RAHMEN parameters
199                      swap = .FALSE.
200                      rtext = '\0.5 ' // TRIM( run_description_header ) // &
201                              '    ' // TRIM( region( fid - 40 ) )
202!
203!--                   Write RAHMEN parameters
204                      IF ( statistic_regions == 0  .AND.  fid == 40 )  THEN
205                         suffix = ''
206                      ELSE
207                         WRITE ( suffix, '(''_'',I1)' )  fid - 40
208                      ENDIF
209                      OPEN ( 90, FILE='PLOT1D_PAR' // TRIM( suffix ), &
210                                 FORM='FORMATTED', DELIM='APOSTROPHE' )
211!
212!--                   Subtitle for crosses with time averaging
213                      IF ( averaging_interval_pr /= 0.0 )  THEN
214                         WRITE ( utext, 4000 )  averaging_interval_pr
215                      ENDIF
216!
217!--                   Determine and write CROSS parameters for each individual
218!--                   cross
219                      cross_count = 0
220                      DO  j = 1, crmax
221                         k = cross_profile_number_count(j)
222                         IF ( k /= 0 )  THEN
223                            cross_count = cross_count + 1
224!
225!--                         Write RAHMEN parameters
226                            IF ( MOD( cross_count-1, &
227                                      profile_rows*profile_columns ) == 0 ) &
228                            THEN
229!
230!--                            Determine number of crosses still to be drawn
231                               cranz = MIN( cross_numbers - cross_count + 1, &
232                                            profile_rows * profile_columns )
233!
234!--                            If the first line cannot be filled with crosses
235!--                            completely, the default number of crosses per
236!--                            line has to be reduced.
237                               IF ( cranz < profile_columns )  THEN
238                                  anzzeile = cranz
239                               ELSE
240                                  anzzeile = profile_columns
241                               ENDIF
242
243                               WRITE ( 90, RAHMEN )
244
245                            ENDIF
246!
247!--                         Store graph numbers
248                            klist(1:k) = cross_profile_numbers(1:k,j)
249                            klist(k+1:100) = 999999
250!
251!--                         Store graph attributes
252                            cucol  = cross_linecolors(:,j)
253                            lstyle = cross_linestyles(:,j)
254                            lwid = 0.6
255!
256!--                         Sizes, text etc.
257                            sizex = 100.0; sizey = 120.0
258                            rlegfak = 0.7; texfac = 1.0
259!
260!--                         Determine range of x-axis values
261                            IF ( cross_normalized_x(j) == ' ' )  THEN
262!
263!--                            Non-normalized profiles
264                               IF ( cross_uxmin(j) == 0.0  .AND. &
265                                    cross_uxmax(j) == 0.0 )  THEN
266                                  uxmin = cross_uxmin_computed(j)
267                                  uxmax = cross_uxmax_computed(j)
268                                  IF ( uxmin == uxmax )  uxmax = uxmin + 1.0
269                               ELSE
270!
271!--                               Values set in check_parameters are used here
272                                  uxmin = cross_uxmin(j); uxmax = cross_uxmax(j)
273                               ENDIF
274                            ELSE
275!
276!--                            Normalized profiles
277                               IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
278                                    cross_uxmax_normalized(j) == 0.0 )  THEN
279                                  uxmin = cross_uxmin_normalized_computed(j)
280                                  uxmax = cross_uxmax_normalized_computed(j)
281                                  IF ( uxmin == uxmax )  uxmax = uxmin + 1.0
282                               ELSE
283!
284!--                               Values set in check_parameters are used here
285                                  uxmin = cross_uxmin_normalized(j)
286                                  uxmax = cross_uxmax_normalized(j)
287                               ENDIF
288                            ENDIF
289!
290!--                         Range of y-axis values
291!--                         may be re-adjusted during normalization if required
292                            uymin = cross_uymin(j); uymax = cross_uymax(j)
293                            ytext = 'height in m'
294!
295!--                         Normalization of the axes
296                            normx = cross_normx_factor(:,j)
297                            normy = cross_normy_factor(:,j)
298!
299!--                         Labelling of the axes
300                            IF ( cross_normalized_x(j) == ' ' )  THEN
301                               xtext = cross_xtext(j)
302                            ELSE
303                               xtext = TRIM( cross_xtext(j) ) // ' / ' // &
304                                       cross_normalized_x(j)
305                            ENDIF
306                            IF ( cross_normalized_y(j) == ' ' )  THEN
307                               ytext = 'height in m'
308                            ELSE
309                               ytext = 'height in m' // ' / ' // &
310                                       cross_normalized_y(j)
311!
312!--                            Determine upper limit of value range
313                               IF ( z_max_do1d_normalized /= -1.0 )  THEN
314                                  uymax = z_max_do1d_normalized
315                               ENDIF
316                            ENDIF
317
318                            WRITE ( 90, CROSS )
319
320                         ENDIF
321                      ENDDO
322
323                      CLOSE ( 90 )
324                   ENDIF
325                ENDIF
326
327             CASE ( 50:59 )
328!
329!--             Write PROFIL namelist parameters for time series
330!--             first determine number of crosses to be drawn
331                IF ( myid == 0 )  THEN
332                   cranz = 0
333                   DO  j = 1, 12
334                      IF ( cross_ts_number_count(j) /= 0 )  cranz = cranz+1
335                   ENDDO
336
337                   IF ( cranz /= 0 )  THEN
338!
339!--                   Determine RAHMEN parameters
340                      anzzeile = 1
341                      swap = .TRUE.
342                      rtext = '\1.0 ' // TRIM( run_description_header ) // &
343                              '    ' // TRIM( region( fid - 50 ) )
344!
345!--                   Write RAHMEN parameters
346                      IF ( statistic_regions == 0  .AND.  fid == 50 )  THEN
347                         suffix = ''
348                      ELSE
349                         WRITE ( suffix, '(''_'',I1)' )  fid - 50
350                      ENDIF
351                      OPEN ( 90, FILE='PLOTTS_PAR' // TRIM( suffix ), &
352                                 FORM='FORMATTED', DELIM='APOSTROPHE' )
353                      WRITE ( 90, RAHMEN )
354!
355!--                   Determine and write CROSS parameters for each individual
356!--                   cross
357                      DO  j = 1, 12
358                         k = cross_ts_number_count(j)
359                         IF ( k /= 0 )  THEN
360!
361!--                         Store graph numbers
362                            klist(1:k) = cross_ts_numbers(1:k,j)
363                            klist(k+1:100) = 999999
364!
365!--                         Store graph attributes
366                            cucol(1:k)  = linecolors(1:k)
367                            lstyle(1:k) = linestyles(1:k)
368                            lwid = 0.4
369!
370!--                         Sizes, text etc.
371                            sizex = 250.0; sizey = 40.0
372                            rlegfak = 1.5; texfac = 1.5
373                            xtext = 'time in s'
374                            ytext = ''
375                            utext = ''
376!
377!--                         Determine range of y-axis values
378                            IF ( cross_ts_uymin(j) == 999.999 )  THEN
379                               uymin = cross_ts_uymin_computed(j)
380                            ELSE
381                               uymin = cross_ts_uymin(j)
382                            ENDIF
383                            IF ( cross_ts_uymax(j) == 999.999 )  THEN
384                               uymax = cross_ts_uymax_computed(j)
385                            ELSE
386                               uymax = cross_ts_uymax(j)
387                            ENDIF
388                            IF ( uymin == uymax )  uymax = uymin + 1.0
389!
390!--                         Range of x-axis values
391                            uxmin = 0.0; uxmax = simulated_time
392!
393!--                         Normalizations
394                            normx = 1.0; normy = 1.0
395
396                            WRITE ( 90, CROSS )
397
398                         ENDIF
399                      ENDDO
400
401                      CLOSE ( 90 )
402                   ENDIF
403                ENDIF
404
405#if defined( __netcdf )
406             CASE ( 101 )
407
408                IF ( myid == 0  .AND.  netcdf_output )  THEN
409                   nc_stat = NF90_CLOSE( id_set_xy(0) )
410                   CALL handle_netcdf_error( 'close_file', 44 )
411                ENDIF
412
413             CASE ( 102 )
414
415                IF ( myid == 0  .AND.  netcdf_output )  THEN
416                   nc_stat = NF90_CLOSE( id_set_xz(0) )
417                   CALL handle_netcdf_error( 'close_file', 45 )
418                ENDIF
419
420             CASE ( 103 )
421
422                IF ( myid == 0  .AND.  netcdf_output )  THEN
423                   nc_stat = NF90_CLOSE( id_set_yz(0) )
424                   CALL handle_netcdf_error( 'close_file', 46 )
425                ENDIF
426
427             CASE ( 104 )
428
429                IF ( myid == 0  .AND.  netcdf_output )  THEN
430                   nc_stat = NF90_CLOSE( id_set_pr )
431                   CALL handle_netcdf_error( 'close_file', 47 )
432                ENDIF
433
434             CASE ( 105 )
435
436                IF ( myid == 0  .AND.  netcdf_output )  THEN
437                   nc_stat = NF90_CLOSE( id_set_ts )
438                   CALL handle_netcdf_error( 'close_file', 48 )
439                ENDIF
440
441             CASE ( 106 )
442
443                IF ( myid == 0  .AND.  netcdf_output )  THEN
444                   nc_stat = NF90_CLOSE( id_set_3d(0) )
445                   CALL handle_netcdf_error( 'close_file', 49 )
446                ENDIF
447
448             CASE ( 107 )
449
450                IF ( myid == 0  .AND.  netcdf_output )  THEN
451                   nc_stat = NF90_CLOSE( id_set_sp )
452                   CALL handle_netcdf_error( 'close_file', 50 )
453                ENDIF
454
455             CASE ( 108 )
456
457                IF (  netcdf_output )  THEN
458                   nc_stat = NF90_CLOSE( id_set_prt )
459                   CALL handle_netcdf_error( 'close_file', 51 )
460                ENDIF
461
462             CASE ( 109 ) 
463
464                IF (  netcdf_output )  THEN
465                   nc_stat = NF90_CLOSE( id_set_pts )
466                   CALL handle_netcdf_error( 'close_file', 412 )
467                ENDIF
468
469             CASE ( 111 )
470
471                IF ( myid == 0  .AND.  netcdf_output )  THEN
472                   nc_stat = NF90_CLOSE( id_set_xy(1) )
473                   CALL handle_netcdf_error( 'close_file', 52 )
474                ENDIF
475
476             CASE ( 112 )
477
478                IF ( myid == 0  .AND.  netcdf_output )  THEN
479                   nc_stat = NF90_CLOSE( id_set_xz(1) )
480                   CALL handle_netcdf_error( 'close_file', 352 )
481                ENDIF
482
483             CASE ( 113 )
484
485                IF ( myid == 0  .AND.  netcdf_output )  THEN
486                   nc_stat = NF90_CLOSE( id_set_yz(1) )
487                   CALL handle_netcdf_error( 'close_file', 353 )
488                ENDIF
489
490             CASE ( 116 )
491
492                IF ( myid == 0  .AND.  netcdf_output )  THEN
493                   nc_stat = NF90_CLOSE( id_set_3d(1) )
494                   CALL handle_netcdf_error( 'close_file', 353 )
495                ENDIF
496
497#endif
498
499          END SELECT
500!
501!--       Close file
502          IF ( openfile(fid)%opened )  CLOSE ( fid )
503
504       ENDIF
505
506    ENDDO
507
508!
509!-- Formats
5103200 FORMAT ('# AVS',A,'field file'/ &
511             '#'/                &
512             '# ',A/             &
513             'ndim=3'/           &
514             'dim1=',I5/         &
515             'dim2=',I5/         &
516             'dim3=',I5/         &
517             'nspace=3'/         &
518             'veclen=',I5/       &
519             'data=xdr_float'/   &
520             'field=rectilinear')
5214000 FORMAT ('time averaged over',F7.1,' s')
522
523
524 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.