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

Last change on this file since 3049 was 3045, checked in by Giersch, 6 years ago

Code adjusted according to coding standards, renamed namelists, error messages revised until PA0347, output CASE 108 disabled

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