source: palm/trunk/SOURCE/close_file.f90 @ 964

Last change on this file since 964 was 964, checked in by raasch, 12 years ago

old profil-parameters (cross_xtext, cross_normalized_x, etc. ) and respective code removed
(check_open, check_parameters, close_file, data_output_profiles, data_output_spectra, header, modules, parin)

reformatting (netcdf)

append feature removed from unit 14 (check_open)

  • Property svn:keywords set to Id
File size: 10.7 KB
Line 
1 SUBROUTINE close_file( file_id )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! old profil-units (40:49) and respective code removed
7!
8! Former revisions:
9! -----------------
10! $Id: close_file.f90 964 2012-07-26 09:14:24Z raasch $
11!
12! 564 2010-09-30 13:18:59Z helmke
13! start number of mask output files changed to 201, netcdf message identifiers
14! of masked output changed
15!
16! 493 2010-03-01 08:30:24Z raasch
17! Adjustments for NetCDF parallel data output
18!
19! 410 2009-12-04 17:05:40Z letzel
20! masked data output
21!
22! 263 2009-03-18 12:26:04Z heinze
23! Output of NetCDF messages with aid of message handling routine.
24!
25! Feb. 2007
26! RCS Log replace by Id keyword, revision history cleaned up
27!
28! Revision 1.10  2006/08/22 13:50:01  raasch
29! xz and yz cross sections now up to nzt+1
30!
31! Revision 1.1  2001/01/02 17:23:41  raasch
32! Initial revision
33!
34! Last revision before renaming subroutine  2001/01/01  raasch
35! Subroutine name changed from close_files to close_file. Closing of a single
36! file is allowed by passing its file-id as an argument. Variable openfile now
37! is of type file_status and contains a flag which indicates if a file has
38! been opened before. Old revision remarks deleted.
39!
40! Revision 1.13 (close_files) 2000/12/20 09:10:24  letzel
41! All comments translated into English.
42!
43! Revision 1.12 (close_files) 1999/03/02 09:22:46  raasch
44! FLD-Header fuer komprimierte 3D-Daten
45!
46! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
47! Initial revision
48!
49!
50! Description:
51! ------------
52! Close specified file or all open files, if "0" has been given as the
53! calling argument. In that case, execute last actions for certain unit
54! numbers, if required.
55!------------------------------------------------------------------------------!
56
57    USE control_parameters
58    USE grid_variables
59    USE indices
60    USE netcdf_control
61    USE pegrid
62    USE profil_parameter
63    USE statistics
64
65    IMPLICIT NONE
66
67    CHARACTER (LEN=2)   ::  suffix
68    CHARACTER (LEN=10)  ::  datform = 'lit_endian'
69    CHARACTER (LEN=80)  ::  rtext, title
70
71    INTEGER ::  av, anzzeile, dimx, dimy, &
72                fid, file_id, j, k, planz
73
74    LOGICAL ::  checkuf = .TRUE., datleg = .TRUE., dp = .FALSE., swap
75
76    REAL ::  sizex, sizey, yright
77
78    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dp, planz, &
79                       title
80    NAMELIST /RAHMEN/  anzzeile, 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, 200+2*max_masks
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#if defined( __netcdf )
185             CASE ( 101 )
186
187                IF ( netcdf_output  .AND.  &
188                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
189                   nc_stat = NF90_CLOSE( id_set_xy(0) )
190                   CALL handle_netcdf_error( 'close_file', 44 )
191                ENDIF
192
193             CASE ( 102 )
194
195                IF ( netcdf_output  .AND.  &
196                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
197                   nc_stat = NF90_CLOSE( id_set_xz(0) )
198                   CALL handle_netcdf_error( 'close_file', 45 )
199                ENDIF
200
201             CASE ( 103 )
202
203                IF ( netcdf_output  .AND.  &
204                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
205                   nc_stat = NF90_CLOSE( id_set_yz(0) )
206                   CALL handle_netcdf_error( 'close_file', 46 )
207                ENDIF
208
209             CASE ( 104 )
210
211                IF ( myid == 0  .AND.  netcdf_output )  THEN
212                   nc_stat = NF90_CLOSE( id_set_pr )
213                   CALL handle_netcdf_error( 'close_file', 47 )
214                ENDIF
215
216             CASE ( 105 )
217
218                IF ( myid == 0  .AND.  netcdf_output )  THEN
219                   nc_stat = NF90_CLOSE( id_set_ts )
220                   CALL handle_netcdf_error( 'close_file', 48 )
221                ENDIF
222
223             CASE ( 106 )
224
225                IF ( netcdf_output  .AND.  &
226                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
227                   nc_stat = NF90_CLOSE( id_set_3d(0) )
228                   CALL handle_netcdf_error( 'close_file', 49 )
229                ENDIF
230
231             CASE ( 107 )
232
233                IF ( myid == 0  .AND.  netcdf_output )  THEN
234                   nc_stat = NF90_CLOSE( id_set_sp )
235                   CALL handle_netcdf_error( 'close_file', 50 )
236                ENDIF
237
238             CASE ( 108 )
239
240                IF (  netcdf_output )  THEN
241                   nc_stat = NF90_CLOSE( id_set_prt )
242                   CALL handle_netcdf_error( 'close_file', 51 )
243                ENDIF
244
245             CASE ( 109 ) 
246
247                IF (  netcdf_output )  THEN
248                   nc_stat = NF90_CLOSE( id_set_pts )
249                   CALL handle_netcdf_error( 'close_file', 412 )
250                ENDIF
251
252             CASE ( 111 )
253
254                IF ( netcdf_output  .AND.  &
255                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
256                   nc_stat = NF90_CLOSE( id_set_xy(1) )
257                   CALL handle_netcdf_error( 'close_file', 52 )
258                ENDIF
259
260             CASE ( 112 )
261
262                IF ( netcdf_output  .AND.  &
263                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
264                   nc_stat = NF90_CLOSE( id_set_xz(1) )
265                   CALL handle_netcdf_error( 'close_file', 352 )
266                ENDIF
267
268             CASE ( 113 )
269
270                IF ( netcdf_output  .AND.  &
271                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
272                   nc_stat = NF90_CLOSE( id_set_yz(1) )
273                   CALL handle_netcdf_error( 'close_file', 353 )
274                ENDIF
275
276             CASE ( 116 )
277
278                IF ( netcdf_output  .AND.  &
279                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
280                   nc_stat = NF90_CLOSE( id_set_3d(1) )
281                   CALL handle_netcdf_error( 'close_file', 353 )
282                ENDIF
283
284             CASE ( 201:200+2*max_masks )
285             
286                IF ( netcdf_output  .AND.  &
287                     ( myid == 0  .OR.  netcdf_data_format > 2 ) )  THEN
288!
289!--                decompose fid into mid and av
290                   IF ( fid <= 200+max_masks )  THEN
291                      mid = fid - 200
292                      av = 0
293                   ELSE
294                      mid = fid - (200+max_masks)
295                      av = 1
296                   ENDIF
297                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
298                   CALL handle_netcdf_error( 'close_file', 459 )
299               
300                ENDIF
301
302#endif
303
304          END SELECT
305!
306!--       Close file
307          IF ( openfile(fid)%opened )  CLOSE ( fid )
308
309       ENDIF
310
311    ENDDO
312
313!
314!-- Formats
3153200 FORMAT ('# AVS',A,'field file'/ &
316             '#'/                &
317             '# ',A/             &
318             'ndim=3'/           &
319             'dim1=',I5/         &
320             'dim2=',I5/         &
321             'dim3=',I5/         &
322             'nspace=3'/         &
323             'veclen=',I5/       &
324             'data=xdr_float'/   &
325             'field=rectilinear')
3264000 FORMAT ('time averaged over',F7.1,' s')
327
328
329 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.