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

Last change on this file since 4123 was 3997, checked in by eckhard, 5 years ago

inifor: Read origin_z from static driver if given; alert user to warnings

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