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

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

inifor: Prefixed all INIFOR modules with inifor_ and removed unused variables

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