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/local_tremain.f90

    r1354 r1682  
    1  SUBROUTINE local_tremain( remaining_time )
    2 
     1!> @file local_tremain.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4948! Description:
    5049! ------------
    51 ! For different operating systems get the remaining cpu-time of the job
     50!> For different operating systems get the remaining cpu-time of the job
    5251!------------------------------------------------------------------------------!
     52 SUBROUTINE local_tremain( remaining_time )
     53 
    5354
    5455    USE control_parameters,                                                    &
     
    6465    IMPLICIT NONE
    6566
    66     REAL(wp)     ::  remaining_time        !:
     67    REAL(wp)     ::  remaining_time        !<
    6768#if defined( __ibm )
    68     INTEGER(idp) ::  IRTC                  !:
    69     REAL(wp)     ::  actual_wallclock_time !:
     69    INTEGER(idp) ::  IRTC                  !<
     70    REAL(wp)     ::  actual_wallclock_time !<
    7071#elif defined( __lc )
    71     INTEGER(idp) ::  count                 !:
    72     INTEGER(idp) ::  count_rate            !:
    73     REAL(wp)     ::  actual_wallclock_time !:
     72    INTEGER(idp) ::  count                 !<
     73    INTEGER(idp) ::  count_rate            !<
     74    REAL(wp)     ::  actual_wallclock_time !<
    7475#endif
    7576
Note: See TracChangeset for help on using the changeset viewer.