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

Last change on this file since 3698 was 3680, checked in by knoop, 5 years ago

Added cpp-option netcdf to inifor

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