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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 8.4 KB
RevLine 
[1682]1!> @file close_file.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1310]16! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[263]19! Current revisions:
[1]20! -----------------
[1682]21! Code annotations made doxygen readable
[1329]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: close_file.f90 1682 2015-10-07 23:56:08Z knoop $
26!
[1329]27! 1327 2014-03-21 11:00:16Z raasch
28! parts concerning iso2d and avs output removed
29!
[1321]30! 1320 2014-03-20 08:40:49Z raasch
[1320]31! ONLY-attribute added to USE-statements,
32! kind-parameters added to all INTEGER and REAL declaration statements,
33! kinds are defined in new module kinds,
34! revision history before 2012 removed,
35! comment fields (!:) to be used for variable explanations added to
36! all variable declaration statements
[1]37!
[1093]38! 1092 2013-02-02 11:24:22Z raasch
39! unused variables removed
40!
[1037]41! 1036 2012-10-22 13:43:42Z raasch
42! code put under GPL (PALM 3.9)
43!
[1035]44! 1031 2012-10-19 14:35:30Z raasch
45! netCDF4 without parallel file support implemented
46!
[965]47! 964 2012-07-26 09:14:24Z raasch
48! old profil-units (40:49) and respective code removed
49!
[1]50! Revision 1.1 (close_files) 1997/08/11 06:11:18  raasch
51! Initial revision
52!
53!
54! Description:
55! ------------
[1682]56!> Close specified file or all open files, if "0" has been given as the
57!> calling argument. In that case, execute last actions for certain unit
58!> numbers, if required.
[1]59!------------------------------------------------------------------------------!
[1682]60 SUBROUTINE close_file( file_id )
61 
[1]62
[1320]63    USE control_parameters,                                                    &
[1327]64        ONLY:  do2d_xz_n, do2d_xy_n, do2d_yz_n, do3d_avs_n,                    &
65               host, max_masks, mid, netcdf_data_format,                       &
66               nz_do3d, openfile, run_description_header,       &
[1320]67               z_max_do2d
68               
69    USE grid_variables,                                                        &
70        ONLY:  dy
71       
72    USE indices,                                                               &
73        ONLY:  nx, ny, nz
74       
75    USE kinds
76   
[1]77    USE netcdf_control
[1320]78               
79    USE pegrid                                           
[1]80
81    IMPLICIT NONE
82
[1682]83    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
84    CHARACTER (LEN=80)  ::  title                  !<
[1]85
[1682]86    INTEGER(iwp) ::  av           !<
87    INTEGER(iwp) ::  dimx         !<
88    INTEGER(iwp) ::  dimy         !<
89    INTEGER(iwp) ::  fid          !<
90    INTEGER(iwp) ::  file_id      !<
91    INTEGER(iwp) ::  planz        !<
[1]92
[1682]93    LOGICAL ::  checkuf = .TRUE.  !<
94    LOGICAL ::  datleg = .TRUE.   !<
95    LOGICAL ::  dbp = .FALSE.     !<
[1]96
[1682]97    REAL(wp) ::  sizex            !<
98    REAL(wp) ::  sizey            !<
99    REAL(wp) ::  yright           !<
[1]100
[1320]101    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
[964]102                       title
[1092]103    NAMELIST /RAHMEN/  datleg
[1]104
105!
106!-- Close specified unit number (if opened) and set a flag that it has
107!-- been opened one time at least
108    IF ( file_id /= 0 )  THEN
109       IF ( openfile(file_id)%opened )  THEN
110          CLOSE ( file_id )
111          openfile(file_id)%opened        = .FALSE.
112          openfile(file_id)%opened_before = .TRUE.
113       ENDIF
114       RETURN
115    ENDIF
116
117!
118!-- Close all open unit numbers
[564]119    DO  fid = 1, 200+2*max_masks
[1]120
121       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
122!
123!--       Last actions for certain unit numbers
124          SELECT CASE ( fid )
125
126#if defined( __netcdf )
127             CASE ( 101 )
128
[1327]129                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]130                   nc_stat = NF90_CLOSE( id_set_xy(0) )
[263]131                   CALL handle_netcdf_error( 'close_file', 44 )
[1]132                ENDIF
133
134             CASE ( 102 )
135
[1327]136                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]137                   nc_stat = NF90_CLOSE( id_set_xz(0) )
[263]138                   CALL handle_netcdf_error( 'close_file', 45 )
[1]139                ENDIF
140
141             CASE ( 103 )
142
[1327]143                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]144                   nc_stat = NF90_CLOSE( id_set_yz(0) )
[263]145                   CALL handle_netcdf_error( 'close_file', 46 )
[1]146                ENDIF
147
148             CASE ( 104 )
149
[1327]150                IF ( myid == 0 )  THEN
[1]151                   nc_stat = NF90_CLOSE( id_set_pr )
[263]152                   CALL handle_netcdf_error( 'close_file', 47 )
[1]153                ENDIF
154
155             CASE ( 105 )
156
[1327]157                IF ( myid == 0 )  THEN
[1]158                   nc_stat = NF90_CLOSE( id_set_ts )
[263]159                   CALL handle_netcdf_error( 'close_file', 48 )
[1]160                ENDIF
161
162             CASE ( 106 )
163
[1327]164                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]165                   nc_stat = NF90_CLOSE( id_set_3d(0) )
[263]166                   CALL handle_netcdf_error( 'close_file', 49 )
[1]167                ENDIF
168
169             CASE ( 107 )
170
[1327]171                IF ( myid == 0 )  THEN
[1]172                   nc_stat = NF90_CLOSE( id_set_sp )
[263]173                   CALL handle_netcdf_error( 'close_file', 50 )
[1]174                ENDIF
175
176             CASE ( 108 )
177
[1327]178                nc_stat = NF90_CLOSE( id_set_prt )
179                CALL handle_netcdf_error( 'close_file', 51 )
[1]180
181             CASE ( 109 ) 
182
[1327]183                nc_stat = NF90_CLOSE( id_set_pts )
184                CALL handle_netcdf_error( 'close_file', 412 )
[1]185
186             CASE ( 111 )
187
[1327]188                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]189                   nc_stat = NF90_CLOSE( id_set_xy(1) )
[263]190                   CALL handle_netcdf_error( 'close_file', 52 )
[1]191                ENDIF
192
193             CASE ( 112 )
194
[1327]195                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]196                   nc_stat = NF90_CLOSE( id_set_xz(1) )
[263]197                   CALL handle_netcdf_error( 'close_file', 352 )
[1]198                ENDIF
199
200             CASE ( 113 )
201
[1327]202                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]203                   nc_stat = NF90_CLOSE( id_set_yz(1) )
[263]204                   CALL handle_netcdf_error( 'close_file', 353 )
[1]205                ENDIF
206
207             CASE ( 116 )
208
[1327]209                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[1]210                   nc_stat = NF90_CLOSE( id_set_3d(1) )
[263]211                   CALL handle_netcdf_error( 'close_file', 353 )
[1]212                ENDIF
213
[564]214             CASE ( 201:200+2*max_masks )
[410]215             
[1327]216                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
[410]217!
218!--                decompose fid into mid and av
[564]219                   IF ( fid <= 200+max_masks )  THEN
220                      mid = fid - 200
[410]221                      av = 0
222                   ELSE
[564]223                      mid = fid - (200+max_masks)
[410]224                      av = 1
225                   ENDIF
226                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
[564]227                   CALL handle_netcdf_error( 'close_file', 459 )
[410]228               
229                ENDIF
230
[1]231#endif
232
233          END SELECT
234!
235!--       Close file
236          IF ( openfile(fid)%opened )  CLOSE ( fid )
237
238       ENDIF
239
240    ENDDO
241
242!
243!-- Formats
[1320]2443200 FORMAT ('# AVS',A,'field file'/                                           &
245             '#'/                                                              &
246             '# ',A/                                                           &
247             'ndim=3'/                                                         &
248             'dim1=',I5/                                                       &
249             'dim2=',I5/                                                       &
250             'dim3=',I5/                                                       &
251             'nspace=3'/                                                       &
252             'veclen=',I5/                                                     &
253             'data=xdr_float'/                                                 &
[1]254             'field=rectilinear')
2554000 FORMAT ('time averaged over',F7.1,' s')
256
257
258 END SUBROUTINE close_file
Note: See TracBrowser for help on using the repository browser.