Ignore:
Timestamp:
Nov 22, 2018 4:01:22 PM (5 years ago)
Author:
eckhard
Message:

inifor: Updated documentation

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/inifor_control.f90

    r3447 r3557  
    2626! -----------------
    2727! $Id$
     28! Updated documentation
     29!
     30!
     31! 3447 2018-10-29 15:52:54Z eckhard
    2832! Renamed source files for compatibilty with PALM build system
    2933!
     
    4448! Authors:
    4549! --------
    46 ! @author Eckhard Kadasch
     50!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
    4751!
    4852! Description:
     
    6165    IMPLICIT NONE
    6266
    63     CHARACTER (LEN=5000) ::  message = ''
     67    CHARACTER (LEN=5000) ::  message = '' !< log message buffer
    6468
    6569 CONTAINS
    6670
     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!------------------------------------------------------------------------------!
    6782    SUBROUTINE report(routine, message, debug)
    6883
    69        CHARACTER(LEN=*), INTENT(IN)  ::  routine
    70        CHARACTER(LEN=*), INTENT(IN)  ::  message
    71        LOGICAL, OPTIONAL, INTENT(IN) ::  debug
    72        INTEGER                       ::  u
    73        LOGICAL, SAVE                 ::  is_first_run = .TRUE.
    74        LOGICAL                       ::  suppress_message
    75 
    76 
    77        IF (is_first_run)  THEN
     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
    7894          OPEN( NEWUNIT=u, FILE='inifor.log', STATUS='replace' )
    7995          is_first_run = .FALSE.
     
    84100
    85101       suppress_message = .FALSE.
    86        IF (PRESENT(debug))  THEN
    87           IF (.NOT. debug)  suppress_message = .TRUE.
     102       IF ( PRESENT(debug) )  THEN
     103          IF ( .NOT. debug )  suppress_message = .TRUE.
    88104       END IF
    89105
    90        IF (.NOT. suppress_message)  THEN
     106       IF ( .NOT. suppress_message )  THEN
    91107          PRINT *, "inifor: " // TRIM(message) // "  [ " // TRIM(routine) // " ]"
    92108          WRITE(u, *)  TRIM(message) // "  [ " // TRIM(routine) // " ]"
     
    98114
    99115
     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!------------------------------------------------------------------------------!
    100126    SUBROUTINE warn(routine, message)
    101127
    102        CHARACTER(LEN=*), INTENT(IN) ::  routine
    103        CHARACTER(LEN=*), INTENT(IN) ::  message
     128       CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
     129       CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
    104130
    105131       CALL report(routine, "WARNING: " // TRIM(message))
     
    108134
    109135
     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!------------------------------------------------------------------------------!
    110146    SUBROUTINE abort(routine, message)
    111147
    112        CHARACTER(LEN=*), INTENT(IN) ::  routine
    113        CHARACTER(LEN=*), INTENT(IN) ::  message
     148       CHARACTER(LEN=*), INTENT(IN) ::  routine !< name of calling subroutine or function
     149       CHARACTER(LEN=*), INTENT(IN) ::  message !< log message
    114150
    115151       CALL report(routine, "ERROR: " // TRIM(message) // " Stopping.")
     
    119155
    120156
     157!------------------------------------------------------------------------------!
     158! Description:
     159! ------------
     160!>
     161!> print_version() prints the INIFOR version number and copyright notice.
     162!------------------------------------------------------------------------------!
    121163    SUBROUTINE print_version()
    122164       PRINT *, "INIFOR " // VERSION
     
    125167
    126168
     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!------------------------------------------------------------------------------!
    127176    SUBROUTINE run_control(mode, budget)
    128177
    129        CHARACTER(LEN=*), INTENT(IN) ::  mode, budget
    130        REAL(dp), SAVE               ::  t0, t1
    131        REAL(dp), SAVE               ::  t_comp=0.0_dp, &
    132                                         t_alloc=0.0_dp, &
    133                                         t_init=0.0_dp, &
    134                                         t_read=0.0_dp, &
    135                                         t_total=0.0_dp, &
    136                                         t_write=0.0_dp
    137        CHARACTER(LEN=*), PARAMETER  ::  fmt='(F6.2)'
     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
    138191
    139192
Note: See TracChangeset for help on using the changeset viewer.