/[MITgcm]/MITgcm/eesupp/src/timers.F
ViewVC logotype

Diff of /MITgcm/eesupp/src/timers.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.9 by cnh, Sun Feb 4 14:38:44 2001 UTC revision 1.10 by cnh, Fri Sep 21 03:54:35 2001 UTC
# Line 14  C--   TIMER_STOP      - Stop CPU tier fo Line 14  C--   TIMER_STOP      - Stop CPU tier fo
14  C--   Routines marked "M" contain specific machine dependent code.  C--   Routines marked "M" contain specific machine dependent code.
15  C--   Routines marked "U" contain UNIX OS calls.  C--   Routines marked "U" contain UNIX OS calls.
16    
17  CStartOfInterface  CBOP
18    C     !ROUTINE: TIMER_INDEX
19    
20    C     !INTERFACE:
21        INTEGER FUNCTION TIMER_INDEX (        INTEGER FUNCTION TIMER_INDEX (
22       I        name,timerNames,maxTimers,nTimers )       I        name,timerNames,maxTimers,nTimers )
 C     /==========================================================\  
 C     | FUNCTION TIMER_INDEX                                     |  
 C     | o Timing support routine.                                |  
 C     |==========================================================|  
 C     | Return index in timer data structure of timer named      |  
 C     | by the function argument "name".                         |  
 C     \==========================================================/  
23        IMPLICIT NONE        IMPLICIT NONE
24    
25    C     !DESCRIPTION:
26    C     *==========================================================*
27    C     | FUNCTION TIMER_INDEX                                      
28    C     | o Timing support routine.                                
29    C     *==========================================================*
30    C     | Return index in timer data structure of timer named      
31    C     | by the function argument "name".                          
32    C     *==========================================================*
33          IMPLICIT NONE
34    
35    C     !INPUT/OUTPUT PARAMETERS:
36    C     == Routine arguements ==
37    C     maxTimers  :: Total number of timers allowed
38    C     nTimers    :: Current number of timers
39    C     name       :: Name of timer to find
40    C     timerNames :: List of valid timer names
41        INTEGER maxTimers        INTEGER maxTimers
42        INTEGER nTimers        INTEGER nTimers
43        CHARACTER*(*) name        CHARACTER*(*) name
44        CHARACTER*(*) timerNames(maxTimers)        CHARACTER*(*) timerNames(maxTimers)
45  CEndOfInterface  
46    C     !LOCAL VARIABLES:
47    C     == Local variables ==
48    C     I :: Index variable
49        INTEGER I        INTEGER I
50    CEOP
51  C  C
52        TIMER_INDEX = 0        TIMER_INDEX = 0
53        IF ( name .EQ. ' ' ) THEN        IF ( name .EQ. ' ' ) THEN
# Line 46  C Line 63  C
63        RETURN        RETURN
64        END        END
65    
66  CStartOfInterface  CBOP
67    C     !ROUTINE: TIMER_CONTROL
68    
69    C     !INTERFACE:
70        SUBROUTINE TIMER_CONTROL ( name , action , callProc , myThreadId )        SUBROUTINE TIMER_CONTROL ( name , action , callProc , myThreadId )
71  C     /==========================================================\        IMPLICIT NONE
72    
73    C     !DESCRIPTION:
74    C     *==========================================================*
75  C     | SUBROUTINE TIMER_CONTROL                                 |  C     | SUBROUTINE TIMER_CONTROL                                 |
76  C     | o Timing routine.                                        |  C     | o Timing routine.                                        |
77  C     |==========================================================|  C     *==========================================================*
78  C     | User callable interface to timing routines. Timers are   |  C     | User callable interface to timing routines. Timers are   |
79  C     | created, stopped, started and queried only through this  |  C     | created, stopped, started and queried only through this  |
80  C     | rtouine.                                                 |  C     | rtouine.                                                 |
81  C     \==========================================================/  C     *==========================================================*
82        IMPLICIT NONE  
83    C     !USES:
84  #include "SIZE.h"  #include "SIZE.h"
85  #include "EEPARAMS.h"  #include "EEPARAMS.h"
86  #include "EESUPPORT.h"  #include "EESUPPORT.h"
       CHARACTER*(*) name  
       CHARACTER*(*) action  
       CHARACTER*(*) callProc  
       INTEGER myThreadId  
 CEndOfInterface  
 C  
