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

Last change on this file since 1036 was 1036, checked in by raasch, 11 years ago

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 5.2 KB
RevLine 
[1]1 SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
[254]20! Current revisions:
[1]21! -----------------
[392]22!
[1]23!
24! Former revisions:
25! -----------------
[3]26! $Id: cpu_log.f90 1036 2012-10-22 13:43:42Z raasch $
[83]27!
[392]28! 274 2009-03-26 15:11:21Z heinze
29! Output of messages replaced by message handling routine.
30! Type of count and count_rate changed to default INTEGER on NEC machines
31!
[226]32! 225 2009-01-26 14:44:20Z raasch
33! Type of count and count_rate changed to INTEGER(8)
34!
[83]35! 82 2007-04-16 15:40:52Z raasch
36! Preprocessor strings for different linux clusters changed to "lc",
37! preprocessor directives for old systems removed
38!
[3]39! RCS Log replace by Id keyword, revision history cleaned up
40!
[1]41! Revision 1.24  2006/06/02 15:12:17  raasch
42! cpp-directives extended for lctit
43!
44! Revision 1.1  1997/07/24 11:12:29  raasch
45! Initial revision
46!
47!
48! Description:
49! ------------
50! Cpu-time measurements for any program part whatever.
[3]51!------------------------------------------------------------------------------!
[1]52
[254]53    USE control_parameters
[1]54    USE cpulog
55    USE pegrid
56
57    IMPLICIT NONE
58
59    CHARACTER (LEN=*)           ::  modus, place
60    CHARACTER (LEN=*), OPTIONAL ::  barrierwait
61    LOGICAL, SAVE               ::  first = .TRUE.
62    REAL                        ::  mtime = 0.0, mtimevec = 0.0
63    TYPE(logpoint)              ::  log_event
64
[239]65#if defined( __lc ) || defined( __decalpha )
[225]66    INTEGER(8)                  ::  count, count_rate
[239]67#elif defined( __nec )
68    INTEGER                     ::  count, count_rate
[1]69#elif defined( __ibm )
70    INTEGER(8)                  ::  IRTC
71#endif
72
73
74!
75!-- Initialize and check, respectively, point of measurement
76    IF ( log_event%place == ' ' )  THEN
77       log_event%place = place
78    ELSEIF ( log_event%place /= place )  THEN
[254]79       WRITE( message_string, * ) 'wrong argument & expected: ', &
80                         TRIM(log_event%place), '  given: ',  TRIM( place )
81       CALL message( 'cpu_log', 'PA0174', 1, 2, 0, 6, 0 )
[1]82    ENDIF
83
84!
85!-- Take current time
[82]86#if defined( __lc ) || defined( __decalpha ) || defined( __nec )
[1]87    CALL SYSTEM_CLOCK( count, count_rate )
88    mtime = REAL( count ) / REAL( count_rate )
89#elif defined( __ibm )
90    mtime = IRTC( ) * 1E-9
91#else
[254]92    message_string = 'no time measurement defined on this host'
93    CALL message( 'cpu_log', 'PA0175', 1, 2, 0, 6, 0 )
[1]94#endif
95
96!
97!-- Start, stop or pause measurement
98    IF ( modus == 'start'  .OR.  modus == 'continue' )  THEN
99       log_event%mtime    = mtime
100       log_event%mtimevec = mtimevec
101    ELSEIF ( modus == 'pause' )  THEN
102       IF ( ( mtime - log_event%mtime ) < 0.0  .AND.  first )  THEN
[274]103          WRITE( message_string, * ) 'negative time interval occured',         &
104                      ' &PE',myid,' L=PAUSE "',TRIM(log_event%place),'" new=', &
105                      mtime,' last=',log_event%mtime
[254]106          CALL message( 'cpu_log', 'PA0176', 0, 1, -1, 6, 0 )
[1]107          first = .FALSE.
108       ENDIF
109       log_event%isum     = log_event%isum + mtime - log_event%mtime
110       log_event%ivect    = log_event%ivect  + mtimevec - log_event%mtimevec
111    ELSEIF ( modus == 'stop' )  THEN
112       IF ( ( mtime - log_event%mtime + log_event%isum ) < 0.0  .AND. &
113            first )  THEN
[274]114          WRITE( message_string, * ) 'negative time interval occured',        &
115                      ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" new=', &
116                      mtime,' last=',log_event%mtime,' isum=',log_event%isum
[254]117          CALL message( 'cpu_log', 'PA0177', 0, 1, -1, 6, 0 )
[1]118          first = .FALSE.
119       ENDIF
120       log_event%mtime    = mtime    - log_event%mtime    + log_event%isum
121       log_event%mtimevec = mtimevec - log_event%mtimevec + log_event%ivect
122       log_event%sum      = log_event%sum  + log_event%mtime
123       IF ( log_event%sum < 0.0  .AND.  first )  THEN
[274]124          WRITE( message_string, * ) 'negative time interval occured',        &
125                      ' &PE',myid,' L=STOP "',TRIM(log_event%place),'" sum=', &
[254]126                                      log_event%sum,' mtime=',log_event%mtime
127          CALL message( 'cpu_log', 'PA0178', 0, 1, -1, 6, 0 )
[1]128          first = .FALSE.
129       ENDIF
130       log_event%vector   = log_event%vector + log_event%mtimevec
131       log_event%counts   = log_event%counts + 1
132       log_event%isum     = 0.0
133       log_event%ivect    = 0.0
134    ELSE
[254]135       message_string = 'unknown modus of time measurement: ' // TRIM( modus )
136       CALL message( 'cpu_log', 'PA0179', 0, 1, -1, 6, 0 )
[1]137    ENDIF
138
139
140 END SUBROUTINE cpu_log
Note: See TracBrowser for help on using the repository browser.