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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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