87        INTEGER  TIMER_INDEX        INTEGER  TIMER_INDEX
88        INTEGER  IFNBLNK        INTEGER  IFNBLNK
89        INTEGER  ILNBLNK        INTEGER  ILNBLNK
90        EXTERNAL TIMER_INDEX        EXTERNAL TIMER_INDEX
91        EXTERNAL IFNBLNK        EXTERNAL IFNBLNK
92        EXTERNAL ILNBLNK        EXTERNAL ILNBLNK
93    
94    C     !INPUT/OUTPUT PARAMETERS:
95    C     name       :: name of the timer
96    C     action     :: operation to perform with this timer
97    C     callProc   :: procedure calling this routine
98    C     myThreadId :: instance number of this thread
99          CHARACTER*(*) name
100          CHARACTER*(*) action
101          CHARACTER*(*) callProc
102          INTEGER myThreadId
103  C  C
104    C     !LOCAL VARIABLES:
105    C     maxTimers :: Total numer of timer allowed
106    C     maxString :: Max length of a timer name
107        INTEGER maxTimers        INTEGER maxTimers
108        INTEGER maxString        INTEGER maxString
109        PARAMETER ( maxTimers = 40 )        PARAMETER ( maxTimers = 40 )
110        PARAMETER ( maxString = 80 )        PARAMETER ( maxString = 80 )
111  C  C     timerStarts :: Timer counters for each timer and each thread
112    C     timerStops
113    C     timerUser
114    C     timerWall
115    C     timerSys
116    C     timerT0User
117    C     timerT0Wall
118    C     timerT0Sys
119    C     timerStatus  :: START/STOP/RUNNING Status of the timer
120    C     timerNameLen :: Length of timer name
121    C     timerNames   :: Table of timer names
122    C     nTimers      :: Number of active timers
123        INTEGER timerStarts( maxTimers , MAX_NO_THREADS)        INTEGER timerStarts( maxTimers , MAX_NO_THREADS)
124        SAVE    timerStarts        SAVE    timerStarts
125        INTEGER timerStops ( maxTimers , MAX_NO_THREADS)        INTEGER timerStops ( maxTimers , MAX_NO_THREADS)
# Line 94  C Line 136  C
136        SAVE timerT0Wall        SAVE timerT0Wall
137        Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)        Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)
138        SAVE timerT0Sys        SAVE timerT0Sys
 C     ===============================================================  
 C  
139        INTEGER timerStatus( maxTimers , MAX_NO_THREADS)        INTEGER timerStatus( maxTimers , MAX_NO_THREADS)
140        SAVE    timerStatus        SAVE    timerStatus
141        INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)        INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)
# Line 125  C Line 165  C
165        Real*8 systemTime        Real*8 systemTime
166        Real*8 wallClockTime        Real*8 wallClockTime
167        CHARACTER*(MAX_LEN_MBUF) msgBuffer        CHARACTER*(MAX_LEN_MBUF) msgBuffer
 C  
168        DATA nTimers  /MAX_NO_THREADS*0/        DATA nTimers  /MAX_NO_THREADS*0/
169        SAVE nTimers        SAVE nTimers
170    CEOP
171  C  C
172        ISTART = IFNBLNK(name)        ISTART = IFNBLNK(name)
173        IEND   = ILNBLNK(name)        IEND   = ILNBLNK(name)
# Line 395  C Line 435  C
435        GOTO 1000        GOTO 1000
436        END        END
437    
438  CStartOfInterface  CBOP
439    C     !ROUTINE: TIMER_GET_TIME
440    
441    C     !INTERFACE:
442        SUBROUTINE TIMER_GET_TIME(        SUBROUTINE TIMER_GET_TIME(
443       O                           userTime,       O                           userTime,
444       O                           systemTime,       O                           systemTime,
445       O                           wallClockTime )       O                           wallClockTime )
 C     /==========================================================\  
 C     | SUBROUTINE TIMER_GET_TIME                                |  
 C     | o Query system timer routines.                           |  
 C     |==========================================================|  
 C     | Routine returns total elapsed time for program so far.   |  
 C     | Three times are returned that conventionally are used as |  
 C     | user time, system time and wall-clock time. Not all these|  
 C     | numbers are available on all machines.                   |  
 C     \==========================================================/  
