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
Line 
1!> @file progress_bar_mod.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
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.
8!
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.
12!
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/>.
15!
16! Copyright 1997-2021 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: progress_bar_mod.f90 4828 2021-01-05 11:21:41Z suehring $
27! File re-formatted to follow the PALM coding standard
28!
29! 4360 2020-01-07 11:25:50Z suehring
30! Corrected "Former revisions" section
31!
32! 3655 2019-01-07 16:51:22Z knoop
33! Increased printed length of run identifier, bugfix for restarts
34
35! 1468 2014-09-24 14:06:57Z maronga
36! Added support for progress file PROGRESS which is used in case of batch jobs
37!
38!--------------------------------------------------------------------------------------------------!
39! Description:
40! ------------
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!--------------------------------------------------------------------------------------------------!
44 MODULE progress_bar
45
46
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,                                                            &
57        ONLY :  OUTPUT_UNIT
58
59    USE kinds
60
61    IMPLICIT NONE
62
63    PRIVATE
64    PUBLIC   progress_bar_disabled, finish_progress_bar, output_progress_bar
65
66    CHARACTER(LEN=60) ::  bar      !< progress bar, initially filled with "_"
67    CHARACTER(LEN=60) ::  crosses  !< filled with "X"
68
69    INTEGER(iwp) ::  ilength !< length of progress bar filled with "X"
70
71    LOGICAL ::  progress_bar_disabled = .FALSE.   !< envpar-Namelist switch
72
73    LOGICAL ::  initialized = .FALSE. !< switch to determine if bar is initialized
74
75    REAL(wp) ::  time_to_be_simulated !< in sec
76
77    SAVE
78
79 CONTAINS
80
81!--------------------------------------------------------------------------------------------------!
82! Description:
83! ------------
84!> Initialize the progress bar/file
85!--------------------------------------------------------------------------------------------------!
86
87 SUBROUTINE init_progress_bar
88
89    IMPLICIT NONE
90
91!
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
102
103    IF ( progress_bar_disabled )  THEN
104
105       CALL check_open ( 117 )
106       WRITE ( 117, FMT = '(A34,/)' ) run_identifier
107
108    ELSE
109       bar = '____________________________________________________________'
110       crosses = 'XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
111!
112!--    Line feed on stdout to seperate the progress bar from previous messages
113       WRITE ( OUTPUT_UNIT, '(1X)' )
114#if defined( __intel_compiler )
115!
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' )
121#endif
122
123    ENDIF
124
125    initialized = .TRUE.
126
127 END SUBROUTINE init_progress_bar
128
129
130!--------------------------------------------------------------------------------------------------!
131! Description:
132! ------------
133!> Print progress data to standard output (interactive) or to file (batch jobs)
134!--------------------------------------------------------------------------------------------------!
135
136 SUBROUTINE output_progress_bar
137
138    IMPLICIT NONE
139
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
142
143    IF ( .NOT. initialized )  CALL init_progress_bar
144
145    IF ( initializing_actions == 'read_restart_data' )  THEN
146       remaining_time_in_percent = ( simulated_time - simulated_time_at_begin )                    &
147                                   / time_to_be_simulated
148
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
153
154       remaining_time_in_percent_total = ( ( simulated_time - spinup_time )                        &
155                                           / ( end_time       - spinup_time ) )
156    ENDIF
157
158!
159!-- In batch mode, use a file (PROGRESS), otherwise use progress bar
160    IF ( progress_bar_disabled )  THEN
161
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 )
166
167    ELSE
168
169!
170!--    Calculate length of progress bar
171       ilength = remaining_time_in_percent * 60.0_wp
172       ilength = MIN( ilength, 60 )
173
174       bar(1:ilength) = crosses(1:ilength)
175
176#if defined( __intel_compiler )
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 )
179#else
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 )
182#endif
183       FLUSH( OUTPUT_UNIT )
184
185    ENDIF
186
187 END SUBROUTINE output_progress_bar
188
189!--------------------------------------------------------------------------------------------------!
190! Description:
191! ------------
192!> Finalization of the progress bar/file
193!--------------------------------------------------------------------------------------------------!
194
195 SUBROUTINE finish_progress_bar
196
197    IMPLICIT NONE
198
199    IF ( progress_bar_disabled )  THEN
200
201       CALL close_file ( 117 )
202
203    ELSE
204
205#if defined( __intel_compiler )
206!
207!--    Reset to the default carriage control
208       OPEN ( OUTPUT_UNIT, CARRIAGECONTROL = 'LIST' )
209#endif
210!
211!--    Line feed when simulation has finished
212       WRITE ( OUTPUT_UNIT, '(1X)' )
213
214    ENDIF
215
216 END SUBROUTINE finish_progress_bar
217
218
219 END MODULE progress_bar
Note: See TracBrowser for help on using the repository browser.