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

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

inifor: bugfix: avoid empty averaging regions, check if all input files are present

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