446        IMPLICIT NONE        IMPLICIT NONE
447    
448    C     !DESCRIPTION:
449    C     *==========================================================*
450    C     | SUBROUTINE TIMER_GET_TIME                                
451    C     | o Query system timer routines.                            
452    C     *==========================================================*
453    C     | Routine returns total elapsed time for program so far.    
454    C     | Three times are returned that conventionally are used as  
455    C     | user time, system time and wall-clock time. Not all these
456    C     | numbers are available on all machines.                    
457    C     *==========================================================*
458    
459    C     !INPUT/OUTPUT PARAMETERS:
460    C     userTime      :: User time returned
461    C     systemTime    :: System time returned
462    C     wallClockTime :: Wall clock time returned
463        Real*8 userTime        Real*8 userTime
464        Real*8 systemTime        Real*8 systemTime
465        Real*8 wallClockTime        Real*8 wallClockTime
466  CEndOfInterface  
467        Real*4 ETIME, ACTUAL, TARRAY(2)  C     !USES:
468  #ifndef TARGET_T3E  #ifndef TARGET_T3E
469  #ifndef TARGET_CRAY_VECTOR  #ifndef TARGET_CRAY_VECTOR
470          Real*4 ETIME
471        EXTERNAL ETIME        EXTERNAL ETIME
472  #endif  #endif
473  #endif  #endif
474    
475    C     !LOCAL VARIABLES:
476    C     ACTUAL, TARRAY, :: Temps. to hold times
477    C     wTime
478          Real*4 ACTUAL, TARRAY(2)
479        Real*8 wtime        Real*8 wtime
480    CEOP
481    
482  C     Real*8 MPI_Wtime  C     Real*8 MPI_Wtime
483  C     EXTERNAL MPI_Wtime  C     EXTERNAL MPI_Wtime
484    
# Line 451  C     wallClockTime = 0. Line 509  C     wallClockTime = 0.
509        RETURN        RETURN
510        END        END
511    
512  CStartOfInterface  CBOP
513    
514    C     !ROUTINE: TIMER_PRINTALL
515    
516    C     !INTERFACE:
517        SUBROUTINE TIMER_PRINTALL( myThreadId )        SUBROUTINE TIMER_PRINTALL( myThreadId )
 C     /==========================================================\  
 C     | SUBROUTINE TIMER_PRINTALL                                |  
 C     | o Print timer information                                |  
 C     |==========================================================|  
 C     | Request print out of table of timing from all timers.    |  
 C     \==========================================================/  
518        IMPLICIT NONE        IMPLICIT NONE
519    
520    C     !DESCRIPTION:
521    C     *==========================================================*
522    C     | SUBROUTINE TIMER_PRINTALL                                
523    C     | o Print timer information                                
524    C     *==========================================================*
525    C     | Request print out of table of timing from all timers.    
526    C     *==========================================================*
527    
528    C     !INPUT PARAMETERS:
529    C     myThreadId :: This threads number
530        INTEGER myThreadId        INTEGER myThreadId
531  CEndOfInterface  CEOP
532  C     Print out value for every timer.  
 C  
533        CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,        CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,
534       &                   myThreadId )       &                   myThreadId )
535  C  C
536        RETURN        RETURN
537        END        END
538  C***********************************************************************  
539    CBOP
540    C     !ROUTINE: TIMER_START
541    
542    C     !INTERFACE:
543        SUBROUTINE TIMER_START ( string , myThreadId )        SUBROUTINE TIMER_START ( string , myThreadId )
 C     Return start timer named "string".  
544        IMPLICIT NONE        IMPLICIT NONE
545    
546    C     !DESCRIPTION:
547    C     Start timer named "string".
548    
549    C     !INPUT PARAMETERS:
550    C     string     :: Name of timer
551    C     myThreadId :: My thread number
552        CHARACTER*(*) string        CHARACTER*(*) string
553        INTEGER myThreadId        INTEGER myThreadId
554    CEOP
555  C  C
556        CALL TIMER_CONTROL( string, 'START', 'TIMER_START' , myThreadId)        CALL TIMER_CONTROL( string, 'START', 'TIMER_START' , myThreadId)
557  C  C
558        RETURN        RETURN
559        END        END
560  C***********************************************************************  CBOP
561    C     !ROUTINE: TIMER_STOP
562    
563    C     !INTERFACE:
564        SUBROUTINE TIMER_STOP  ( string , myThreadId)        SUBROUTINE TIMER_STOP  ( string , myThreadId)
 C     Return start timer named "string".  
565        IMPLICIT NONE        IMPLICIT NONE
566    
567    C     !DESCRIPTION:
568    C     Stop timer named "string".
569    
570    C     !INPUT PARAMETERS:
571    C     string     :: Name of timer
572    C     myThreadId :: My thread number
573        CHARACTER*(*) string        CHARACTER*(*) string
574        INTEGER myThreadId        INTEGER myThreadId
575    CEOP
576  C  C
577        CALL TIMER_CONTROL( string, 'STOP', 'TIMER_STOP' , myThreadId )        CALL TIMER_CONTROL( string, 'STOP', 'TIMER_STOP' , myThreadId )
578  C  C

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22