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

Last change on this file since 1092 was 1092, checked in by raasch, 11 years ago

unused variables remove from several routines

  • Property svn:keywords set to Id
File size: 11.6 KB
RevLine 
[1]1 SUBROUTINE close_file( file_id )
2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
[263]20! Current revisions:
[1]21! -----------------
[1092]22! unused variables removed
[1]23!
24! Former revisions:
25! -----------------
[3]26! $Id: close_file.f90 1092 2013-02-02 11:24:22Z raasch $
[392]27!
[1037]28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
[1035]31! 1031 2012-10-19 14:35:30Z raasch
32! netCDF4 without parallel file support implemented
33!
[965]34! 964 2012-07-26 09:14:24Z raasch
35! old profil-units (40:49) and respective code removed
36!
[565]37! 564 2010-09-30 13:18:59Z helmke
38! start number of mask output files changed to 201, netcdf message identifiers
39! of masked output changed
40!
[494]41! 493 2010-03-01 08:30:24Z raasch
42! Adjustments for NetCDF parallel data output
43!
[449]44! 410 2009-12-04 17:05:40Z letzel
45! masked data output
46!
[392]47! 263 2009-03-18 12:26:04Z heinze
48! Output of NetCDF messages with aid of message handling routine.
49!
50! Feb. 2007
[3]51! RCS Log replace by Id keyword, revision history cleaned up
52!
[1]53! Revision 1.10  2006/08/22 13:50:01  raasch
54! xz and yz cross sections now up to nzt+1
55!
56! Revision 1.1  2001/01/02 17:23:41  raasch
57! Initial revision
58!
59! Last revision before renaming subroutine  2001/01/01  raasch
60! Subroutine name changed from close_files to close_file. Closing of a single
61! file is allowed by passing its file-id as an argument. Variable openfile now
62! is of type file_status and contains a flag which indicates if a file has
63! been opened before. Old revision remarks deleted.
64!
65! Revision 1.13 (close_files) 2000/12/20 09:10:24  letzel
66! All comments translated into English.
67!
68! Revision 1.12 (close_files) 1999/03/02 09:22:46  raasch
69! FLD-Header fuer komprimierte 3D-Daten
70!
71! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
72! Initial revision
73!
74!
75! Description:
76! ------------
77! Close specified file or all open files, if "0" has been given as the
78! calling argument. In that case, execute last actions for certain unit
79! numbers, if required.
80!------------------------------------------------------------------------------!
81
82    USE control_parameters
83    USE grid_variables
84    USE indices
85    USE netcdf_control
86    USE pegrid
87    USE profil_parameter
88    USE statistics
89
90    IMPLICIT NONE
91
92    CHARACTER (LEN=10)  ::  datform = 'lit_endian'
[1092]93    CHARACTER (LEN=80)  ::  title
[1]94
[1092]95    INTEGER ::  av, dimx, dimy, &
96                fid, file_id, planz
[1]97
[1092]98    LOGICAL ::  checkuf = .TRUE., datleg = .TRUE., dp = .FALSE.
[1]99
[964]100    REAL ::  sizex, sizey, yright
[1]101
[964]102    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dp, planz, &
103                       title
[1092]104    NAMELIST /RAHMEN/  datleg
[1]105
106!
107!-- Close specified unit number (if opened) and set a flag that it has
108!-- been opened one time at least
109    IF ( file_id /= 0 )  THEN
110       IF ( openfile(file_id)%opened )  THEN
111          CLOSE ( file_id )
112          openfile(file_id)%opened        = .FALSE.
113          openfile(file_id)%opened_before = .TRUE.
114       ENDIF
115       RETURN
116    ENDIF
117
118!
119!-- Close all open unit numbers
[564]120    DO  fid = 1, 200+2*max_masks
[1]121
122       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
123!
124!--       Last actions for certain unit numbers
125          SELECT CASE ( fid )
126
127             CASE ( 21 )
128!
129!--             Write ISO2D global parameters
130                IF ( myid == 0  .AND.  iso2d_output )  THEN
131                   planz  = do2d_xy_n
132                   dimx   = nx + 2
133                   dimy   = ny + 2
134                   sizex  = 100.0
135                   sizey  = 100.0
136                   title  = run_description_header
137                   yright = ( ny + 1.0 ) * dy
138                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
139                      checkuf = .FALSE.; dp = .TRUE.
140                   ENDIF
141                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
142                      datform = 'big_endian'
143                   ENDIF
144                   OPEN ( 90, FILE='PLOT2D_XY_GLOBAL', FORM='FORMATTED', &
145                              DELIM='APOSTROPHE' )
146                   WRITE ( 90, GLOBAL )
147                   CLOSE ( 90 )
148                ENDIF
149
150             CASE ( 22 )
151!
152!--             Write ISO2D global parameters
153                IF ( myid == 0 )  THEN
154                   planz  = do2d_xz_n
155                   dimx   = nx + 2
156                   dimy   = nz + 2
157                   sizex  = 100.0
158                   sizey  =  65.0
159                   title  = run_description_header
160                   yright = z_max_do2d
161                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
162                      checkuf = .FALSE.; dp = .TRUE.
163                   ENDIF
164                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
165                      datform = 'big_endian'
166                   ENDIF
167                   OPEN ( 90, FILE='PLOT2D_XZ_GLOBAL', FORM='FORMATTED', &
168                              DELIM='APOSTROPHE' )
169                   WRITE ( 90, GLOBAL )
170                   CLOSE ( 90 )
171                ENDIF
172
173             CASE ( 23 )
174!
175!--             Write ISO2D global parameters
176                IF ( myid == 0 )  THEN
177                   planz  = do2d_yz_n
178                   dimx   = ny + 2
179                   dimy   = nz + 2
180                   sizex  = 100.0
181                   sizey  =  65.0
182                   title  = run_description_header
183                   yright = z_max_do2d
184                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 't3e' )  THEN
185                      checkuf = .FALSE.; dp = .TRUE.
186                   ENDIF
187                   IF ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec' )  THEN
188                      datform = 'big_endian'
189                   ENDIF
190                   OPEN ( 90, FILE='PLOT2D_YZ_GLOBAL', FORM='FORMATTED', &
191                              DELIM='APOSTROPHE' )
192                   WRITE ( 90, GLOBAL )
193                   CLOSE ( 90 )
194                ENDIF
195
196             CASE ( 32 )
197!
198!--             Write header for FLD-file
199                IF ( do3d_compress )  THEN
200                   WRITE ( 32, 3200)  ' compressed ',                       &
201                                      TRIM( run_description_header ), nx+2, &
202                                      ny+2, nz_do3d+1, do3d_avs_n
203                ELSE
204                   WRITE ( 32, 3200)  ' ', TRIM( run_description_header ), &
205                                      nx+2, ny+2, nz_do3d+1, do3d_avs_n
206                ENDIF
207
208#if defined( __netcdf )
209             CASE ( 101 )
210
[493]211                IF ( netcdf_output  .AND.  &
[1031]212                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]213                   nc_stat = NF90_CLOSE( id_set_xy(0) )
[263]214                   CALL handle_netcdf_error( 'close_file', 44 )
[1]215                ENDIF
216
217             CASE ( 102 )
218
[493]219                IF ( netcdf_output  .AND.  &
[1031]220                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]221                   nc_stat = NF90_CLOSE( id_set_xz(0) )
[263]222                   CALL handle_netcdf_error( 'close_file', 45 )
[1]223                ENDIF
224
225             CASE ( 103 )
226
[493]227                IF ( netcdf_output  .AND.  &
[1031]228                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]229                   nc_stat = NF90_CLOSE( id_set_yz(0) )
[263]230                   CALL handle_netcdf_error( 'close_file', 46 )
[1]231                ENDIF
232
233             CASE ( 104 )
234
235                IF ( myid == 0  .AND.  netcdf_output )  THEN
236                   nc_stat = NF90_CLOSE( id_set_pr )
[263]237                   CALL handle_netcdf_error( 'close_file', 47 )
[1]238                ENDIF
239
240             CASE ( 105 )
241
242                IF ( myid == 0  .AND.  netcdf_output )  THEN
243                   nc_stat = NF90_CLOSE( id_set_ts )
[263]244                   CALL handle_netcdf_error( 'close_file', 48 )
[1]245                ENDIF
246
247             CASE ( 106 )
248
[493]249                IF ( netcdf_output  .AND.  &
[1031]250                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]251                   nc_stat = NF90_CLOSE( id_set_3d(0) )
[263]252                   CALL handle_netcdf_error( 'close_file', 49 )
[1]253                ENDIF
254
255             CASE ( 107 )
256
257                IF ( myid == 0  .AND.  netcdf_output )  THEN
258                   nc_stat = NF90_CLOSE( id_set_sp )
[263]259                   CALL handle_netcdf_error( 'close_file', 50 )
[1]260                ENDIF
261
262             CASE ( 108 )
263
264                IF (  netcdf_output )  THEN
265                   nc_stat = NF90_CLOSE( id_set_prt )
[263]266                   CALL handle_netcdf_error( 'close_file', 51 )
[1]267                ENDIF
268
269             CASE ( 109 ) 
270
271                IF (  netcdf_output )  THEN
272                   nc_stat = NF90_CLOSE( id_set_pts )
[263]273                   CALL handle_netcdf_error( 'close_file', 412 )
[1]274                ENDIF
275
276             CASE ( 111 )
277
[493]278                IF ( netcdf_output  .AND.  &
[1031]279                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]280                   nc_stat = NF90_CLOSE( id_set_xy(1) )
[263]281                   CALL handle_netcdf_error( 'close_file', 52 )
[1]282                ENDIF
283
284             CASE ( 112 )
285
[493]286                IF ( netcdf_output  .AND.  &
[1031]287                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]288                   nc_stat = NF90_CLOSE( id_set_xz(1) )
[263]289                   CALL handle_netcdf_error( 'close_file', 352 )
[1]290                ENDIF
291
292             CASE ( 113 )
293
[493]294                IF ( netcdf_output  .AND.  &
[1031]295                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]296                   nc_stat = NF90_CLOSE( id_set_yz(1) )
[263]297                   CALL handle_netcdf_error( 'close_file', 353 )
[1]298                ENDIF
299
300             CASE ( 116 )
301
[493]302                IF ( netcdf_output  .AND.  &
[1031]303                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[1]304                   nc_stat = NF90_CLOSE( id_set_3d(1) )
[263]305                   CALL handle_netcdf_error( 'close_file', 353 )
[1]306                ENDIF
307
[564]308             CASE ( 201:200+2*max_masks )
[410]309             
[493]310                IF ( netcdf_output  .AND.  &
[1031]311                     ( myid == 0  .OR.  netcdf_data_format > 4 ) )  THEN
[410]312!
313!--                decompose fid into mid and av
[564]314                   IF ( fid <= 200+max_masks )  THEN
315                      mid = fid - 200
[410]316                      av = 0
317                   ELSE
[564]318                      mid = fid - (200+max_masks)
[410]319                      av = 1
320                   ENDIF
321                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
[564]322                   CALL handle_netcdf_error( 'close_file', 459 )
[410]323               
324                ENDIF
325
[1]326#endif
327
328          END SELECT
329!
330!--       Close file
331          IF ( openfile(fid)%opened )  CLOSE ( fid )
332
333       ENDIF
334
335    ENDDO
336
337!
338!-- Formats
3393200 FORMAT ('# AVS',A,'field file'/ &
340             '#'/                &
341             '# ',A/             &
342             'ndim=3'/           &
343             'dim1=',I5/         &
344             'dim2=',I5/         &
345             'dim3=',I5/         &
346             'nspace=3'/         &
347             'veclen=',I5/       &
348             'data=xdr_float'/   &
349             'field=rectilinear')
3504000 FORMAT ('time averaged over',F7.1,' s')
351
352
353 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.