Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/cpulog.f90

    r1403 r1682  
    1  MODULE cpulog
    2 
     1!> @file cpulog.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5958! Description:
    6059! ------------
    61 ! CPU-time measurements for any program part whatever. Results of the
    62 ! measurements are output at the end of the run in local file CPU_MEASURES.
    63 !
    64 ! To measure the CPU-time (better to say the wallclock time) of a specific code
    65 ! segment, two calls of cpu_log have to be used as brackets in front and at the
    66 ! end of the segment:
    67 !
    68 !     CALL cpu_log( log_point(n), 'any identifier', 'start' )
    69 !       ... code segment ...
    70 !     CALL cpu_log( log_point(n), 'any identifier', 'stop' )
    71 !
    72 ! Parts of the code segment can be excluded from the measurement by additional
    73 ! call of cpu_log:
    74 !
    75 !       ... first segment to be measured
    76 !     CALL cpu_log( log_point(n), 'any identifier', 'pause' )
    77 !       ... oart of segment to be excluded from measurement
    78 !     CALL cpu_log( log_point(n), 'any identifier', 'continue' )
    79 !       ... second segment to be mesasured
    80 !
    81 ! n is an INTEGER within the interval [1,100] defining the id of the specific
    82 ! code segment, 'any identifier' is a string describing the code segment to be
    83 ! measured. It can be freely chosen and results will appear under this name in
    84 ! file CPU_MEASURES. ids can only be used once. If you like to do a
    85 ! measurement of a new part of the code, please look for an id which is unused
    86 ! ao far.
    87 !
    88 ! d3par-parameter cpu_log_barrierwait can be used to set an MPI barrier at the
    89 ! beginning of the measurement (modus 'start' or 'continue'), to avoid that
    90 ! idle times (due to MPI calls in the code segment, which are
    91 ! waiting for other processes to be finished) affect the measurements.
    92 ! If barriers shall not be used at all, a fourth, optional parameter has to be
    93 ! given:
    94 !
    95 !     CALL cpu_log( ..., ..., 'start', cpu_log_nowait )
    96 !
    97 ! Variable log_point should be used for non-overlapping code segments, and they
    98 ! should sum up to the total cpu-time required by the complete run.
    99 ! Variable log_point_s can be used for any other special (s) measurements.
     60!> CPU-time measurements for any program part whatever. Results of the
     61!> measurements are output at the end of the run in local file CPU_MEASURES.
     62!>
     63!> To measure the CPU-time (better to say the wallclock time) of a specific code
     64!> segment, two calls of cpu_log have to be used as brackets in front and at the
     65!> end of the segment:
     66!>
     67!>     CALL cpu_log( log_point(n), 'any identifier', 'start' )
     68!>       ... code segment ...
     69!>     CALL cpu_log( log_point(n), 'any identifier', 'stop' )
     70!>
     71!> Parts of the code segment can be excluded from the measurement by additional
     72!> call of cpu_log:
     73!>
     74!>       ... first segment to be measured
     75!>     CALL cpu_log( log_point(n), 'any identifier', 'pause' )
     76!>       ... oart of segment to be excluded from measurement
     77!>     CALL cpu_log( log_point(n), 'any identifier', 'continue' )
     78!>       ... second segment to be mesasured
     79!>
     80!> n is an INTEGER within the interval [1,100] defining the id of the specific
     81!> code segment, 'any identifier' is a string describing the code segment to be
     82!> measured. It can be freely chosen and results will appear under this name in
     83!> file CPU_MEASURES. ids can only be used once. If you like to do a
     84!> measurement of a new part of the code, please look for an id which is unused
     85!> ao far.
     86!>
     87!> d3par-parameter cpu_log_barrierwait can be used to set an MPI barrier at the
     88!> beginning of the measurement (modus 'start' or 'continue'), to avoid that
     89!> idle times (due to MPI calls in the code segment, which are
     90!> waiting for other processes to be finished) affect the measurements.
     91!> If barriers shall not be used at all, a fourth, optional parameter has to be
     92!> given:
     93!>
     94!>     CALL cpu_log( ..., ..., 'start', cpu_log_nowait )
     95!>
     96!> Variable log_point should be used for non-overlapping code segments, and they
     97!> should sum up to the total cpu-time required by the complete run.
     98!> Variable log_point_s can be used for any other special (s) measurements.
    10099!------------------------------------------------------------------------------!
     100 MODULE cpulog
     101 
    101102
    102103    USE control_parameters,                                                    &
     
    125126    END INTERFACE cpu_statistics
    126127
    127     INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !:
    128     INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !:
    129     INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !:
    130     INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !:
    131 
    132     LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !:
    133     LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !:
    134 
    135     REAL(wp) ::  initial_wallclock_time  !:
     128    INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !<
     129    INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !<
     130    INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !<
     131    INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !<
     132
     133    LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !<
     134    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !<
     135
     136    REAL(wp) ::  initial_wallclock_time  !<
    136137
    137138    TYPE logpoint
    138        REAL(wp)           ::  isum       !:
    139        REAL(wp)           ::  ivect      !:
    140        REAL(wp)           ::  mean       !:
    141        REAL(wp)           ::  mtime      !:
    142        REAL(wp)           ::  mtimevec   !:
    143        REAL(wp)           ::  sum        !:
    144        REAL(wp)           ::  vector     !:
    145        INTEGER(iwp)       ::  counts     !:
    146        CHARACTER (LEN=20) ::  place      !:
     139       REAL(wp)           ::  isum       !<
     140       REAL(wp)           ::  ivect      !<
     141       REAL(wp)           ::  mean       !<
     142       REAL(wp)           ::  mtime      !<
     143       REAL(wp)           ::  mtimevec   !<
     144       REAL(wp)           ::  sum        !<
     145       REAL(wp)           ::  vector     !<
     146       INTEGER(iwp)       ::  counts     !<
     147       CHARACTER (LEN=20) ::  place      !<
    147148    END TYPE logpoint
    148149
     
    158159 CONTAINS
    159160
     161!------------------------------------------------------------------------------!
     162! Description:
     163! ------------
     164!> @todo Missing subroutine description.
     165!------------------------------------------------------------------------------!
    160166    SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
    161167
    162168       IMPLICIT NONE
    163169
    164        CHARACTER (LEN=*) ::  modus              !:
    165        CHARACTER (LEN=*) ::  place              !:
     170       CHARACTER (LEN=*) ::  modus              !<
     171       CHARACTER (LEN=*) ::  place              !<
    166172       
    167        LOGICAL           ::  wait_allowed       !:
    168        LOGICAL, OPTIONAL ::  barrierwait        !:
    169        LOGICAL, SAVE     ::  first = .TRUE.     !:
     173       LOGICAL           ::  wait_allowed       !<
     174       LOGICAL, OPTIONAL ::  barrierwait        !<
     175       LOGICAL, SAVE     ::  first = .TRUE.     !<
    170176       
    171        REAL(wp)          ::  mtime = 0.0_wp     !:
    172        REAL(wp)          ::  mtimevec = 0.0_wp  !:
    173        TYPE(logpoint)    ::  log_event          !:
     177       REAL(wp)          ::  mtime = 0.0_wp     !<
     178       REAL(wp)          ::  mtimevec = 0.0_wp  !<
     179       TYPE(logpoint)    ::  log_event          !<
    174180
    175181#if defined( __lc ) || defined( __decalpha )
    176        INTEGER(idp)     ::  count        !:
    177        INTEGER(idp)     ::  count_rate   !:
     182       INTEGER(idp)     ::  count        !<
     183       INTEGER(idp)     ::  count_rate   !<
    178184#elif defined( __nec )
    179        INTEGER(iwp)      ::  count       !:
    180        INTEGER(iwp)      ::  count_rate  !:
     185       INTEGER(iwp)      ::  count       !<
     186       INTEGER(iwp)      ::  count_rate  !<
    181187#elif defined( __ibm )
    182        INTEGER(idp)     ::  IRTC         !:
     188       INTEGER(idp)     ::  IRTC         !<
    183189#endif
    184190
     
    271277
    272278
    273     SUBROUTINE cpu_statistics
    274279!------------------------------------------------------------------------------!
    275280! Description:
    276281! ------------
    277 ! Analysis and output of the cpu-times measured. All PE results are collected
    278 ! on PE0 in order to calculate the mean cpu-time over all PEs and other
    279 ! statistics. The output is sorted according to the amount of cpu-time consumed
    280 ! and output on PE0.
     282!> Analysis and output of the cpu-times measured. All PE results are collected
     283!> on PE0 in order to calculate the mean cpu-time over all PEs and other
     284!> statistics. The output is sorted according to the amount of cpu-time consumed
     285!> and output on PE0.
    281286!------------------------------------------------------------------------------!
     287 
     288    SUBROUTINE cpu_statistics
    282289
    283290       IMPLICIT NONE
    284291
    285        INTEGER(iwp)    ::  i               !:
    286        INTEGER(iwp)    ::  ii(1)           !:
    287        INTEGER(iwp)    ::  iii             !:
    288        INTEGER(iwp)    ::  sender          !:
    289        REAL(wp)       ::  average_cputime  !:
    290        REAL(wp), SAVE ::  norm = 1.0_wp    !:
    291        REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_max        !:
    292        REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_min        !:
    293        REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_rms        !:
    294        REAL(wp), DIMENSION(:),   ALLOCATABLE ::  sum           !:
    295        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pe_log_points !:
     292       INTEGER(iwp)    ::  i               !<
     293       INTEGER(iwp)    ::  ii(1)           !<
     294       INTEGER(iwp)    ::  iii             !<
     295       INTEGER(iwp)    ::  sender          !<
     296       REAL(wp)       ::  average_cputime  !<
     297       REAL(wp), SAVE ::  norm = 1.0_wp    !<
     298       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_max        !<
     299       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_min        !<
     300       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_rms        !<
     301       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  sum           !<
     302       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pe_log_points !<
    296303
    297304
Note: See TracChangeset for help on using the changeset viewer.