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

Last change on this file since 3655 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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