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

Last change on this file since 2001 was 2001, checked in by knoop, 8 years ago

last commit documented

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