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

Last change on this file since 4633 was 4523, checked in by eckhard, 4 years ago

fixed constant-density pressure extrapolation, respect integer working precision

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