source: palm/tags/release-3.6/SOURCE/cpu_log.f90 @ 366

Last change on this file since 366 was 226, checked in by raasch, 15 years ago

preparations for the next release

  • Property svn:keywords set to Id
File size: 3.9 KB
Line 
1 SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: cpu_log.f90 226 2009-02-02 07:39:34Z raasch $
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 ) || defined( __nec )
45    INTEGER(8)                  ::  count, count_rate
46#elif defined( __ibm )
47    INTEGER(8)                  ::  IRTC
48#endif
49
50
51!
52!-- Initialize and check, respectively, point of measurement
53    IF ( log_event%place == ' ' )  THEN
54       log_event%place = place
55    ELSEIF ( log_event%place /= place )  THEN
56       IF ( myid == 0 )  THEN
57          PRINT*,'+++ cpu_log: wrong argument'
58          PRINT*,'    expected: ',log_event%place,'  given: ', place
59       ENDIF
60       CALL local_stop
61    ENDIF
62
63!
64!-- Take current time
65#if defined( __lc ) || defined( __decalpha ) || defined( __nec )
66    CALL SYSTEM_CLOCK( count, count_rate )
67    mtime = REAL( count ) / REAL( count_rate )
68#elif defined( __ibm )
69    mtime = IRTC( ) * 1E-9
70#else
71    IF ( myid == 0 )  THEN
72       PRINT*, '+++ cpu_log: no time measurement defined on this host'
73    ENDIF
74    CALL local_stop
75#endif
76
77!
78!-- Start, stop or pause measurement
79    IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
80       log_event%mtime    = mtime
81       log_event%mtimevec = mtimevec
82    ELSEIF ( modus == 'pause' )  THEN
83       IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
84          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
85          PRINT*,'+++ PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
86                 mtime,' last=',log_event%mtime
87          first = .FALSE.
88       ENDIF
89       log_event%isum     = log_event%isum + mtime - log_event%mtime
90       log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
91    ELSEIF ( modus == 'stop' )  THEN
92       IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
93            first )  THEN
94          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
95          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
96                 mtime,' last=',log_event%mtime,' isum=',log_event%isum
97          first = .FALSE.
98       ENDIF
99       log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
100       log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
101       log_event%sum      = log_event%sum  + log_event%mtime
102       IF ( log_event%sum < 0.0  .AND.  first )  THEN
103          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
104          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
105                 log_event%sum,' mtime=',log_event%mtime
106          first = .FALSE.
107       ENDIF
108       log_event%vector   = log_event%vector + log_event%mtimevec
109       log_event%counts   = log_event%counts + 1
110       log_event%isum     = 0.0
111       log_event%ivect    = 0.0
112    ELSE
113       PRINT*, '+++ unknown modus of time measurement: ', modus
114    ENDIF
115
116
117 END SUBROUTINE cpu_log
Note: See TracBrowser for help on using the repository browser.