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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

  • Property svn:keywords set to Id
File size: 9.2 KB
Line 
1!> @file close_file.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2016 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! Forced header and separation lines into 80 columns
23!
24! Former revisions:
25! -----------------
26! $Id: close_file.f90 2000 2016-08-20 18:09:15Z knoop $
27!
28! 1992 2016-08-12 15:14:59Z suehring
29! -Close file containing flight data
30! -Some tabs removed.
31!
32! 1783 2016-03-06 18:36:17Z raasch
33! name change of netcdf routines and module + related changes
34!
35! 1682 2015-10-07 23:56:08Z knoop
36! Code annotations made doxygen readable
37!
38! 1327 2014-03-21 11:00:16Z raasch
39! parts concerning iso2d and avs output removed
40!
41! 1320 2014-03-20 08:40:49Z raasch
42! ONLY-attribute added to USE-statements,
43! kind-parameters added to all INTEGER and REAL declaration statements,
44! kinds are defined in new module kinds,
45! revision history before 2012 removed,
46! comment fields (!:) to be used for variable explanations added to
47! all variable declaration statements
48!
49! 1092 2013-02-02 11:24:22Z raasch
50! unused variables removed
51!
52! 1036 2012-10-22 13:43:42Z raasch
53! code put under GPL (PALM 3.9)
54!
55! 1031 2012-10-19 14:35:30Z raasch
56! netCDF4 without parallel file support implemented
57!
58! 964 2012-07-26 09:14:24Z raasch
59! old profil-units (40:49) and respective code removed
60!
61! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
62! Initial revision
63!
64!
65! Description:
66! ------------
67!> Close specified file or all open files, if "0" has been given as the
68!> calling argument. In that case, execute last actions for certain unit
69!> numbers, if required.
70!------------------------------------------------------------------------------!
71 SUBROUTINE close_file( file_id )
72 
73
74    USE control_parameters,                                                    &
75        ONLY:  do2d_xz_n, do2d_xy_n, do2d_yz_n, do3d_avs_n, host, max_masks,   &
76               mid, nz_do3d, openfile, run_description_header, z_max_do2d
77               
78    USE grid_variables,                                                        &
79        ONLY:  dy
80       
81    USE indices,                                                               &
82        ONLY:  nx, ny, nz
83       
84    USE kinds
85   
86#if defined( __netcdf )
87    USE NETCDF
88#endif
89
90    USE netcdf_interface,                                                      &
91        ONLY:  id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp,      &
92               id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d,          &
93               id_set_fl, nc_stat, netcdf_data_format, netcdf_handle_error
94               
95    USE pegrid                                           
96
97    IMPLICIT NONE
98
99    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
100    CHARACTER (LEN=80)  ::  title                  !<
101
102    INTEGER(iwp) ::  av           !<
103    INTEGER(iwp) ::  dimx         !<
104    INTEGER(iwp) ::  dimy         !<
105    INTEGER(iwp) ::  fid          !<
106    INTEGER(iwp) ::  file_id      !<
107    INTEGER(iwp) ::  planz        !<
108
109    LOGICAL ::  checkuf = .TRUE.  !<
110    LOGICAL ::  datleg = .TRUE.   !<
111    LOGICAL ::  dbp = .FALSE.     !<
112
113    REAL(wp) ::  sizex            !<
114    REAL(wp) ::  sizey            !<
115    REAL(wp) ::  yright           !<
116
117    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
118                       title
119    NAMELIST /RAHMEN/  datleg
120
121!
122!-- Close specified unit number (if opened) and set a flag that it has
123!-- been opened one time at least
124    IF ( file_id /= 0 )  THEN
125       IF ( openfile(file_id)%opened )  THEN
126          CLOSE ( file_id )
127          openfile(file_id)%opened        = .FALSE.
128          openfile(file_id)%opened_before = .TRUE.
129       ENDIF
130       RETURN
131    ENDIF
132
133!
134!-- Close all open unit numbers
135    DO  fid = 1, 200+2*max_masks
136
137       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
138!
139!--       Last actions for certain unit numbers
140          SELECT CASE ( fid )
141
142#if defined( __netcdf )
143             CASE ( 101 )
144
145                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
146                   nc_stat = NF90_CLOSE( id_set_xy(0) )
147                   CALL netcdf_handle_error( 'close_file', 44 )
148                ENDIF
149
150             CASE ( 102 )
151
152                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
153                   nc_stat = NF90_CLOSE( id_set_xz(0) )
154                   CALL netcdf_handle_error( 'close_file', 45 )
155                ENDIF
156
157             CASE ( 103 )
158
159                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
160                   nc_stat = NF90_CLOSE( id_set_yz(0) )
161                   CALL netcdf_handle_error( 'close_file', 46 )
162                ENDIF
163
164             CASE ( 104 )
165
166                IF ( myid == 0 )  THEN
167                   nc_stat = NF90_CLOSE( id_set_pr )
168                   CALL netcdf_handle_error( 'close_file', 47 )
169                ENDIF
170
171             CASE ( 105 )
172
173                IF ( myid == 0 )  THEN
174                   nc_stat = NF90_CLOSE( id_set_ts )
175                   CALL netcdf_handle_error( 'close_file', 48 )
176                ENDIF
177
178             CASE ( 106 )
179
180                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
181                   nc_stat = NF90_CLOSE( id_set_3d(0) )
182                   CALL netcdf_handle_error( 'close_file', 49 )
183                ENDIF
184
185             CASE ( 107 )
186
187                IF ( myid == 0 )  THEN
188                   nc_stat = NF90_CLOSE( id_set_sp )
189                   CALL netcdf_handle_error( 'close_file', 50 )
190                ENDIF
191
192             CASE ( 108 )
193
194                nc_stat = NF90_CLOSE( id_set_prt )
195                CALL netcdf_handle_error( 'close_file', 51 )
196
197             CASE ( 109 ) 
198
199                nc_stat = NF90_CLOSE( id_set_pts )
200                CALL netcdf_handle_error( 'close_file', 412 )
201
202             CASE ( 111 )
203
204                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
205                   nc_stat = NF90_CLOSE( id_set_xy(1) )
206                   CALL netcdf_handle_error( 'close_file', 52 )
207                ENDIF
208
209             CASE ( 112 )
210
211                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
212                   nc_stat = NF90_CLOSE( id_set_xz(1) )
213                   CALL netcdf_handle_error( 'close_file', 352 )
214                ENDIF
215
216             CASE ( 113 )
217
218                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
219                   nc_stat = NF90_CLOSE( id_set_yz(1) )
220                   CALL netcdf_handle_error( 'close_file', 353 )
221                ENDIF
222
223             CASE ( 116 )
224
225                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
226                   nc_stat = NF90_CLOSE( id_set_3d(1) )
227                   CALL netcdf_handle_error( 'close_file', 353 )
228                ENDIF
229
230             CASE ( 199 )
231
232                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
233                   nc_stat = NF90_CLOSE( id_set_fl )
234                   CALL netcdf_handle_error( 'close_file', 353 )
235                ENDIF
236
237             CASE ( 201:200+2*max_masks )
238
239                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
240!
241!--                decompose fid into mid and av
242                   IF ( fid <= 200+max_masks )  THEN
243                      mid = fid - 200
244                      av = 0
245                   ELSE
246                      mid = fid - (200+max_masks)
247                      av = 1
248                   ENDIF
249                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
250                   CALL netcdf_handle_error( 'close_file', 459 )
251
252                ENDIF
253
254#endif
255
256          END SELECT
257!
258!--       Close file
259          IF ( openfile(fid)%opened )  CLOSE ( fid )
260
261       ENDIF
262
263    ENDDO
264
265!
266!-- Formats
2673200 FORMAT ('# AVS',A,'field file'/                                           &
268             '#'/                                                              &
269             '# ',A/                                                           &
270             'ndim=3'/                                                         &
271             'dim1=',I5/                                                       &
272             'dim2=',I5/                                                       &
273             'dim3=',I5/                                                       &
274             'nspace=3'/                                                       &
275             'veclen=',I5/                                                     &
276             'data=xdr_float'/                                                 &
277             'field=rectilinear')
2784000 FORMAT ('time averaged over',F7.1,' s')
279
280
281 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.