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

Last change on this file since 1818 was 1818, checked in by maronga, 8 years ago

last commit documented / copyright update

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