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

    r1510 r1682  
    1  SUBROUTINE check_for_restart
    2 
     1!> @file check_for_restart.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5655! Description:
    5756! ------------
    58 ! Set stop flag, if restart is neccessary because of expiring cpu-time or
    59 ! if it is forced by user
     57!> Set stop flag, if restart is neccessary because of expiring cpu-time or
     58!> if it is forced by user
    6059!------------------------------------------------------------------------------!
     60 SUBROUTINE check_for_restart
     61 
    6162
    6263    USE control_parameters,                                                    &
     
    7273
    7374
    74     LOGICAL :: terminate_run_l           !:
    75     LOGICAL :: do_stop_now = .FALSE.     !:
    76     LOGICAL :: do_restart_now = .FALSE.  !:
    77 
    78     REAL(wp) ::  remaining_time !:
     75    LOGICAL :: terminate_run_l           !<
     76    LOGICAL :: do_stop_now = .FALSE.     !<
     77    LOGICAL :: do_restart_now = .FALSE.  !<
     78
     79    REAL(wp) ::  remaining_time !<
    7980
    8081
Note: See TracChangeset for help on using the changeset viewer.