source: palm/trunk/UTIL/inifor/src/inifor_control.f90 @ 4671

Last change on this file since 4671 was 4659, checked in by eckhard, 4 years ago

inifor: Support for COSMO cloud water and precipitation

  • Property svn:keywords set to Id
File size: 12.9 KB
RevLine 
[3447]1!> @file src/inifor_control.f90
[2696]2!------------------------------------------------------------------------------!
[2718]3! This file is part of the PALM model system.
[2696]4!
[2718]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
[2696]8! version.
9!
[2718]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.
[2696]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!
[4481]17! Copyright 2017-2020 Leibniz Universitaet Hannover
18! Copyright 2017-2020 Deutscher Wetterdienst Offenbach
[2696]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
[4659]23!
24!
[2696]25! Former revisions:
26! -----------------
27! $Id: inifor_control.f90 4659 2020-08-31 11:21:17Z pavelkrc $
[4659]28! List warnings after successful run or abort
29! Produce failure exit code (1) on program abort for test automation
30! Improved code formatting
31!
32!
33! 4523 2020-05-07 15:58:16Z eckhard
[4523]34! respect integer working precision (iwp) specified in inifor_defs.f90
35!
36!
37! 4481 2020-03-31 18:55:54Z maronga
[4475]38! Change output format in routine report to allow for better message formatting
39!
40! 3997 2019-05-23 12:35:57Z eckhard
[3997]41! Added warnings counter
42!
43!
44! 3866 2019-04-05 14:25:01Z eckhard
[3866]45! Use PALM's working precision
46! Renamed run_control -> log_runtime
47! Open log file only once
48! Improved coding style
49!
50!
51! 3785 2019-03-06 10:41:14Z eckhard
[3678]52! Added message buffer for displaying tips to rectify encountered errors
53!
54!
55! 3618 2018-12-10 13:25:22Z eckhard
[3618]56! Prefixed all INIFOR modules with inifor_
57!
58!
59! 3614 2018-12-10 07:05:46Z raasch
[3614]60! abort renamed inifor_abort to avoid intrinsic problem in Fortran
61!
62! 3557 2018-11-22 16:01:22Z eckhard
[3557]63! Updated documentation
64!
65!
66! 3447 2018-10-29 15:52:54Z eckhard
[3447]67! Renamed source files for compatibilty with PALM build system
68!
69!
70! 3395 2018-10-22 17:32:49Z eckhard
[3395]71! Suppress debugging messages unless --debug option is given
72!
73!
74! 3183 2018-07-27 14:25:55Z suehring
[3183]75! Added version and copyright output
76!
77!
78! 3182 2018-07-27 13:36:03Z suehring
[2696]79! Initial revision
80!
81!
82!
83! Authors:
84! --------
[3557]85!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
[2696]86!
87! Description:
88! ------------
89!> The control module provides routines for timing INIFOR and writing runtime
90!> feedback to the terminal and a log file.
91!------------------------------------------------------------------------------!
[3618]92 MODULE inifor_control
[2696]93
[3618]94    USE inifor_defs,                                                           &
[4659]95        ONLY:  COPYRIGHT, LNAME, LOG_FILE_NAME, PATH, VERSION, iwp, wp
[3618]96    USE inifor_util,                                                           &
[4659]97        ONLY:  real_to_str, real_to_str_f, str
[2696]98
99    IMPLICIT NONE
100
[4659]101    INTEGER(iwp), SAVE         ::  u                     !< Fortran file unit for the log file
102    INTEGER(iwp), PARAMETER    ::  n_max_wrngs = 512     !< Fortran file unit for the log file
103    INTEGER(iwp), SAVE         ::  n_wrngs = 0           !< Fortran file unit for the log file
104    CHARACTER (LEN=5000)       ::  message = ''          !< log message buffer
105    CHARACTER (LEN=5000)       ::  tip     = ''          !< optional log message buffer for tips on how to rectify encountered errors
106    CHARACTER (LEN=5000), SAVE ::  warnings(n_max_wrngs) !< log of warnings
[2696]107
108 CONTAINS
109
[3557]110!------------------------------------------------------------------------------!
111! Description:
112! ------------
113!>
114!> report() is INIFOR's general logging routine. It prints the given 'message'
115!> to the terminal and writes it to the INIFOR log file.
116!>
117!> You can use this routine to log events across INIFOR's code to log. For
118!> warnings and abort messages, you may use the dedicated routines warn() and
[3614]119!> inifor_abort() in this module. Both use report() and add specific behaviour
120!> to it.
[3557]121!------------------------------------------------------------------------------!
[4659]122 SUBROUTINE report( routine, message, debug )
[2696]123
[3866]124    CHARACTER(LEN=*), INTENT(IN)  ::  routine !< name of calling subroutine of function
125    CHARACTER(LEN=*), INTENT(IN)  ::  message !< log message
126    LOGICAL, OPTIONAL, INTENT(IN) ::  debug   !< flag the current message as debugging message
[2696]127
[3866]128    LOGICAL, SAVE                 ::  is_first_run = .TRUE. !< control flag for file opening mode
129    LOGICAL                       ::  suppress_message      !< control falg for additional debugging log
[2696]130
[3866]131    IF ( is_first_run )  THEN
132       OPEN( NEWUNIT=u, FILE=LOG_FILE_NAME, STATUS='replace' )
133       is_first_run = .FALSE.
134    ENDIF
135       
[3557]136
[3866]137    suppress_message = .FALSE.
[4659]138    IF ( PRESENT( debug ) )  THEN
[3866]139       IF ( .NOT. debug )  suppress_message = .TRUE.
140    ENDIF
[2696]141
[3866]142    IF ( .NOT. suppress_message )  THEN
[4659]143       CALL write_to_sdtout_and_logfile(                                       &
144          TRIM( message ) // "  [ " // TRIM( routine ) // " ]"                 &
145       )
[3866]146    ENDIF
[3395]147
[3866]148 END SUBROUTINE report
[3395]149
[2696]150
[3557]151!------------------------------------------------------------------------------!
152! Description:
153! ------------
[4659]154!> This routine writes the given message to SDTOUT as well as to the INIFOR log
155!> file.
156!------------------------------------------------------------------------------!
157 SUBROUTINE write_to_sdtout_and_logfile( message )
158
159    CHARACTER(LEN=*), INTENT(IN)  ::  message
160
161    WRITE(*, '(A)') "inifor: " // TRIM( message )
162    WRITE(u, '(A)') TRIM( message )
163
164 END SUBROUTINE write_to_sdtout_and_logfile
165
166
167!------------------------------------------------------------------------------!
168! Description:
169! ------------
[3557]170!>
171!> warn() prepends "WARNING:" the given 'message' and prints the result to the
172!> terminal and writes it to the INIFOR logfile.
173!>
174!> You can use this routine for messaging issues, that still allow INIFOR to
175!> continue.
176!------------------------------------------------------------------------------!
[4659]177 SUBROUTINE warn( routine, message )
[2696]178
[3866]179    CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
180    CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
[2696]181
[4659]182    CALL cache_warning( routine, message )
183    CALL report( routine, "WARNING: " // TRIM( message ) )
[2696]184
[3866]185 END SUBROUTINE warn
[2696]186
187
[4659]188 SUBROUTINE cache_warning( routine, message )
189
190    CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
191    CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
192
193    n_wrngs = n_wrngs + 1
194    warnings(n_wrngs) = "  WARNING: " // TRIM( message ) //                      &
195                        "  [ " // TRIM( routine ) // " ]"
196
197 END SUBROUTINE cache_warning
198
199
[3557]200!------------------------------------------------------------------------------!
201! Description:
202! ------------
203!>
[4659]204!> This routine writes all warnings cached with cache_warning() to STDOUT
205!> and the INIFOR log file.
206!------------------------------------------------------------------------------!
207 SUBROUTINE report_warnings()
208
209    INTEGER(iwp) ::  warning_idx
210
211    IF (n_wrngs > 0)  THEN
212       message = 'Encountered the following '// TRIM( str( n_wrngs ) ) // " warning(s) during this run:"
213       CALL report( 'report_warnings', message )
214
215       DO warning_idx = 1, n_wrngs
216          CALL write_to_sdtout_and_logfile( warnings(warning_idx) )
217       ENDDO
218    ENDIF
219
220 END SUBROUTINE report_warnings
221
222!------------------------------------------------------------------------------!
223! Description:
224! ------------
225!>
226!> Report successful run. To be called at the end of the main loop.
227!------------------------------------------------------------------------------!
228 SUBROUTINE report_success( output_file_name )
229
230    CHARACTER(LEN=PATH), INTENT(IN) ::  output_file_name
231
232    message = "Finished writing dynamic driver '" // TRIM( output_file_name )
233    message = TRIM( message ) // "' successfully."
234    IF (n_wrngs > 0)  THEN
235       message = TRIM( message ) // " Some warnings were encountered."
236    ENDIF
237    CALL report( 'main loop', message )
238
239 END SUBROUTINE report_success
240   
241
242!------------------------------------------------------------------------------!
243! Description:
244! ------------
245!>
246!> Report runtime statistics
247!------------------------------------------------------------------------------!
248 SUBROUTINE report_runtime()
249
250    CALL log_runtime( 'report', 'void' )
251
252 END SUBROUTINE report_runtime
253
254
255!------------------------------------------------------------------------------!
256! Description:
257! ------------
258!>
[3614]259!> inifor_abort() prepends "ERROR:" the given 'message' and prints the result to
260!> stdout, writes it to the INIFOR logfile, and exits INIFOR.
[3557]261!>
262!> You can use this routine for messaging issues, that are critical and prevent
263!> INIFOR from continueing.
264!------------------------------------------------------------------------------!
[4659]265 SUBROUTINE inifor_abort( routine , message )
[2696]266
[3866]267    CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
268    CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
[2696]269
[4659]270    CALL report( routine, "ERROR: " // TRIM( message ) // " Stopping." )
271    CALL report_warnings
[3866]272    CALL close_log
[4659]273    CALL EXIT(1)
[2696]274
[3866]275 END SUBROUTINE inifor_abort
[2696]276
277
[3866]278 SUBROUTINE close_log()
279
[4659]280    CLOSE( u )
[3866]281
282 END SUBROUTINE close_log
283
284
[3557]285!------------------------------------------------------------------------------!
286! Description:
287! ------------
288!>
289!> print_version() prints the INIFOR version number and copyright notice.
290!------------------------------------------------------------------------------!
[3866]291 SUBROUTINE print_version()
292    PRINT *, "INIFOR " // VERSION
293    PRINT *, COPYRIGHT
294 END SUBROUTINE print_version
[3182]295
296
[3557]297!------------------------------------------------------------------------------!
298! Description:
299! ------------
300!>
[3866]301!> log_runtime() measures the run times of various parts of INIFOR and
[3557]302!> accumulates them in timing budgets.
303!------------------------------------------------------------------------------!
[4659]304 SUBROUTINE log_runtime( mode, budget )
[2696]305
[3866]306    CHARACTER(LEN=*), INTENT(IN) ::  mode   !< name of the calling mode
307    CHARACTER(LEN=*), INTENT(IN) ::  budget !< name of the timing budget
[2696]308
[3866]309    REAL(wp), SAVE ::  t0               !< begin of timing interval
310    REAL(wp), SAVE ::  t1               !< end of timing interval
311    REAL(wp), SAVE ::  t_comp  = 0.0_wp !< computation timing budget
312    REAL(wp), SAVE ::  t_alloc = 0.0_wp !< allocation timing budget
313    REAL(wp), SAVE ::  t_init  = 0.0_wp !< initialization timing budget
314    REAL(wp), SAVE ::  t_read  = 0.0_wp !< reading timing budget
315    REAL(wp), SAVE ::  t_total = 0.0_wp !< total time
316    REAL(wp), SAVE ::  t_write = 0.0_wp !< writing timing budget
[2696]317
[3866]318    CHARACTER(LEN=*), PARAMETER  ::  fmt='(F6.2)' !< floating-point output format
[3557]319
320
[4659]321    SELECT CASE( TRIM( mode ) )
[2696]322
[4659]323    CASE( 'init' )
[3866]324       CALL CPU_TIME(t0)
[2696]325
[4659]326    CASE( 'time' )
[2696]327
[3866]328       CALL CPU_TIME(t1)
[2696]329
[4659]330       SELECT CASE( TRIM( budget ) )
[2696]331
[4659]332          CASE( 'alloc' )
[3866]333             t_alloc = t_alloc + t1 - t0
[2696]334
[4659]335          CASE( 'init' )
[3866]336             t_init = t_init + t1 - t0
[2696]337
[4659]338          CASE( 'read' )
[3866]339             t_read = t_read + t1 - t0
[2696]340
[4659]341          CASE( 'write' )
[3866]342             t_write = t_write + t1 - t0
[2696]343
[4659]344          CASE( 'comp' )
[3866]345             t_comp = t_comp + t1 - t0
[2696]346
[3866]347          CASE DEFAULT
[4659]348             CALL inifor_abort(                                                &
349                'log_runtime',                                                 &
350                "Time Budget '" // TRIM( mode ) // "' is not supported."       &
351             )
[2696]352
[3866]353       END SELECT
[2696]354
[3866]355       t0 = t1
[2696]356
[4659]357    CASE( 'report' )
[3866]358        t_total = t_init + t_read + t_write + t_comp
[2696]359
[4659]360        CALL report( 'log_runtime', "*** CPU time ***" )
[2696]361
[4659]362        CALL report( 'log_runtime', "Initialization:  " // TRIM( real_to_str( t_init ) ) // &
363                     " s  (" // TRIM( real_to_str( 100 * t_init / t_total, fmt ) ) // " %)" )
[2696]364
[4659]365        CALL report( 'log_runtime', "(De-)Allocation: " // TRIM( real_to_str( t_alloc ) ) // &
366                     " s  (" // TRIM( real_to_str( 100 * t_alloc / t_total, fmt ) ) // " %)" )
[2696]367
[4659]368        CALL report( 'log_runtime', "Reading data:    " // TRIM( real_to_str( t_read ) )  // &
369                     " s  (" // TRIM( real_to_str( 100 * t_read / t_total, fmt ) ) // " %)" )
[2696]370
[4659]371        CALL report( 'log_runtime', "Writing data:    " // TRIM( real_to_str( t_write ) ) // &
372                     " s  (" // TRIM( real_to_str( 100 * t_write / t_total, fmt ) ) // " %)" )
[2696]373
[4659]374        CALL report( 'log_runtime', "Computation:     " // TRIM( real_to_str( t_comp ) )  // &
375                     " s  (" // TRIM( real_to_str( 100 * t_comp / t_total, fmt) ) // " %)" )
[2696]376
[4659]377        CALL report( 'log_runtime', "Total:           " // TRIM( real_to_str( t_total ) ) // &
378                     " s  (" // TRIM( real_to_str( 100 * t_total / t_total, fmt ) ) // " %)" )
[2696]379
[3866]380    CASE DEFAULT
[4659]381       CALL inifor_abort( 'log_runtime', "Mode '" // TRIM(mode) // "' is not supported." )
[2696]382
[3866]383    END SELECT
[2696]384
[3866]385 END SUBROUTINE log_runtime
[2696]386
[4659]387
[3618]388 END MODULE inifor_control
Note: See TracBrowser for help on using the repository browser.