Ignore:
Timestamp:
Jun 11, 2020 8:51:48 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/close_file.f90

    r4360 r4559  
    11!> @file close_file.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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.
    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/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 4069 2019-07-01 14:05:51Z Giersch
    30 ! Masked output running index mid has been introduced as a local variable to 
     32! Masked output running index mid has been introduced as a local variable to
    3133! avoid runtime error (Loop variable has been modified) in time_integration
    32 ! 
     34!
    3335! 3655 2019-01-07 16:51:22Z knoop
    3436! unused variables and format statements removed
     
    4042! Description:
    4143! ------------
    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.
    45 !------------------------------------------------------------------------------!
     44!> Close specified file or all open files, if "0" has been given as the calling argument. In that
     45!> case, execute last actions for certain unit numbers, if required.
     46!--------------------------------------------------------------------------------------------------!
    4647 SUBROUTINE close_file( file_id )
    47  
    48 
    49     USE control_parameters,                                                    &
     48
     49
     50    USE control_parameters,                                                                        &
    5051        ONLY:  max_masks, openfile
    51                
     52
    5253    USE kinds
    53    
     54
    5455#if defined( __netcdf )
    5556    USE NETCDF
     
    5758
    5859    USE netcdf_interface,                                                      &
    59         ONLY:  id_set_mask, id_set_pr, id_set_pts, id_set_sp,                  &
    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
    62                
    63     USE pegrid                                           
     60        ONLY:  id_set_mask, id_set_pr, id_set_pts, id_set_sp,  id_set_ts, id_set_xy, id_set_xz,    &
     61               id_set_yz, id_set_3d, id_set_fl, nc_stat, netcdf_data_format, netcdf_handle_error
     62
     63    USE pegrid
    6464
    6565    IMPLICIT NONE
    6666
    67     CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
    68     CHARACTER (LEN=80)  ::  title                  !<
    69 
    70     INTEGER(iwp) ::  av           !<
    71     INTEGER(iwp) ::  dimx         !<
    72     INTEGER(iwp) ::  dimy         !<
    73     INTEGER(iwp) ::  fid          !<
    74     INTEGER(iwp) ::  file_id      !<
    75     INTEGER(iwp) ::  mid          !< masked output running index
    76     INTEGER(iwp) ::  planz        !<
    77 
    78     LOGICAL ::  checkuf = .TRUE.  !<
    79     LOGICAL ::  datleg = .TRUE.   !<
    80     LOGICAL ::  dbp = .FALSE.     !<
    81 
    82     NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
    83                        title
     67    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
     68    CHARACTER (LEN=80)  ::  title                  !<
     69
     70    INTEGER(iwp) ::  av           !<
     71    INTEGER(iwp) ::  dimx         !<
     72    INTEGER(iwp) ::  dimy         !<
     73    INTEGER(iwp) ::  fid          !<
     74    INTEGER(iwp) ::  file_id      !<
     75    INTEGER(iwp) ::  mid          !< masked output running index
     76    INTEGER(iwp) ::  planz        !<
     77
     78    LOGICAL ::  checkuf = .TRUE.  !<
     79    LOGICAL ::  datleg = .TRUE.   !<
     80    LOGICAL ::  dbp = .FALSE.     !<
     81
     82    NAMELIST /GLOBAL/  checkuf, datform, dbp, dimx, dimy, planz, title
    8483    NAMELIST /RAHMEN/  datleg
    8584
    8685!
    87 !-- Close specified unit number (if opened) and set a flag that it has
    88 !-- been opened one time at least
     86!-- Close specified unit number (if opened) and set a flag that it has been opened one time at least
    8987    IF ( file_id /= 0 )  THEN
    9088       IF ( openfile(file_id)%opened )  THEN
     
    162160!                CALL netcdf_handle_error( 'close_file', 51 )
    163161
    164              CASE ( 109 ) 
     162             CASE ( 109 )
    165163
    166164                nc_stat = NF90_CLOSE( id_set_pts )
     
    206204                IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
    207205!
    208 !--                decompose fid into mid and av
     206!--                Decompose fid into mid and av
    209207                   IF ( fid <= 200+max_masks )  THEN
    210208                      mid = fid - 200
Note: See TracChangeset for help on using the changeset viewer.