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

Last change on this file since 2277 was 2277, checked in by kanani, 7 years ago

code documentation and cleanup

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