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

Last change on this file since 1992 was 1992, checked in by suehring, 7 years ago

Prescribing scalar flux at model top; several bugfixes concering data output of scalars and output of flight data

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