source: palm/trunk/SOURCE/cpu_log.f90 @ 247

Last change on this file since 247 was 239, checked in by letzel, 15 years ago
  • Bugfix: Type of count and count_rate changed to default INTEGER on NEC

machines (cpu_log)

  • Property svn:keywords set to Id
File size: 4.0 KB
Line 
1 SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Type of count and count_rate changed to default INTEGER on NEC machines
7!
8! Former revisions:
9! -----------------
10! $Id: cpu_log.f90 239 2009-02-17 13:27:28Z heinze $
11!
12! 225 2009-01-26 14:44:20Z raasch
13! Type of count and count_rate changed to INTEGER(8)
14!
15! 82 2007-04-16 15:40:52Z raasch
16! Preprocessor strings for different linux clusters changed to "lc",
17! preprocessor directives for old systems removed
18!
19! RCS Log replace by Id keyword, revision history cleaned up
20!
21! Revision 1.24  2006/06/02 15:12:17  raasch
22! cpp-directives extended for lctit
23!
24! Revision 1.1  1997/07/24 11:12:29  raasch
25! Initial revision
26!
27!
28! Description:
29! ------------
30! Cpu-time measurements for any program part whatever.
31!------------------------------------------------------------------------------!
32
33    USE cpulog
34    USE pegrid
35
36    IMPLICIT NONE
37
38    CHARACTER (LEN=*)           ::  modus, place
39    CHARACTER (LEN=*), OPTIONAL ::  barrierwait
40    LOGICAL, SAVE               ::  first = .TRUE.
41    REAL                        ::  mtime = 0.0, mtimevec = 0.0
42    TYPE(logpoint)              ::  log_event
43
44#if defined( __lc ) || defined( __decalpha )
45    INTEGER(8)                  ::  count, count_rate
46#elif defined( __nec )
47    INTEGER                     ::  count, count_rate
48#elif defined( __ibm )
49    INTEGER(8)                  ::  IRTC
50#endif
51
52
53!
54!-- Initialize and check, respectively, point of measurement
55    IF ( log_event%place == ' ' )  THEN
56       log_event%place = place
57    ELSEIF ( log_event%place /= place )  THEN
58       IF ( myid == 0 )  THEN
59          PRINT*,'+++ cpu_log: wrong argument'
60          PRINT*,'    expected: ',log_event%place,'  given: ', place
61       ENDIF
62       CALL local_stop
63    ENDIF
64
65!
66!-- Take current time
67#if defined( __lc ) || defined( __decalpha ) || defined( __nec )
68    CALL SYSTEM_CLOCK( count, count_rate )
69    mtime = REAL( count ) / REAL( count_rate )
70#elif defined( __ibm )
71    mtime = IRTC( ) * 1E-9
72#else
73    IF ( myid == 0 )  THEN
74       PRINT*, '+++ cpu_log: no time measurement defined on this host'
75    ENDIF
76    CALL local_stop
77#endif
78
79!
80!-- Start, stop or pause measurement
81    IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
82       log_event%mtime    = mtime
83       log_event%mtimevec = mtimevec
84    ELSEIF ( modus == 'pause' )  THEN
85       IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
86          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
87          PRINT*,'+++ PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
88                 mtime,' last=',log_event%mtime
89          first = .FALSE.
90       ENDIF
91       log_event%isum     = log_event%isum + mtime - log_event%mtime
92       log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
93    ELSEIF ( modus == 'stop' )  THEN
94       IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
95            first )  THEN
96          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
97          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
98                 mtime,' last=',log_event%mtime,' isum=',log_event%isum
99          first = .FALSE.
100       ENDIF
101       log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
102       log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
103       log_event%sum      = log_event%sum  + log_event%mtime
104       IF ( log_event%sum < 0.0  .AND.  first )  THEN
105          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
106          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
107                 log_event%sum,' mtime=',log_event%mtime
108          first = .FALSE.
109       ENDIF
110       log_event%vector   = log_event%vector + log_event%mtimevec
111       log_event%counts   = log_event%counts + 1
112       log_event%isum     = 0.0
113       log_event%ivect    = 0.0
114    ELSE
115       PRINT*, '+++ unknown modus of time measurement: ', modus
116    ENDIF
117
118
119 END SUBROUTINE cpu_log
Note: See TracBrowser for help on using the repository browser.