Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1319 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    3238! 1036 2012-10-22 13:43:42Z raasch
    3339! code put under GPL (PALM 3.9)
    34 !
    35 ! 274 2009-03-26 15:11:21Z heinze
    36 ! Output of messages replaced by message handling routine.
    37 ! Type of count and count_rate changed to default INTEGER on NEC machines
    38 !
    39 ! 225 2009-01-26 14:44:20Z raasch
    40 ! Type of count and count_rate changed to INTEGER(8)
    41 !
    42 ! 82 2007-04-16 15:40:52Z raasch
    43 ! Preprocessor strings for different linux clusters changed to "lc",
    44 ! preprocessor directives for old systems removed
    45 !
    46 ! RCS Log replace by Id keyword, revision history cleaned up
    47 !
    48 ! Revision 1.24  2006/06/02 15:12:17  raasch
    49 ! cpp-directives extended for lctit
    5040!
    5141! Revision 1.1  1997/07/24 11:12:29  raasch
     
    5848!------------------------------------------------------------------------------!
    5949
    60     USE control_parameters
    61     USE indices,  ONLY: nx, ny, nz
     50    USE control_parameters,                                                    &
     51        ONLY: message_string, nr_timesteps_this_run, run_description_header,   &
     52              synchronous_exchange
     53               
     54    USE indices,                                                               &
     55        ONLY: nx, ny, nz
     56       
     57    USE kinds
     58   
    6259    USE pegrid
    6360
     
    6562
    6663    PRIVATE
    67     PUBLIC   cpu_log, cpu_log_barrierwait, cpu_log_nowait, cpu_statistics, &
     64    PUBLIC   cpu_log, cpu_log_barrierwait, cpu_log_nowait, cpu_statistics,     &
    6865             initial_wallclock_time, log_point, log_point_s
    6966
     
    7673    END INTERFACE cpu_statistics
    7774
    78     INTEGER, PARAMETER ::  cpu_log_continue = 0, cpu_log_pause = 1, &
    79                            cpu_log_start = 2, cpu_log_stop = 3
    80 
    81     LOGICAL            ::  cpu_log_barrierwait = .FALSE.
    82     LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.
    83 
    84     REAL ::  initial_wallclock_time
     75    INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !:
     76    INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !:
     77    INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !:
     78    INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !:
     79
     80    LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !:
     81    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !:
     82
     83    REAL(wp) ::  initial_wallclock_time  !:
    8584
    8685    TYPE logpoint
    87        REAL               ::  isum, ivect, mean, mtime, mtimevec, sum, vector
    88        INTEGER            ::  counts
    89        CHARACTER (LEN=20) ::  place
     86       REAL(wp)           ::  isum       !:
     87       REAL(wp)           ::  ivect      !:
     88       REAL(wp)           ::  mean       !:
     89       REAL(wp)           ::  mtime      !:
     90       REAL(wp)           ::  mtimevec   !:
     91       REAL(wp)           ::  sum        !:
     92       REAL(wp)           ::  vector     !:
     93       INTEGER(iwp)       ::  counts     !:
     94       CHARACTER (LEN=20) ::  place      !:
    9095    END TYPE logpoint
    9196
     
    103108       IMPLICIT NONE
    104109
    105        CHARACTER (LEN=*)           ::  modus, place
    106        LOGICAL                     ::  wait_allowed
    107        LOGICAL, OPTIONAL           ::  barrierwait
    108        LOGICAL, SAVE               ::  first = .TRUE.
    109        REAL                        ::  mtime = 0.0, mtimevec = 0.0
    110        TYPE(logpoint)              ::  log_event
     110       CHARACTER (LEN=*) ::  modus              !:
     111       CHARACTER (LEN=*) ::  place              !:
     112       
     113       LOGICAL           ::  wait_allowed       !:
     114       LOGICAL, OPTIONAL ::  barrierwait        !:
     115       LOGICAL, SAVE     ::  first = .TRUE.     !:
     116       
     117       REAL(wp)          ::  mtime = 0.0        !:
     118       REAL(wp)          ::   mtimevec = 0.0    !:
     119       TYPE(logpoint)    ::  log_event          !:
    111120
    112121#if defined( __lc ) || defined( __decalpha )
    113        INTEGER(8)                  ::  count, count_rate
     122       INTEGER(idp)     ::  count        !:
     123       INTEGER(idp)     ::  count_rate   !:
    114124#elif defined( __nec )
    115        INTEGER                     ::  count, count_rate
     125       INTEGER(iwp)      ::  count       !:
     126       INTEGER(iwp)      ::  count_rate  !:
    116127#elif defined( __ibm )
    117        INTEGER(8)                  ::  IRTC
     128       INTEGER(idp)     ::  IRTC         !:
    118129#endif
    119130
     
    124135          log_event%place = place
    125136       ELSEIF ( log_event%place /= place )  THEN
    126           WRITE( message_string, * ) 'wrong argument & expected: ', &
     137          WRITE( message_string, * ) 'wrong argument & expected: ',            &
    127138                            TRIM(log_event%place), '  given: ',  TRIM( place )
    128139          CALL message( 'cpu_log', 'PA0174', 1, 2, 0, 6, 0 )
     
    142153!--    PEs that have not yet finished
    143154#if defined( __parallel )
    144        IF ( cpu_log_barrierwait  .AND.  wait_allowed  .AND.  &
     155       IF ( cpu_log_barrierwait  .AND.  wait_allowed  .AND.                    &
    145156            ( modus == 'start'  .OR.  modus == 'continue' ) )  THEN
    146157          CALL MPI_BARRIER( comm2d, ierr )
     
    167178       ELSEIF ( modus == 'pause' )  THEN
    168179          IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
    169              WRITE( message_string, * ) 'negative time interval occured',         &
    170                          ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
    171                          mtime,' last=',log_event%mtime
     180             WRITE( message_string, * ) 'negative time interval occured',      &
     181                         ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),      &
     182                         '" new=', mtime,' last=',log_event%mtime
    172183             CALL message( 'cpu_log', 'PA0176', 0, 1, -1, 6, 0 )
    173184             first = .FALSE.
     
    176187          log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
    177188       ELSEIF ( modus == 'stop' )  THEN
    178           IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
     189          IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND.       &
    179190               first )  THEN
    180              WRITE( message_string, * ) 'negative time interval occured',        &
     191             WRITE( message_string, * ) 'negative time interval occured',      &
    181192                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
    182193                         mtime,' last=',log_event%mtime,' isum=',log_event%isum
     
    188199          log_event%sum      = log_event%sum  + log_event%mtime
    189200          IF ( log_event%sum < 0.0  .AND.  first )  THEN
    190              WRITE( message_string, * ) 'negative time interval occured',        &
     201             WRITE( message_string, * ) 'negative time interval occured',      &
    191202                         ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
    192203                                         log_event%sum,' mtime=',log_event%mtime
     
    218229       IMPLICIT NONE
    219230
    220        INTEGER    ::  i, ii(1), iii, sender
    221        REAL       ::  average_cputime
    222        REAL, SAVE ::  norm = 1.0
    223        REAL, DIMENSION(:),   ALLOCATABLE ::  pe_max, pe_min, pe_rms, sum
    224        REAL, DIMENSION(:,:), ALLOCATABLE ::  pe_log_points
     231       INTEGER(iwp)    ::  i               !:
     232       INTEGER(iwp)    ::  ii(1)           !:
     233       INTEGER(iwp)    ::  iii             !:
     234       INTEGER(iwp)    ::  sender          !:
     235       REAL(wp)       ::  average_cputime  !:
     236       REAL(wp), SAVE ::  norm = 1.0       !:
     237       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_max        !:
     238       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_min        !:
     239       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  pe_rms        !:
     240       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  sum           !:
     241       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pe_log_points !:
    225242
    226243
     
    240257!
    241258!--       Allocate and initialize temporary arrays needed for statistics
    242           ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ), &
    243                     pe_rms( SIZE( log_point ) ),                              &
     259          ALLOCATE( pe_max( SIZE( log_point ) ), pe_min( SIZE( log_point ) ),  &
     260                    pe_rms( SIZE( log_point ) ),                               &
    244261                    pe_log_points( SIZE( log_point ), 0:numprocs-1 ) )
    245262          pe_min = log_point%sum
     
    251268!--       Receive data from all PEs
    252269          DO  i = 1, numprocs-1
    253              CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
     270             CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL,            &
    254271                            i, i, comm2d, status, ierr )
    255272             sender = status(MPI_SOURCE)
     
    270287!--          Calculate rms
    271288             DO  i = 0, numprocs-1
    272                 pe_rms(iii) = pe_rms(iii) + ( &
    273                                     pe_log_points(iii,i) - log_point(iii)%sum &
     289                pe_rms(iii) = pe_rms(iii) + (                                  &
     290                                    pe_log_points(iii,i) - log_point(iii)%sum  &
    274291                                            )**2
    275292             ENDDO
Note: See TracChangeset for help on using the changeset viewer.