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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 5.7 KB
Line 
1 SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: cpu_log.f90,v $
11! Revision 1.24  2006/06/02 15:12:17  raasch
12! cpp-directives extended for lctit
13!
14! Revision 1.23  2004/01/28 15:08:52  raasch
15! Type log changed to logpoint due to name conflict with intrinsic log
16!
17! Revision 1.22  2003/05/09 14:15:18  raasch
18! Time measurement on linux machines included, measurements on IBM are now using
19! function irtc, which allows correct measurements for jobs running over
20! the 24:00 timeline
21!
22! Revision 1.21  2003/03/16 09:30:04  raasch
23! Two underscores (_) are placed in front of all define-strings
24!
25! Revision 1.20  2003/03/12 16:24:18  raasch
26! Time measurement on NEC implemented
27!
28! Revision 1.19  2002/12/20 09:38:43  raasch
29! variable first is defined for all hosts
30!
31! Revision 1.18  2002/12/19 14:09:36  raasch
32! Output of warnings in case of negative cpu-times, STOP statement replaced by
33! call of subroutine local_stop
34!
35! Revision 1.17  2002/05/02 18:49:37  raasch
36! Time measurement on IBM implemented
37!
38! Revision 1.16  2001/03/30 07:00:43  raasch
39! Translation of remaining German identifiers (variables, subroutines, etc.)
40!
41! Revision 1.14  2001/01/25 06:56:49  raasch
42! +cpp-directives for dec-alpha-workstations
43!
44! Revision 1.13  2001/01/22 08:32:46  raasch
45! Module test_variables removed
46!
47! Revision 1.11  2000/12/20 10:18:58  letzel
48! All comments translated into English.
49!
50! Revision 1.9  1999/11/25 16:19:07  raasch
51! TIMEF jetzt als Function-Aufruf
52!
53! Revision 1.8  1999/03/03 09:26:14  raasch
54! Zeitmessung auf T3E grundsaetzlich auf TIMEF umgestellt
55!
56! Revision 1.7  1998/12/15 07:32:39  raasch
57! Messung der wahren I/O-Zeiten auf T3E mit TIMEF moeglich
58!
59! Revision 1.4  1997/09/16 06:37:24  raasch
60! Zeitmessungen auf t3e umgestellt auf tsecnd (schneller als mpi_wtime)
61!
62! Revision 1.1  1997/07/24 11:12:29  raasch
63! Initial revision
64!
65!
66! Description:
67! ------------
68! Cpu-time measurements for any program part whatever.
69!-------------------------------------------------------------------------------!
70
71    USE cpulog
72    USE pegrid
73
74    IMPLICIT NONE
75
76    CHARACTER (LEN=*)           ::  modus, place
77    CHARACTER (LEN=*), OPTIONAL ::  barrierwait
78    LOGICAL, SAVE               ::  first = .TRUE.
79    REAL                        ::  mtime = 0.0, mtimevec = 0.0
80    TYPE(logpoint)              ::  log_event
81
82#if defined( __lcmuk ) || defined( __lctit ) || defined( __hpmuk ) || defined( __decalpha ) || defined( __nec )
83    INTEGER                     ::  count, count_rate
84#elif defined( __ibm )
85    INTEGER(8)                  ::  IRTC
86#elif defined( __t3eb )
87    REAL                        ::  TIMEF
88#endif
89
90
91!
92!-- Initialize and check, respectively, point of measurement
93    IF ( log_event%place == ' ' )  THEN
94       log_event%place = place
95    ELSEIF ( log_event%place /= place )  THEN
96       IF ( myid == 0 )  THEN
97          PRINT*,'+++ cpu_log: wrong argument'
98          PRINT*,'    expected: ',log_event%place,'  given: ', place
99       ENDIF
100       CALL local_stop
101    ENDIF
102
103!
104!-- Take current time
105#if defined( __lcmuk ) || defined( __lctit ) || defined( __hpmuk ) || defined( __decalpha ) || defined( __nec )
106    CALL SYSTEM_CLOCK( count, count_rate )
107    mtime = REAL( count ) / REAL( count_rate )
108#elif defined( __ibm )
109    mtime = IRTC( ) * 1E-9
110!#elif defined( __vpp )
111!    CALL CLOCKV ( mtimevec, mtime, 0, 2 )
112#elif defined( __t3eb ) || defined( __t3eh ) || defined( __t3ej2 ) || defined( __t3ej5 )
113#if defined( __parallel )
114    IF ( .NOT. PRESENT( barrierwait ) )  THEN
115       CALL MPI_BARRIER( comm2d, ierr )
116       CONTINUE
117    ENDIF
118#endif
119    mtime = TIMEF( )
120    mtime = mtime * 0.001
121#else
122    IF ( myid == 0 )  THEN
123       PRINT*, '+++ cpu_log: no time measurement defined on this host'
124    ENDIF
125    CALL local_stop
126#endif
127
128!
129!-- Start, stop or pause measurement
130    IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
131       log_event%mtime    = mtime
132       log_event%mtimevec = mtimevec
133    ELSEIF ( modus == 'pause' )  THEN
134       IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
135          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
136          PRINT*,'+++ PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
137                 mtime,' last=',log_event%mtime
138          first = .FALSE.
139       ENDIF
140       log_event%isum     = log_event%isum + mtime - log_event%mtime
141       log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
142    ELSEIF ( modus == 'stop' )  THEN
143       IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
144            first )  THEN
145          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
146          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
147                 mtime,' last=',log_event%mtime,' isum=',log_event%isum
148          first = .FALSE.
149       ENDIF
150       log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
151       log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
152       log_event%sum      = log_event%sum  + log_event%mtime
153       IF ( log_event%sum < 0.0  .AND.  first )  THEN
154          PRINT*,'+++ WARNING: cpu_log: negative time interval occured'
155          PRINT*,'+++ PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
156                 log_event%sum,' mtime=',log_event%mtime
157          first = .FALSE.
158       ENDIF
159       log_event%vector   = log_event%vector + log_event%mtimevec
160       log_event%counts   = log_event%counts + 1
161       log_event%isum     = 0.0
162       log_event%ivect    = 0.0
163    ELSE
164       PRINT*, '+++ unknown modus of time measurement: ', modus
165    ENDIF
166
167
168 END SUBROUTINE cpu_log
Note: See TracBrowser for help on using the repository browser.