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

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22