source: palm/trunk/SOURCE/progress_bar.f90 @ 1437

Last change on this file since 1437 was 1402, checked in by raasch, 10 years ago

output of location messages complemented, output of location bar added
(Makefile, check_parameters, cpulog, init_pegrid, init_3d_model, message, palm, parin, time_integration, new: progress_bar)
preprocessor switch intel_compiler added, -r8 compiler options removed
(.mrun.config.default, .mrun.config.imuk, .mrun.config.kiaps)

batch_job added to envpar-NAMELIST
(mrun, parin)

  • Property svn:keywords set to Id
File size: 5.1 KB
Line 
1 MODULE progress_bar
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: progress_bar.f90 1402 2014-05-09 14:25:13Z raasch $
27!
28! Description:
29! ------------
30! CPU-time measurements for any program part whatever. Results of the
31!------------------------------------------------------------------------------!
32
33    USE control_parameters,                                                    &
34        ONLY : end_time, simulated_time, simulated_time_at_begin, time_restart
35
36    USE, INTRINSIC ::  ISO_FORTRAN_ENV,                                     &
37        ONLY :  OUTPUT_UNIT
38
39    USE kinds
40
41    IMPLICIT NONE
42
43    PRIVATE
44    PUBLIC   batch_job, finish_progress_bar, output_progress_bar
45
46    CHARACTER(LEN=60) ::  bar      !: progress bar, initially filled with "_"
47    CHARACTER(LEN=60) ::  crosses  !: filled with "X"
48
49    INTEGER(iwp) ::  ilength !: length of progress bar filled with "X"
50
51    LOGICAL ::  batch_job = .FALSE.   !: switch to determine the run mode
52
53    REAL(wp) ::  time_to_be_simulated !: in sec
54
55    LOGICAL ::  initialized = .FALSE. !: switch to determine if bar is initialized
56
57    SAVE
58
59 CONTAINS
60
61    SUBROUTINE init_progress_bar
62
63       IMPLICIT NONE
64
65!
66!--    Calculate the time to be simulated in this job
67!--    (in case of automatic restarts the calculated time will probably be
68!--    larger than the time which will actually be simulated)
69       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time  .AND.&
70            time_restart > simulated_time_at_begin )  THEN
71          time_to_be_simulated = time_restart - simulated_time_at_begin
72       ELSE
73          time_to_be_simulated = end_time     - simulated_time_at_begin
74       ENDIF
75
76       bar = '____________________________________________________________'
77       crosses = 'XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
78!
79!--    Line feed on stdout to seperate the progress bar from previous messages
80       WRITE ( OUTPUT_UNIT, '(1X)' )
81#if defined( __intel_compiler )
82!
83!--    The Intel compiler does not allow to immediately flush the output buffer
84!--    in case that option ADVANCE='NO' is used in the write statement.
85!--    A workaround is to set a special carriage control feature and use "+" as
86!--    first output character, but this non-standard and only available with the
87!--    Intel compiler
88       OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='FORTRAN' )
89#endif
90       initialized = .TRUE.
91
92    END SUBROUTINE init_progress_bar
93
94
95    SUBROUTINE output_progress_bar
96!------------------------------------------------------------------------------!
97! Description:
98! ------------
99!
100!------------------------------------------------------------------------------!
101
102       IMPLICIT NONE
103
104       REAL(wp) ::  remaining_time_in_percent  !: remaining time to be simulated
105                                               !: in the job
106
107!
108!--    Porgress bar does not make sense in batch mode (and also ADVANCE=no does
109!--    not properly work in batch mode on Cray XC30)
110       IF ( batch_job )  RETURN
111
112       IF ( .NOT. initialized )  CALL init_progress_bar
113!
114!--    Calculate length of progress bar
115       remaining_time_in_percent =                                             &
116             ( simulated_time - simulated_time_at_begin ) / time_to_be_simulated
117
118       ilength = remaining_time_in_percent * 60.0_wp
119       ilength = MIN( ilength, 60 )
120
121       bar(1:ilength) = crosses(1:ilength)
122
123#if defined( __intel_compiler )
124       WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')' )           &
125               '+', bar,                                                       &
126                MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
127#else
128       WRITE ( OUTPUT_UNIT, '(A,6X,''['',A,''] '',F5.1,'' left'')',            &
129               ADVANCE='NO' )  CHAR( 13 ), bar,                                &
130                MAX( 0.0_wp, ( 1.0_wp - remaining_time_in_percent ) * 100.0_wp )
131#endif
132       CALL local_flush( OUTPUT_UNIT )
133
134    END SUBROUTINE output_progress_bar
135
136    SUBROUTINE finish_progress_bar
137
138       IMPLICIT NONE
139
140       IF ( batch_job )  RETURN
141
142#if defined( __intel_compiler )
143!
144!--    Reset to the default carriage control
145       OPEN ( OUTPUT_UNIT, CARRIAGECONTROL='LIST' )
146#endif
147!
148!--    Line feed when simulation has finished
149       WRITE ( OUTPUT_UNIT, '(1X)' )
150
151    END SUBROUTINE finish_progress_bar
152
153 END MODULE progress_bar
Note: See TracBrowser for help on using the repository browser.