Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

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

    r1329 r1682  
    1  SUBROUTINE close_file( file_id )
    2 
     1!> @file close_file.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5554! Description:
    5655! ------------
    57 ! Close specified file or all open files, if "0" has been given as the
    58 ! calling argument. In that case, execute last actions for certain unit
    59 ! numbers, if required.
     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.
    6059!------------------------------------------------------------------------------!
     60 SUBROUTINE close_file( file_id )
     61 
    6162
    6263    USE control_parameters,                                                    &
     
    8081    IMPLICIT NONE
    8182
    82     CHARACTER (LEN=10)  ::  datform = 'lit_endian' !:
    83     CHARACTER (LEN=80)  ::  title                  !:
    84 
    85     INTEGER(iwp) ::  av           !:
    86     INTEGER(iwp) ::  dimx         !:
    87     INTEGER(iwp) ::  dimy         !:
    88     INTEGER(iwp) ::  fid          !:
    89     INTEGER(iwp) ::  file_id      !:
    90     INTEGER(iwp) ::  planz        !:
    91 
    92     LOGICAL ::  checkuf = .TRUE.  !:
    93     LOGICAL ::  datleg = .TRUE.   !:
    94     LOGICAL ::  dbp = .FALSE.     !:
    95 
    96     REAL(wp) ::  sizex            !:
    97     REAL(wp) ::  sizey            !:
    98     REAL(wp) ::  yright           !:
     83    CHARACTER (LEN=10)  ::  datform = 'lit_endian' !<
     84    CHARACTER (LEN=80)  ::  title                  !<
     85
     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        !<
     92
     93    LOGICAL ::  checkuf = .TRUE.  !<
     94    LOGICAL ::  datleg = .TRUE.   !<
     95    LOGICAL ::  dbp = .FALSE.     !<
     96
     97    REAL(wp) ::  sizex            !<
     98    REAL(wp) ::  sizey            !<
     99    REAL(wp) ::  yright           !<
    99100
    100101    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dbp, planz,               &
Note: See TracChangeset for help on using the changeset viewer.