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

Last change on this file since 3614 was 3614, checked in by raasch, 5 years ago

unused variables removed, abort renamed inifor_abort to avoid intrinsic problem in Fortran

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