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

Last change on this file since 1327 was 1327, checked in by raasch, 10 years ago

Changed:


-s real64 removed (.mrun.config.hlrnIII)
-r8 removed (.mrun.config.imuk)
deleted: .mrun.config.imuk_ice2_netcdf4 .mrun.config.imuk_hlrn

REAL constants defined as wp-kind in modules

"baroclinicity" renamed "baroclinity", "ocean version" replaced by
"ocean mode"

code parts concerning old output formats "iso2d" and "avs" removed.
netCDF is the only remaining output format.

Errors:


bugfix: duplicate error message 56 removed

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