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

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

last commit documented

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