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

    r1469 r1682  
    1  MODULE progress_bar
    2 
     1!> @file progress_bar.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    3130! Description:
    3231! ------------
    33 ! This routine prints either a progress bar on the standard output in case of
    34 ! interactive runs, or it prints the progress in a separate file called
    35 ! PROGRESS.
    36 !------------------------------------------------------------------------------!
     32!> This routine prints either a progress bar on the standard output in case of
     33!> interactive runs, or it prints the progress in a separate file called
     34!> PROGRESS.
     35!------------------------------------------------------------------------------!
     36 MODULE progress_bar
     37 
    3738
    3839    USE control_parameters,                                                    &
     
    5051    PUBLIC   batch_job, finish_progress_bar, output_progress_bar
    5152
    52     CHARACTER(LEN=60) ::  bar      !: progress bar, initially filled with "_"
    53     CHARACTER(LEN=60) ::  crosses  !: filled with "X"
    54 
    55     INTEGER(iwp) ::  ilength !: length of progress bar filled with "X"
    56 
    57     LOGICAL ::  batch_job = .FALSE.   !: switch to determine the run mode
    58 
    59     REAL(wp) ::  time_to_be_simulated !: in sec
    60 
    61     LOGICAL ::  initialized = .FALSE. !: switch to determine if bar is initialized
     53    CHARACTER(LEN=60) ::  bar      !< progress bar, initially filled with "_"
     54    CHARACTER(LEN=60) ::  crosses  !< filled with "X"
     55
     56    INTEGER(iwp) ::  ilength !< length of progress bar filled with "X"
     57
     58    LOGICAL ::  batch_job = .FALSE.   !< switch to determine the run mode
     59
     60    REAL(wp) ::  time_to_be_simulated !< in sec
     61
     62    LOGICAL ::  initialized = .FALSE. !< switch to determine if bar is initialized
    6263
    6364    SAVE
     
    6566 CONTAINS
    6667
     68!------------------------------------------------------------------------------!
     69! Description:
     70! ------------
     71!> Initialize the progress bar/file
     72!------------------------------------------------------------------------------!
     73 
    6774    SUBROUTINE init_progress_bar
    68 !------------------------------------------------------------------------------!
    69 ! Description:
    70 ! ------------
    71 ! Initialize the progress bar/file
    72 !------------------------------------------------------------------------------!
    7375
    7476       IMPLICIT NONE
     
    113115
    114116
     117!------------------------------------------------------------------------------!
     118! Description:
     119! ------------
     120!> Print progress data to standard output (interactive) or to file (batch jobs)
     121!------------------------------------------------------------------------------!
     122 
    115123    SUBROUTINE output_progress_bar
    116 !------------------------------------------------------------------------------!
    117 ! Description:
    118 ! ------------
    119 ! Print progress data to standard output (interactive) or to file (batch jobs)
    120 !------------------------------------------------------------------------------!
    121124
    122125       IMPLICIT NONE
    123126
    124        REAL(wp) ::  remaining_time_in_percent  !: remaining time to be simulated
    125                                                !: in the job
    126        REAL(wp) ::  remaining_time_in_percent_total !: total remaining time of
    127                                                     !: the job chain
     127       REAL(wp) ::  remaining_time_in_percent  !< remaining time to be simulated
     128                                               !< in the job
     129       REAL(wp) ::  remaining_time_in_percent_total !< total remaining time of
     130                                                    !< the job chain
    128131
    129132       IF ( .NOT. initialized )  CALL init_progress_bar
     
    170173    END SUBROUTINE output_progress_bar
    171174
     175!------------------------------------------------------------------------------!
     176! Description:
     177! ------------
     178!> Finalization of the progress bar/file
     179!------------------------------------------------------------------------------!
     180 
    172181    SUBROUTINE finish_progress_bar
    173 !------------------------------------------------------------------------------!
    174 ! Description:
    175 ! ------------
    176 ! Finalization of the progress bar/file
    177 !------------------------------------------------------------------------------!
    178182
    179183       IMPLICIT NONE
Note: See TracChangeset for help on using the changeset viewer.