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

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

bugfixes concerning cpu time measurements and calculation of spectra in case of multigrid method switched on

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