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

Last change on this file since 4182 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 7.2 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 4182 2019-08-22 15:20:23Z scharf $
[4182]27! Corrected "Former revisions" section
28!
29! 4069 2019-07-01 14:05:51Z Giersch
[4069]30! Masked output running index mid has been introduced as a local variable to
31! avoid runtime error (Loop variable has been modified) in time_integration
32!
33! 3655 2019-01-07 16:51:22Z knoop
[3241]34! unused variables and format statements removed
[2716]35!
[4182]36! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
37! Initial revision
38!
39!
[1]40! Description:
41! ------------
[1682]42!> Close specified file or all open files, if "0" has been given as the
43!> calling argument. In that case, execute last actions for certain unit
44!> numbers, if required.
[1]45!------------------------------------------------------------------------------!
[1682]46 SUBROUTINE close_file( file_id )
47 
[1]48
[1320]49    USE control_parameters,                                                    &
[4069]50        ONLY:  max_masks, openfile
[1320]51               
52    USE kinds
53   
[1783]54#if defined( __netcdf )
55    USE NETCDF
56#endif
57
58    USE netcdf_interface,                                                      &
[3241]59        ONLY:  id_set_mask, id_set_pr, id_set_pts, id_set_sp,                  &
[1992]60               id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d,          &
61               id_set_fl, nc_stat, netcdf_data_format, netcdf_handle_error
[1320]62               
63    USE pegrid                                           
[1]64
65    IMPLICIT NONE
66
[1682]67    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
68    CHARACTER (LEN=80)  ::  title                  !<
[1]69
[1682]70    INTEGER(iwp) ::  av           !<
71    INTEGER(iwp) ::  dimx         !<
72    INTEGER(iwp) ::  dimy         !<
73    INTEGER(iwp) ::  fid          !<
74    INTEGER(iwp) ::  file_id      !<
[4069]75    INTEGER(iwp) ::  mid          !< masked output running index
[1682]76    INTEGER(iwp) ::  planz        !<
[1]77
[1682]78    LOGICAL ::  checkuf = .TRUE.  !<
79    LOGICAL ::  datleg = .TRUE.   !<
80    LOGICAL ::  dbp = .FALSE.     !<
[1]81
[1320]82    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
[964]83                       title
[1092]84    NAMELIST /RAHMEN/  datleg
[1]85
86!
87!-- Close specified unit number (if opened) and set a flag that it has
88!-- been opened one time at least
89    IF ( file_id /= 0 )  THEN
90       IF ( openfile(file_id)%opened )  THEN
91          CLOSE ( file_id )
92          openfile(file_id)%opened        = .FALSE.
93          openfile(file_id)%opened_before = .TRUE.
94       ENDIF
95       RETURN
96    ENDIF
97
98!
99!-- Close all open unit numbers
[564]100    DO  fid = 1, 200+2*max_masks
[1]101
102       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
103!
104!--       Last actions for certain unit numbers
105          SELECT CASE ( fid )
106
107#if defined( __netcdf )
108             CASE ( 101 )
109
[1327]110                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]111                   nc_stat = NF90_CLOSE( id_set_xy(0) )
[1783]112                   CALL netcdf_handle_error( 'close_file', 44 )
[1]113                ENDIF
114
115             CASE ( 102 )
116
[1327]117                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]118                   nc_stat = NF90_CLOSE( id_set_xz(0) )
[1783]119                   CALL netcdf_handle_error( 'close_file', 45 )
[1]120                ENDIF
121
122             CASE ( 103 )
123
[1327]124                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]125                   nc_stat = NF90_CLOSE( id_set_yz(0) )
[1783]126                   CALL netcdf_handle_error( 'close_file', 46 )
[1]127                ENDIF
128
129             CASE ( 104 )
130
[1327]131                IF ( myid == 0 )  THEN
[1]132                   nc_stat = NF90_CLOSE( id_set_pr )
[1783]133                   CALL netcdf_handle_error( 'close_file', 47 )
[1]134                ENDIF
135
136             CASE ( 105 )
137
[1327]138                IF ( myid == 0 )  THEN
[1]139                   nc_stat = NF90_CLOSE( id_set_ts )
[1783]140                   CALL netcdf_handle_error( 'close_file', 48 )
[1]141                ENDIF
142
143             CASE ( 106 )
144
[1327]145                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]146                   nc_stat = NF90_CLOSE( id_set_3d(0) )
[1783]147                   CALL netcdf_handle_error( 'close_file', 49 )
[1]148                ENDIF
149
150             CASE ( 107 )
151
[1327]152                IF ( myid == 0 )  THEN
[1]153                   nc_stat = NF90_CLOSE( id_set_sp )
[1783]154                   CALL netcdf_handle_error( 'close_file', 50 )
[1]155                ENDIF
156
[3045]157!
158!--           Currently disabled
159!             CASE ( 108 )
[1]160
[3045]161!                nc_stat = NF90_CLOSE( id_set_prt )
162!                CALL netcdf_handle_error( 'close_file', 51 )
[1]163
164             CASE ( 109 ) 
165
[1327]166                nc_stat = NF90_CLOSE( id_set_pts )
[1783]167                CALL netcdf_handle_error( 'close_file', 412 )
[1]168
169             CASE ( 111 )
170
[1327]171                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]172                   nc_stat = NF90_CLOSE( id_set_xy(1) )
[1783]173                   CALL netcdf_handle_error( 'close_file', 52 )
[1]174                ENDIF
175
176             CASE ( 112 )
177
[1327]178                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]179                   nc_stat = NF90_CLOSE( id_set_xz(1) )
[1783]180                   CALL netcdf_handle_error( 'close_file', 352 )
[1]181                ENDIF
182
183             CASE ( 113 )
184
[1327]185                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]186                   nc_stat = NF90_CLOSE( id_set_yz(1) )
[1783]187                   CALL netcdf_handle_error( 'close_file', 353 )
[1]188                ENDIF
189
190             CASE ( 116 )
191
[1327]192                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]193                   nc_stat = NF90_CLOSE( id_set_3d(1) )
[1783]194                   CALL netcdf_handle_error( 'close_file', 353 )
[1]195                ENDIF
196
[1992]197             CASE ( 199 )
198
199                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
200                   nc_stat = NF90_CLOSE( id_set_fl )
201                   CALL netcdf_handle_error( 'close_file', 353 )
202                ENDIF
203
[564]204             CASE ( 201:200+2*max_masks )
[1992]205
[1327]206                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[410]207!
208!--                decompose fid into mid and av
[564]209                   IF ( fid <= 200+max_masks )  THEN
210                      mid = fid - 200
[410]211                      av = 0
212                   ELSE
[564]213                      mid = fid - (200+max_masks)
[410]214                      av = 1
215                   ENDIF
216                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
[1783]217                   CALL netcdf_handle_error( 'close_file', 459 )
[1992]218
[410]219                ENDIF
220
[1]221#endif
222
223          END SELECT
224!
225!--       Close file
226          IF ( openfile(fid)%opened )  CLOSE ( fid )
227
228       ENDIF
229
230    ENDDO
231
232 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.