source: palm/trunk/SOURCE/close_file.f90

Last change on this file was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 7.2 KB
RevLine 
[1682]1!> @file close_file.f90
[4559]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[4559]5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
[1036]8!
[4559]9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
[1036]12!
[4559]13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
[1036]15!
[4828]16! Copyright 1997-2021 Leibniz Universitaet Hannover
[4559]17!--------------------------------------------------------------------------------------------------!
[1036]18!
[263]19! Current revisions:
[1]20! -----------------
[1993]21!
[2001]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: close_file.f90 4828 2021-01-05 11:21:41Z banzhafs $
[4559]26! file re-formatted to follow the PALM coding standard
27!
28! 4360 2020-01-07 11:25:50Z suehring
[4182]29! Corrected "Former revisions" section
[4559]30!
[4182]31! 4069 2019-07-01 14:05:51Z Giersch
[4559]32! Masked output running index mid has been introduced as a local variable to
[4069]33! avoid runtime error (Loop variable has been modified) in time_integration
[4559]34!
[4069]35! 3655 2019-01-07 16:51:22Z knoop
[3241]36! unused variables and format statements removed
[2716]37!
[4182]38! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
39! Initial revision
40!
41!
[1]42! Description:
43! ------------
[4559]44!> Close specified file or all open files, if "0" has been given as the calling argument. In that
45!> case, execute last actions for certain unit numbers, if required.
46!--------------------------------------------------------------------------------------------------!
[1682]47 SUBROUTINE close_file( file_id )
[1]48
[4559]49
50    USE control_parameters,                                                                        &
[4069]51        ONLY:  max_masks, openfile
[4559]52
[1320]53    USE kinds
[4559]54
[1783]55#if defined( __netcdf )
56    USE NETCDF
57#endif
58
59    USE netcdf_interface,                                                      &
[4559]60        ONLY:  id_set_mask, id_set_pr, id_set_pts, id_set_sp,  id_set_ts, id_set_xy, id_set_xz,    &
61               id_set_yz, id_set_3d, id_set_fl, nc_stat, netcdf_data_format, netcdf_handle_error
[1]62
[4559]63    USE pegrid
64
[1]65    IMPLICIT NONE
66
[4559]67    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
68    CHARACTER (LEN=80)  ::  title                  !<
[1]69
[4559]70    INTEGER(iwp) ::  av           !<
71    INTEGER(iwp) ::  dimx         !<
72    INTEGER(iwp) ::  dimy         !<
73    INTEGER(iwp) ::  fid          !<
74    INTEGER(iwp) ::  file_id      !<
75    INTEGER(iwp) ::  mid          !< masked output running index
76    INTEGER(iwp) ::  planz        !<
[1]77
[4559]78    LOGICAL ::  checkuf = .TRUE.  !<
79    LOGICAL ::  datleg = .TRUE.   !<
80    LOGICAL ::  dbp = .FALSE.     !<
[1]81
[4559]82    NAMELIST /GLOBAL/  checkuf, datform, dbp, dimx, dimy, planz, title
[1092]83    NAMELIST /RAHMEN/  datleg
[1]84
85!
[4559]86!-- Close specified unit number (if opened) and set a flag that it has been opened one time at least
[1]87    IF ( file_id /= 0 )  THEN
88       IF ( openfile(file_id)%opened )  THEN
89          CLOSE ( file_id )
90          openfile(file_id)%opened        = .FALSE.
91          openfile(file_id)%opened_before = .TRUE.
92       ENDIF
93       RETURN
94    ENDIF
95
96!
97!-- Close all open unit numbers
[564]98    DO  fid = 1, 200+2*max_masks
[1]99
100       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
101!
102!--       Last actions for certain unit numbers
103          SELECT CASE ( fid )
104
105#if defined( __netcdf )
106             CASE ( 101 )
107
[1327]108                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]109                   nc_stat = NF90_CLOSE( id_set_xy(0) )
[1783]110                   CALL netcdf_handle_error( 'close_file', 44 )
[1]111                ENDIF
112
113             CASE ( 102 )
114
[1327]115                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]116                   nc_stat = NF90_CLOSE( id_set_xz(0) )
[1783]117                   CALL netcdf_handle_error( 'close_file', 45 )
[1]118                ENDIF
119
120             CASE ( 103 )
121
[1327]122                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]123                   nc_stat = NF90_CLOSE( id_set_yz(0) )
[1783]124                   CALL netcdf_handle_error( 'close_file', 46 )
[1]125                ENDIF
126
127             CASE ( 104 )
128
[1327]129                IF ( myid == 0 )  THEN
[1]130                   nc_stat = NF90_CLOSE( id_set_pr )
[1783]131                   CALL netcdf_handle_error( 'close_file', 47 )
[1]132                ENDIF
133
134             CASE ( 105 )
135
[1327]136                IF ( myid == 0 )  THEN
[1]137                   nc_stat = NF90_CLOSE( id_set_ts )
[1783]138                   CALL netcdf_handle_error( 'close_file', 48 )
[1]139                ENDIF
140
141             CASE ( 106 )
142
[1327]143                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]144                   nc_stat = NF90_CLOSE( id_set_3d(0) )
[1783]145                   CALL netcdf_handle_error( 'close_file', 49 )
[1]146                ENDIF
147
148             CASE ( 107 )
149
[1327]150                IF ( myid == 0 )  THEN
[1]151                   nc_stat = NF90_CLOSE( id_set_sp )
[1783]152                   CALL netcdf_handle_error( 'close_file', 50 )
[1]153                ENDIF
154
[3045]155!
156!--           Currently disabled
157!             CASE ( 108 )
[1]158
[3045]159!                nc_stat = NF90_CLOSE( id_set_prt )
160!                CALL netcdf_handle_error( 'close_file', 51 )
[1]161
[4559]162             CASE ( 109 )
[1]163
[1327]164                nc_stat = NF90_CLOSE( id_set_pts )
[1783]165                CALL netcdf_handle_error( 'close_file', 412 )
[1]166
167             CASE ( 111 )
168
[1327]169                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]170                   nc_stat = NF90_CLOSE( id_set_xy(1) )
[1783]171                   CALL netcdf_handle_error( 'close_file', 52 )
[1]172                ENDIF
173
174             CASE ( 112 )
175
[1327]176                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]177                   nc_stat = NF90_CLOSE( id_set_xz(1) )
[1783]178                   CALL netcdf_handle_error( 'close_file', 352 )
[1]179                ENDIF
180
181             CASE ( 113 )
182
[1327]183                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]184                   nc_stat = NF90_CLOSE( id_set_yz(1) )
[1783]185                   CALL netcdf_handle_error( 'close_file', 353 )
[1]186                ENDIF
187
188             CASE ( 116 )
189
[1327]190                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]191                   nc_stat = NF90_CLOSE( id_set_3d(1) )
[1783]192                   CALL netcdf_handle_error( 'close_file', 353 )
[1]193                ENDIF
194
[1992]195             CASE ( 199 )
196
197                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
198                   nc_stat = NF90_CLOSE( id_set_fl )
199                   CALL netcdf_handle_error( 'close_file', 353 )
200                ENDIF
201
[564]202             CASE ( 201:200+2*max_masks )
[1992]203
[1327]204                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[410]205!
[4559]206!--                Decompose fid into mid and av
[564]207                   IF ( fid <= 200+max_masks )  THEN
208                      mid = fid - 200
[410]209                      av = 0
210                   ELSE
[564]211                      mid = fid - (200+max_masks)
[410]212                      av = 1
213                   ENDIF
214                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
[1783]215                   CALL netcdf_handle_error( 'close_file', 459 )
[1992]216
[410]217                ENDIF
218
[1]219#endif
220
221          END SELECT
222!
223!--       Close file
224          IF ( openfile(fid)%opened )  CLOSE ( fid )
225
226       ENDIF
227
228    ENDDO
229
[4559]230 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.