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

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

inifor: Updated documentation

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