source: palm/trunk/SOURCE/progress_bar_mod.f90 @ 4850

Last change on this file since 4850 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 7.9 KB
RevLine 
[1850]1!> @file progress_bar_mod.f90
[4649]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1402]4!
[4649]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.
[1402]8!
[4649]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.
[1402]12!
[4649]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/>.
[1402]15!
[4828]16! Copyright 1997-2021 Leibniz Universitaet Hannover
[4649]17!--------------------------------------------------------------------------------------------------!
[1402]18!
[4649]19!
[1402]20! Current revisions:
21! -----------------
[4649]22!
23!
[1402]24! Former revisions:
25! -----------------
26! $Id: progress_bar_mod.f90 4828 2021-01-05 11:21:41Z suehring $
[4649]27! File re-formatted to follow the PALM coding standard
28!
29! 4360 2020-01-07 11:25:50Z suehring
[4182]30! Corrected "Former revisions" section
[4649]31!
[4182]32! 3655 2019-01-07 16:51:22Z knoop
[4649]33! Increased printed length of run identifier, bugfix for restarts
34
[4182]35! 1468 2014-09-24 14:06:57Z maronga
36! Added support for progress file PROGRESS which is used in case of batch jobs
[1402]37!
[4649]38!--------------------------------------------------------------------------------------------------!
[1402]39! Description:
40! ------------
[4649]41!> This routine prints either a progress bar on the standard output in case of interactive runs, or
42!> it prints the progress in a separate file called PROGRESS.
43!--------------------------------------------------------------------------------------------------!
[1682]44 MODULE progress_bar
[1402]45
46
[4649]47    USE control_parameters,                                                                        &
48        ONLY : end_time,                                                                           &
49               initializing_actions,                                                               &
50               run_identifier,                                                                     &
51               simulated_time,                                                                     &
52               simulated_time_at_begin,                                                            &
53               spinup_time,                                                                        &
54               time_restart
55
56    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                                            &
[1402]57        ONLY :  OUTPUT_UNIT
58
59    USE kinds
60
61    IMPLICIT NONE
62
63    PRIVATE
[3313]64    PUBLIC   progress_bar_disabled, finish_progress_bar, output_progress_bar
[1402]65
[1682]66    CHARACTER(LEN=60) ::  bar      !< progress bar, initially filled with "_"
67    CHARACTER(LEN=60) ::  crosses  !< filled with "X"
[1402]68
[1682]69    INTEGER(iwp) ::  ilength !< length of progress bar filled with "X"
[1402]70
[3313]71    LOGICAL ::  progress_bar_disabled = .FALSE.   !< envpar-Namelist switch
[1402]72
[4649]73    LOGICAL ::  initialized = .FALSE. !< switch to determine if bar is initialized
74
[1682]75    REAL(wp) ::  time_to_be_simulated !< in sec
[1402]76
77    SAVE
78
79 CONTAINS
80
[4649]81!--------------------------------------------------------------------------------------------------!
[1468]82! Description:
83! ------------
[1682]84!> Initialize the progress bar/file
[4649]85!--------------------------------------------------------------------------------------------------!
[1402]86
[4649]87 SUBROUTINE init_progress_bar
[1402]88
[4649]89    IMPLICIT NONE
90
[1402]91!
[4649]92!-- Calculate the time to be simulated in this job (in case of automatic restarts the calculated
93!-- time will probably be larger than the time which will actually be simulated)
94    IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time  .AND.                       &
95         time_restart > simulated_time_at_begin )  THEN
96       time_to_be_simulated = time_restart - simulated_time_at_begin
97    ELSEIF ( initializing_actions == 'read_restart_data' )  THEN
98       time_to_be_simulated = end_time - simulated_time_at_begin
99    ELSE
100       time_to_be_simulated = end_time - simulated_time_at_begin - spinup_time
101    ENDIF
[1402]102
[4649]103    IF ( progress_bar_disabled )  THEN
[1468]104
[4649]105       CALL check_open ( 117 )
106       WRITE ( 117, FMT = '(A34,/)' ) run_identifier
[1468]107
[4649]108    ELSE
109       bar = '____________________________________________________________'
110       crosses = 'XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
[1402]111!
[4649]112!--    Line feed on stdout to seperate the progress bar from previous messages
113       WRITE ( OUTPUT_UNIT, '(1X)' )
[1402]114#if defined( __intel_compiler )
115!
[4649]116!--    The Intel compiler does not allow to immediately flush the output buffer in case that option
117!--    ADVANCE = 'NO' is used in the write statement. A workaround is to set a special carriage
118!--    control feature and use "+" as first output character, but this is non-standard and only
119!--    available with the Intel compiler.
120       OPEN ( OUTPUT_UNIT, CARRIAGECONTROL = 'FORTRAN' )
[1402]121#endif
[1468]122
[4649]123    ENDIF
[1468]124
[4649]125    initialized = .TRUE.
[1402]126
[4649]127 END SUBROUTINE init_progress_bar
[1402]128
129
[4649]130!--------------------------------------------------------------------------------------------------!
[1402]131! Description:
132! ------------
[1682]133!> Print progress data to standard output (interactive) or to file (batch jobs)
[4649]134!--------------------------------------------------------------------------------------------------!
[1402]135
[4649]136 SUBROUTINE output_progress_bar
[1402]137
[4649]138    IMPLICIT NONE
[1402]139
[4649]140    REAL(wp) ::  remaining_time_in_percent       !< remaining time to be simulated in the job
141    REAL(wp) ::  remaining_time_in_percent_total !< total remaining time of the job chain
[1468]142
[4649]143    IF ( .NOT. initialized )  CALL init_progress_bar
[1468]144
[4649]145    IF ( initializing_actions == 'read_restart_data' )  THEN
146       remaining_time_in_percent = ( simulated_time - simulated_time_at_begin )                    &
147                                   / time_to_be_simulated
[1468]148
[4649]149       remaining_time_in_percent_total = simulated_time / end_time
150    ELSE
151       remaining_time_in_percent = ( simulated_time - simulated_time_at_begin - spinup_time )      &
152                                   / time_to_be_simulated
[1468]153
[4649]154       remaining_time_in_percent_total = ( ( simulated_time - spinup_time )                        &
155                                           / ( end_time       - spinup_time ) )
156    ENDIF
157
[1402]158!
[4649]159!-- In batch mode, use a file (PROGRESS), otherwise use progress bar
160    IF ( progress_bar_disabled )  THEN
[1402]161
[4649]162       BACKSPACE ( 117 )
163       WRITE ( 117, FMT = '(F5.2,1X,F5.2)' ) remaining_time_in_percent,                              &
164                                             remaining_time_in_percent_total
165       FLUSH( 117 )
[1468]166
[4649]167    ELSE
[1468]168
[1402]169!
[4649]170!--    Calculate length of progress bar
171       ilength = remaining_time_in_percent * 60.0_wp
172       ilength = MIN( ilength, 60 )
[1402]173
[4649]174       bar(1:ilength) = crosses(1:ilength)
[1402]175
176#if defined( __intel_compiler )
[4649]177       WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')' ) '+', bar,                     &
178             MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
[1402]179#else
[4649]180       WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')', ADVANCE = 'NO' )  CHAR( 13 ),  &
181             bar, MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
[1402]182#endif
[4649]183       FLUSH( OUTPUT_UNIT )
[1402]184
[4649]185    ENDIF
[1468]186
[4649]187 END SUBROUTINE output_progress_bar
[1402]188
[4649]189!--------------------------------------------------------------------------------------------------!
[1468]190! Description:
191! ------------
[1682]192!> Finalization of the progress bar/file
[4649]193!--------------------------------------------------------------------------------------------------!
[1402]194
[4649]195 SUBROUTINE finish_progress_bar
[1402]196
[4649]197    IMPLICIT NONE
[1402]198
[4649]199    IF ( progress_bar_disabled )  THEN
[1468]200
[4649]201       CALL close_file ( 117 )
202
203    ELSE
204
[1402]205#if defined( __intel_compiler )
206!
[4649]207!--    Reset to the default carriage control
208       OPEN ( OUTPUT_UNIT, CARRIAGECONTROL = 'LIST' )
[1402]209#endif
210!
[4649]211!--    Line feed when simulation has finished
212       WRITE ( OUTPUT_UNIT, '(1X)' )
[1402]213
[4649]214    ENDIF
[1468]215
[4649]216 END SUBROUTINE finish_progress_bar
[1402]217
[1468]218
[1402]219 END MODULE progress_bar
Note: See TracBrowser for help on using the repository browser.