source: palm/tags/release-5.0/SOURCE/close_file.f90 @ 3425

Last change on this file since 3425 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

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