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

Last change on this file since 4475 was 4475, checked in by gronemeier, 4 years ago

bugfixes/changes to INIFOR:

  • c: revise output format in routine report (inifor_control)
  • b: check if namelist file was opened (inifor_grid)
  • b: use explicit loop in routine reverse (inifor_util)
  • Property svn:keywords set to Id
File size: 9.5 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!
[3779]17! Copyright 2017-2019 Leibniz Universitaet Hannover
18! Copyright 2017-2019 Deutscher Wetterdienst Offenbach
[2696]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: inifor_control.f90 4475 2020-03-26 16:28:19Z gronemeier $
[4475]28! Change output format in routine report to allow for better message formatting
29!
30! 3997 2019-05-23 12:35:57Z eckhard
[3997]31! Added warnings counter
32!
33!
34! 3866 2019-04-05 14:25:01Z eckhard
[3866]35! Use PALM's working precision
36! Renamed run_control -> log_runtime
37! Open log file only once
38! Improved coding style
39!
40!
41! 3785 2019-03-06 10:41:14Z eckhard
[3678]42! Added message buffer for displaying tips to rectify encountered errors
43!
44!
45! 3618 2018-12-10 13:25:22Z eckhard
[3618]46! Prefixed all INIFOR modules with inifor_
47!
48!
49! 3614 2018-12-10 07:05:46Z raasch
[3614]50! abort renamed inifor_abort to avoid intrinsic problem in Fortran
51!
52! 3557 2018-11-22 16:01:22Z eckhard
[3557]53! Updated documentation
54!
55!
56! 3447 2018-10-29 15:52:54Z eckhard
[3447]57! Renamed source files for compatibilty with PALM build system
58!
59!
60! 3395 2018-10-22 17:32:49Z eckhard
[3395]61! Suppress debugging messages unless --debug option is given
62!
63!
64! 3183 2018-07-27 14:25:55Z suehring
[3183]65! Added version and copyright output
66!
67!
68! 3182 2018-07-27 13:36:03Z suehring
[2696]69! Initial revision
70!
71!
72!
73! Authors:
74! --------
[3557]75!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
[2696]76!
77! Description:
78! ------------
79!> The control module provides routines for timing INIFOR and writing runtime
80!> feedback to the terminal and a log file.
81!------------------------------------------------------------------------------!
[3618]82 MODULE inifor_control
[2696]83
[3618]84    USE inifor_defs,                                                           &
[3866]85        ONLY:  COPYRIGHT, LNAME, LOG_FILE_NAME, VERSION, wp
[3618]86    USE inifor_util,                                                           &
[2696]87        ONLY:  real_to_str, real_to_str_f
88
89    IMPLICIT NONE
90
[3557]91    CHARACTER (LEN=5000) ::  message = '' !< log message buffer
[3678]92    CHARACTER (LEN=5000) ::  tip     = '' !< optional log message buffer for tips on how to rectify encountered errors
[3866]93    INTEGER, SAVE        ::  u            !< Fortran file unit for the log file
[3997]94    INTEGER, SAVE        ::  n_wrngs = 0  !< Fortran file unit for the log file
[2696]95
96 CONTAINS
97
[3557]98!------------------------------------------------------------------------------!
99! Description:
100! ------------
101!>
102!> report() is INIFOR's general logging routine. It prints the given 'message'
103!> to the terminal and writes it to the INIFOR log file.
104!>
105!> You can use this routine to log events across INIFOR's code to log. For
106!> warnings and abort messages, you may use the dedicated routines warn() and
[3614]107!> inifor_abort() in this module. Both use report() and add specific behaviour
108!> to it.
[3557]109!------------------------------------------------------------------------------!
[3866]110 SUBROUTINE report(routine, message, debug)
[2696]111
[3866]112    CHARACTER(LEN=*), INTENT(IN)  ::  routine !< name of calling subroutine of function
113    CHARACTER(LEN=*), INTENT(IN)  ::  message !< log message
114    LOGICAL, OPTIONAL, INTENT(IN) ::  debug   !< flag the current message as debugging message
[2696]115
[3866]116    LOGICAL, SAVE                 ::  is_first_run = .TRUE. !< control flag for file opening mode
117    LOGICAL                       ::  suppress_message      !< control falg for additional debugging log
[2696]118
[3866]119    IF ( is_first_run )  THEN
120       OPEN( NEWUNIT=u, FILE=LOG_FILE_NAME, STATUS='replace' )
121       is_first_run = .FALSE.
122    ENDIF
123       
[3557]124
[3866]125    suppress_message = .FALSE.
126    IF ( PRESENT(debug) )  THEN
127       IF ( .NOT. debug )  suppress_message = .TRUE.
128    ENDIF
[2696]129
[3866]130    IF ( .NOT. suppress_message )  THEN
[4475]131       WRITE(*, '(A)') "inifor: " // TRIM(message) // "  [ " // TRIM(routine) // " ]"
132       WRITE(u, '(A)')  TRIM(message) // "  [ " // TRIM(routine) // " ]"
[3866]133    ENDIF
[3395]134
[3866]135 END SUBROUTINE report
[3395]136
[2696]137
[3557]138!------------------------------------------------------------------------------!
139! Description:
140! ------------
141!>
142!> warn() prepends "WARNING:" the given 'message' and prints the result to the
143!> terminal and writes it to the INIFOR logfile.
144!>
145!> You can use this routine for messaging issues, that still allow INIFOR to
146!> continue.
147!------------------------------------------------------------------------------!
[3866]148 SUBROUTINE warn(routine, message)
[2696]149
[3866]150    CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
151    CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
[2696]152
[3997]153    n_wrngs = n_wrngs + 1
[3866]154    CALL report(routine, "WARNING: " // TRIM(message))
[2696]155
[3866]156 END SUBROUTINE warn
[2696]157
158
[3557]159!------------------------------------------------------------------------------!
160! Description:
161! ------------
162!>
[3614]163!> inifor_abort() prepends "ERROR:" the given 'message' and prints the result to
164!> stdout, writes it to the INIFOR logfile, and exits INIFOR.
[3557]165!>
166!> You can use this routine for messaging issues, that are critical and prevent
167!> INIFOR from continueing.
168!------------------------------------------------------------------------------!
[3866]169 SUBROUTINE inifor_abort(routine, message)
[2696]170
[3866]171    CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
172    CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
[2696]173
[3866]174    CALL report(routine, "ERROR: " // TRIM(message) // " Stopping.")
175    CALL close_log
176    STOP
[2696]177
[3866]178 END SUBROUTINE inifor_abort
[2696]179
180
[3866]181 SUBROUTINE close_log()
182
183    CLOSE(u)
184
185 END SUBROUTINE close_log
186
187
[3557]188!------------------------------------------------------------------------------!
189! Description:
190! ------------
191!>
192!> print_version() prints the INIFOR version number and copyright notice.
193!------------------------------------------------------------------------------!
[3866]194 SUBROUTINE print_version()
195    PRINT *, "INIFOR " // VERSION
196    PRINT *, COPYRIGHT
197 END SUBROUTINE print_version
[3182]198
199
[3557]200!------------------------------------------------------------------------------!
201! Description:
202! ------------
203!>
[3866]204!> log_runtime() measures the run times of various parts of INIFOR and
[3557]205!> accumulates them in timing budgets.
206!------------------------------------------------------------------------------!
[3866]207 SUBROUTINE log_runtime(mode, budget)
[2696]208
[3866]209    CHARACTER(LEN=*), INTENT(IN) ::  mode   !< name of the calling mode
210    CHARACTER(LEN=*), INTENT(IN) ::  budget !< name of the timing budget
[2696]211
[3866]212    REAL(wp), SAVE ::  t0               !< begin of timing interval
213    REAL(wp), SAVE ::  t1               !< end of timing interval
214    REAL(wp), SAVE ::  t_comp  = 0.0_wp !< computation timing budget
215    REAL(wp), SAVE ::  t_alloc = 0.0_wp !< allocation timing budget
216    REAL(wp), SAVE ::  t_init  = 0.0_wp !< initialization timing budget
217    REAL(wp), SAVE ::  t_read  = 0.0_wp !< reading timing budget
218    REAL(wp), SAVE ::  t_total = 0.0_wp !< total time
219    REAL(wp), SAVE ::  t_write = 0.0_wp !< writing timing budget
[2696]220
[3866]221    CHARACTER(LEN=*), PARAMETER  ::  fmt='(F6.2)' !< floating-point output format
[3557]222
223
[3866]224    SELECT CASE(TRIM(mode))
[2696]225
[3866]226    CASE('init')
227       CALL CPU_TIME(t0)
[2696]228
[3866]229    CASE('time')
[2696]230
[3866]231       CALL CPU_TIME(t1)
[2696]232
[3866]233       SELECT CASE(TRIM(budget))
[2696]234
[3866]235          CASE('alloc')
236             t_alloc = t_alloc + t1 - t0
[2696]237
[3866]238          CASE('init')
239             t_init = t_init + t1 - t0
[2696]240
[3866]241          CASE('read')
242             t_read = t_read + t1 - t0
[2696]243
[3866]244          CASE('write')
245             t_write = t_write + t1 - t0
[2696]246
[3866]247          CASE('comp')
248             t_comp = t_comp + t1 - t0
[2696]249
[3866]250          CASE DEFAULT
251             CALL inifor_abort('log_runtime', "Time Budget '" // TRIM(mode) // "' is not supported.")
[2696]252
[3866]253       END SELECT
[2696]254
[3866]255       t0 = t1
[2696]256
[3866]257    CASE('report')
258        t_total = t_init + t_read + t_write + t_comp
[2696]259
[3866]260        CALL report('log_runtime', " *** CPU time ***")
[2696]261
[3866]262        CALL report('log_runtime', "Initialization:  " // TRIM( real_to_str( t_init ) ) // &
263                    " s  (" // TRIM( real_to_str( 100 * t_init / t_total, fmt ) ) // " %)" )
[2696]264
[3866]265        CALL report('log_runtime', "(De-)Allocation: " // TRIM( real_to_str( t_alloc ) ) // &
266                    " s  (" // TRIM( real_to_str( 100 * t_alloc / t_total, fmt ) ) // " %)" )
[2696]267
[3866]268        CALL report('log_runtime', "Reading data:    " // TRIM( real_to_str( t_read ) )  // &
269                    " s  (" // TRIM( real_to_str( 100 * t_read / t_total, fmt ) ) // " %)" )
[2696]270
[3866]271        CALL report('log_runtime', "Writing data:    " // TRIM( real_to_str( t_write ) ) // &
272                    " s  (" // TRIM( real_to_str( 100 * t_write / t_total, fmt ) ) // " %)" )
[2696]273
[3866]274        CALL report('log_runtime', "Computation:     " // TRIM( real_to_str( t_comp ) )  // &
275                    " s  (" // TRIM( real_to_str( 100 * t_comp / t_total, fmt) ) // " %)" )
[2696]276
[3866]277        CALL report('log_runtime', "Total:           " // TRIM( real_to_str( t_total ) ) // &
278                    " s  (" // TRIM( real_to_str( 100 * t_total / t_total, fmt ) ) // " %)")
[2696]279
[3866]280    CASE DEFAULT
281       CALL inifor_abort('log_runtime', "Mode '" // TRIM(mode) // "' is not supported.")
[2696]282
[3866]283    END SELECT
[2696]284
[3866]285 END SUBROUTINE log_runtime
[2696]286
[3618]287 END MODULE inifor_control
Note: See TracBrowser for help on using the repository browser.