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

Last change on this file since 1783 was 1783, checked in by raasch, 8 years ago

NetCDF routines modularized; new parameter netcdf_deflate; further changes in the pmc

  • Property svn:keywords set to Id
File size: 8.7 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! name change of netcdf routines and module + related changes
22!
23! Former revisions:
24! -----------------
25! $Id: close_file.f90 1783 2016-03-06 18:36:17Z raasch $
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, host, max_masks,   &
68               mid, nz_do3d, openfile, run_description_header, z_max_do2d
69               
70    USE grid_variables,                                                        &
71        ONLY:  dy
72       
73    USE indices,                                                               &
74        ONLY:  nx, ny, nz
75       
76    USE kinds
77   
78#if defined( __netcdf )
79    USE NETCDF
80#endif
81
82    USE netcdf_interface,                                                      &
83        ONLY:  id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp,      &
84               id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d, nc_stat, &
85               netcdf_data_format, netcdf_handle_error
86               
87    USE pegrid                                           
88
89    IMPLICIT NONE
90
91    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
92    CHARACTER (LEN=80)  ::  title                  !<
93
94    INTEGER(iwp) ::  av           !<
95    INTEGER(iwp) ::  dimx         !<
96    INTEGER(iwp) ::  dimy         !<
97    INTEGER(iwp) ::  fid          !<
98    INTEGER(iwp) ::  file_id      !<
99    INTEGER(iwp) ::  planz        !<
100
101    LOGICAL ::  checkuf = .TRUE.  !<
102    LOGICAL ::  datleg = .TRUE.   !<
103    LOGICAL ::  dbp = .FALSE.     !<
104
105    REAL(wp) ::  sizex            !<
106    REAL(wp) ::  sizey            !<
107    REAL(wp) ::  yright           !<
108
109    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
110                       title
111    NAMELIST /RAHMEN/  datleg
112
113!
114!-- Close specified unit number (if opened) and set a flag that it has
115!-- been opened one time at least
116    IF ( file_id /= 0 )  THEN
117       IF ( openfile(file_id)%opened )  THEN
118          CLOSE ( file_id )
119          openfile(file_id)%opened        = .FALSE.
120          openfile(file_id)%opened_before = .TRUE.
121       ENDIF
122       RETURN
123    ENDIF
124
125!
126!-- Close all open unit numbers
127    DO  fid = 1, 200+2*max_masks
128
129       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
130!
131!--       Last actions for certain unit numbers
132          SELECT CASE ( fid )
133
134#if defined( __netcdf )
135             CASE ( 101 )
136
137                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
138                   nc_stat = NF90_CLOSE( id_set_xy(0) )
139                   CALL netcdf_handle_error( 'close_file', 44 )
140                ENDIF
141
142             CASE ( 102 )
143
144                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
145                   nc_stat = NF90_CLOSE( id_set_xz(0) )
146                   CALL netcdf_handle_error( 'close_file', 45 )
147                ENDIF
148
149             CASE ( 103 )
150
151                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
152                   nc_stat = NF90_CLOSE( id_set_yz(0) )
153                   CALL netcdf_handle_error( 'close_file', 46 )
154                ENDIF
155
156             CASE ( 104 )
157
158                IF ( myid == 0 )  THEN
159                   nc_stat = NF90_CLOSE( id_set_pr )
160                   CALL netcdf_handle_error( 'close_file', 47 )
161                ENDIF
162
163             CASE ( 105 )
164
165                IF ( myid == 0 )  THEN
166                   nc_stat = NF90_CLOSE( id_set_ts )
167                   CALL netcdf_handle_error( 'close_file', 48 )
168                ENDIF
169
170             CASE ( 106 )
171
172                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
173                   nc_stat = NF90_CLOSE( id_set_3d(0) )
174                   CALL netcdf_handle_error( 'close_file', 49 )
175                ENDIF
176
177             CASE ( 107 )
178
179                IF ( myid == 0 )  THEN
180                   nc_stat = NF90_CLOSE( id_set_sp )
181                   CALL netcdf_handle_error( 'close_file', 50 )
182                ENDIF
183
184             CASE ( 108 )
185
186                nc_stat = NF90_CLOSE( id_set_prt )
187                CALL netcdf_handle_error( 'close_file', 51 )
188
189             CASE ( 109 ) 
190
191                nc_stat = NF90_CLOSE( id_set_pts )
192                CALL netcdf_handle_error( 'close_file', 412 )
193
194             CASE ( 111 )
195
196                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
197                   nc_stat = NF90_CLOSE( id_set_xy(1) )
198                   CALL netcdf_handle_error( 'close_file', 52 )
199                ENDIF
200
201             CASE ( 112 )
202
203                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
204                   nc_stat = NF90_CLOSE( id_set_xz(1) )
205                   CALL netcdf_handle_error( 'close_file', 352 )
206                ENDIF
207
208             CASE ( 113 )
209
210                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
211                   nc_stat = NF90_CLOSE( id_set_yz(1) )
212                   CALL netcdf_handle_error( 'close_file', 353 )
213                ENDIF
214
215             CASE ( 116 )
216
217                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
218                   nc_stat = NF90_CLOSE( id_set_3d(1) )
219                   CALL netcdf_handle_error( 'close_file', 353 )
220                ENDIF
221
222             CASE ( 201:200+2*max_masks )
223             
224                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
225!
226!--                decompose fid into mid and av
227                   IF ( fid <= 200+max_masks )  THEN
228                      mid = fid - 200
229                      av = 0
230                   ELSE
231                      mid = fid - (200+max_masks)
232                      av = 1
233                   ENDIF
234                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
235                   CALL netcdf_handle_error( 'close_file', 459 )
236               
237                ENDIF
238
239#endif
240
241          END SELECT
242!
243!--       Close file
244          IF ( openfile(fid)%opened )  CLOSE ( fid )
245
246       ENDIF
247
248    ENDDO
249
250!
251!-- Formats
2523200 FORMAT ('# AVS',A,'field file'/                                           &
253             '#'/                                                              &
254             '# ',A/                                                           &
255             'ndim=3'/                                                         &
256             'dim1=',I5/                                                       &
257             'dim2=',I5/                                                       &
258             'dim3=',I5/                                                       &
259             'nspace=3'/                                                       &
260             'veclen=',I5/                                                     &
261             'data=xdr_float'/                                                 &
262             'field=rectilinear')
2634000 FORMAT ('time averaged over',F7.1,' s')
264
265
266 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.