/[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.28 by ce107, Tue Jul 31 22:46:46 2007 UTC revision 1.29 by jmc, Tue Dec 8 21:44:41 2009 UTC
# Line 20  C--   Routines marked "U" contain UNIX O Line 20  C--   Routines marked "U" contain UNIX O
20  CGG   Modified following A. Biastoch for use with SP3. Is backwards  CGG   Modified following A. Biastoch for use with SP3. Is backwards
21  CGG   compatible. G. Gebbie, gebbie@mit.edu, 20 Oct 2001, Scripps.  CGG   compatible. G. Gebbie, gebbie@mit.edu, 20 Oct 2001, Scripps.
22    
23    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
24  CBOP  CBOP
25  C     !ROUTINE: TIMER_INDEX  C     !ROUTINE: TIMER_INDEX
26    
27  C     !INTERFACE:  C     !INTERFACE:
28        INTEGER FUNCTION TIMER_INDEX (        INTEGER FUNCTION TIMER_INDEX (
29       I        name,timerNames,maxTimers,nTimers )       I        name,timerNames,maxTimers,nTimers )
30        IMPLICIT NONE        IMPLICIT NONE
31    
32  C     !DESCRIPTION:  C     !DESCRIPTION:
33  C     *==========================================================*  C     *==========================================================*
34  C     | FUNCTION TIMER\_INDEX                                        C     | FUNCTION TIMER\_INDEX
35  C     | o Timing support routine.                                  C     | o Timing support routine.
36  C     *==========================================================*  C     *==========================================================*
37  C     | Return index in timer data structure of timer named        C     | Return index in timer data structure of timer named
38  C     | by the function argument "name".                            C     | by the function argument "name".
39  C     *==========================================================*  C     *==========================================================*
40    
41  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
# Line 68  C Line 69  C
69        RETURN        RETURN
70        END        END
71    
72    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
73  CBOP  CBOP
74  C     !ROUTINE: TIMER_CONTROL  C     !ROUTINE: TIMER_CONTROL
75    
# Line 114  C     maxString :: Max length of a timer Line 116  C     maxString :: Max length of a timer
116        PARAMETER ( maxTimers = 50 )        PARAMETER ( maxTimers = 50 )
117        PARAMETER ( maxString = 80 )        PARAMETER ( maxString = 80 )
118  C     timerStarts :: Timer counters for each timer and each thread  C     timerStarts :: Timer counters for each timer and each thread
119  C     timerStops  C     timerStops
120  C     timerUser  C     timerUser
121  C     timerWall  C     timerWall
122  C     timerSys  C     timerSys
123  C     timerT0User  C     timerT0User
124  C     timerT0Wall  C     timerT0Wall
125  C     timerT0Sys  C     timerT0Sys
126  C     timerStatus  :: START/STOP/RUNNING Status of the timer  C     timerStatus  :: START/STOP/RUNNING Status of the timer
127  C     timerNameLen :: Length of timer name  C     timerNameLen :: Length of timer name
128  C     timerNames   :: Table of timer names  C     timerNames   :: Table of timer names
# Line 128  C     nTimers      :: Number of active t Line 130  C     nTimers      :: Number of active t
130        INTEGER timerStarts( maxTimers , MAX_NO_THREADS)        INTEGER timerStarts( maxTimers , MAX_NO_THREADS)
131        SAVE    timerStarts        SAVE    timerStarts
132        INTEGER timerStops ( maxTimers , MAX_NO_THREADS)        INTEGER timerStops ( maxTimers , MAX_NO_THREADS)
133        SAVE    timerStops        SAVE    timerStops
134        Real*8 timerUser  ( maxTimers , MAX_NO_THREADS)        Real*8 timerUser  ( maxTimers , MAX_NO_THREADS)
135        SAVE timerUser        SAVE timerUser
136        Real*8 timerWall  ( maxTimers , MAX_NO_THREADS)        Real*8 timerWall  ( maxTimers , MAX_NO_THREADS)
137        SAVE timerWall        SAVE timerWall
138        Real*8 timerSys   ( maxTimers , MAX_NO_THREADS)        Real*8 timerSys   ( maxTimers , MAX_NO_THREADS)
139        SAVE timerSys            SAVE timerSys
140        Real*8 timerT0User( maxTimers , MAX_NO_THREADS)        Real*8 timerT0User( maxTimers , MAX_NO_THREADS)
141        SAVE timerT0User          SAVE timerT0User
142        Real*8 timerT0Wall( maxTimers , MAX_NO_THREADS)        Real*8 timerT0Wall( maxTimers , MAX_NO_THREADS)
143        SAVE timerT0Wall        SAVE timerT0Wall
144        Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)        Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)
145        SAVE timerT0Sys        SAVE timerT0Sys
146        INTEGER timerStatus( maxTimers , MAX_NO_THREADS)        INTEGER timerStatus( maxTimers , MAX_NO_THREADS)
147        SAVE    timerStatus        SAVE    timerStatus
148        INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)        INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)
# Line 183  C     nTimers      :: Number of active t Line 185  C     nTimers      :: Number of active t
185        INTEGER Check, EventSet        INTEGER Check, EventSet
186        INTEGER papiunit        INTEGER papiunit
187        SAVE EventCode, EventSet        SAVE EventCode, EventSet
188          INTEGER j
189  #else  #else
190  #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)  #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
191  #include <pclh.f>  #include <pclh.f>
# Line 197  C     nTimers      :: Number of active t Line 200  C     nTimers      :: Number of active t
200        INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)        INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)
201        INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)        INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)
202        REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)        REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)
203          INTEGER j
204  #else  #else
205        INTEGER pcl_counter_list(5), alt_counter_list(5)        INTEGER pcl_counter_list(5), alt_counter_list(5)
206        INTEGER*8 i_result(5)        INTEGER*8 i_result(5)
# Line 212  C     nTimers      :: Number of active t Line 216  C     nTimers      :: Number of active t
216  #endif  #endif
217  #endif  #endif
218  #endif  #endif
219        INTEGER I, J        INTEGER I
220        Real*8 userTime        Real*8 userTime
221        Real*8 systemTime        Real*8 systemTime
222        Real*8 wallClockTime        Real*8 wallClockTime
# Line 246  C Line 250  C
250              nTimers(myThreadId) = nTimers(myThreadId) + 1              nTimers(myThreadId) = nTimers(myThreadId) + 1
251              iTimer  = nTimers(myThreadId)              iTimer  = nTimers(myThreadId)
252              timerNames(iTimer,myThreadId)    = tmpName              timerNames(iTimer,myThreadId)    = tmpName
253              timerNameLen(iTimer,myThreadId)  =              timerNameLen(iTimer,myThreadId)  =
254       &       ILNBLNK(tmpName)-IFNBLNK(tmpName)+1       &       ILNBLNK(tmpName)-IFNBLNK(tmpName)+1
255              timerUser(iTimer,myThreadId)     = 0.              timerUser(iTimer,myThreadId)     = 0.
256              timerSys (iTimer,myThreadId)     = 0.              timerSys (iTimer,myThreadId)     = 0.
# Line 261  C Line 265  C
265            timerT0Sys(iTimer,myThreadId)  = systemTime            timerT0Sys(iTimer,myThreadId)  = systemTime
266            timerT0Wall(iTimer,myThreadId) = wallClockTime            timerT0Wall(iTimer,myThreadId) = wallClockTime
267            timerStatus(iTimer,myThreadId) = RUNNING            timerStatus(iTimer,myThreadId) = RUNNING
268            timerStarts(iTimer,myThreadId) =            timerStarts(iTimer,myThreadId) =
269       &       timerStarts(iTimer,myThreadId)+1       &       timerStarts(iTimer,myThreadId)+1
270  #ifdef USE_PAPI  #ifdef USE_PAPI
271  CCE107 PAPI - Read event counts  CCE107 PAPI - Read event counts
# Line 302  CCE107 PCL - Read event counts Line 306  CCE107 PCL - Read event counts
306  #endif  #endif
307  #endif  #endif
308            CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )            CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )
309            timerUser(iTimer,myThreadId)    =            timerUser(iTimer,myThreadId)    =
310       &       timerUser(iTimer,myThreadId) +       &       timerUser(iTimer,myThreadId) +
311       &                           userTime          -       &                           userTime          -
312       &                           timerT0User(iTimer,myThreadId)       &                           timerT0User(iTimer,myThreadId)
313            timerSys (iTimer,myThreadId)    =            timerSys (iTimer,myThreadId)    =
314       &       timerSys(iTimer,myThreadId) +       &       timerSys(iTimer,myThreadId) +
315       &                           systemTime -       &                           systemTime -
316       &                           timerT0Sys(iTimer,myThreadId)       &                           timerT0Sys(iTimer,myThreadId)
317            timerWall(iTimer,myThreadId)    =            timerWall(iTimer,myThreadId)    =
318       &       timerWall(iTimer,myThreadId) +       &       timerWall(iTimer,myThreadId) +
319       &                           wallClockTime -       &                           wallClockTime -
320       &                           timerT0Wall(iTimer,myThreadId)       &                           timerT0Wall(iTimer,myThreadId)
321  #ifdef USE_PAPI  #ifdef USE_PAPI
# Line 329  CCE107 PCL - Read event counts Line 333  CCE107 PCL - Read event counts
333  #endif  #endif
334  #endif  #endif
335            timerStatus(iTimer,myThreadId)  = STOPPED            timerStatus(iTimer,myThreadId)  = STOPPED
336            timerStops (iTimer,myThreadId)  =            timerStops (iTimer,myThreadId)  =
337       &    timerStops (iTimer,myThreadId)+1       &    timerStops (iTimer,myThreadId)+1
338          ENDIF          ENDIF
339  #if defined (USE_PAPI) || defined (USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)  #if defined (USE_PAPI) || defined (USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
340        ELSEIF ( tmpAction .EQ. INIT ) THEN        ELSEIF ( tmpAction .EQ. INIT ) THEN
341  #ifdef USE_PAPI  #ifdef USE_PAPI
342  CCE107 PAPI - Check PAPI version, find the maximum number of events and  CCE107 PAPI - Check PAPI version, find the maximum number of events and
343  C      initialize the library, read the suggested events and create  C      initialize the library, read the suggested events and create
344  C      EventSet, prepare counter for use  C      EventSet, prepare counter for use
345           Check = PAPI_VER_CURRENT           Check = PAPI_VER_CURRENT
346           call PAPIF_library_init(Check)           call PAPIF_library_init(Check)
# Line 349  C      EventSet, prepare counter for use Line 353  C      EventSet, prepare counter for use
353           call PAPIF_num_counters(neventsmax)           call PAPIF_num_counters(neventsmax)
354           if (neventsmax .GT. nmaxevents) then           if (neventsmax .GT. nmaxevents) then
355              WRITE(msgBuffer,*) "Fix the nmaxevents in the code to ",              WRITE(msgBuffer,*) "Fix the nmaxevents in the code to ",
356       $           neventsmax       $           neventsmax
357              CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,              CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
358       &           SQUEEZE_RIGHT,myThreadId)       &           SQUEEZE_RIGHT,myThreadId)
359              CALL ABORT              CALL ABORT
# Line 362  C       reset to reasonable values Line 366  C       reset to reasonable values
366          if (nevents .gt. neventsmax) then          if (nevents .gt. neventsmax) then
367             nevents = neventsmax             nevents = neventsmax
368             WRITE(msgBuffer,*)             WRITE(msgBuffer,*)
369       $          "resetting the number of PAPI events to the maximum"       $          "resetting the number of PAPI events to the maximum"
370             CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,             CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
371       &          SQUEEZE_RIGHT,myThreadId)       &          SQUEEZE_RIGHT,myThreadId)
372          endif          endif
# Line 412  C     reset to reasonable values Line 416  C     reset to reasonable values
416          if (nevents .gt. nmaxevents) then          if (nevents .gt. nmaxevents) then
417             nevents = nmaxevents             nevents = nmaxevents
418             WRITE(msgBuffer,*)             WRITE(msgBuffer,*)
419       $          "resetting the number of PCL events to the maximum"       $          "resetting the number of PCL events to the maximum"
420             CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,             CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
421       &          SQUEEZE_RIGHT,myThreadId)       &          SQUEEZE_RIGHT,myThreadId)
422          endif          endif
# Line 565  CCE107 - Start counting events Line 569  CCE107 - Start counting events
569             WRITE(msgBuffer,71) Eventname,             WRITE(msgBuffer,71) Eventname,
570       $          values(j,I,myThreadId)/timerUser(I,myThreadId),       $          values(j,I,myThreadId)/timerUser(I,myThreadId),
571       $          values(j,I,myThreadId)/timerWall(I,myThreadId),       $          values(j,I,myThreadId)/timerWall(I,myThreadId),
572       $          1.D0*values(j,I,myThreadId)       $          1.D0*values(j,I,myThreadId)
573             CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,             CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
574       &          SQUEEZE_RIGHT,myThreadId)       &          SQUEEZE_RIGHT,myThreadId)
575          enddo          enddo
# Line 575  CCE107 - Start counting events Line 579  CCE107 - Start counting events
579             WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(j)),             WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(j)),
580       $          i_result(j,I,myThreadId)/timerUser(I,myThreadId)       $          i_result(j,I,myThreadId)/timerUser(I,myThreadId)
581       $          ,i_result(j,I,myThreadId)/timerWall(I,myThreadId),1.D0       $          ,i_result(j,I,myThreadId)/timerWall(I,myThreadId),1.D0
582       $          *i_result(j,I,myThreadId)       $          *i_result(j,I,myThreadId)
583             CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,             CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
584       &          SQUEEZE_RIGHT,myThreadId)       &          SQUEEZE_RIGHT,myThreadId)
585          enddo          enddo
# Line 732  C Line 736  C
736   72   FORMAT(A,D13.7)   72   FORMAT(A,D13.7)
737        END        END
738    
739    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
740  CBOP  CBOP
741  C     !ROUTINE: TIMER_GET_TIME  C     !ROUTINE: TIMER_GET_TIME
742    
743  C     !INTERFACE:  C     !INTERFACE:
744        SUBROUTINE TIMER_GET_TIME(            SUBROUTINE TIMER_GET_TIME(
745       O                           userTime,           O                           userTime,
746       O                           systemTime,           O                           systemTime,
747       O                           wallClockTime )       O                           wallClockTime )
748        IMPLICIT NONE        IMPLICIT NONE
749    
750  C     !DESCRIPTION:  C     !DESCRIPTION:
751  C     *==========================================================*  C     *==========================================================*
752  C     | SUBROUTINE TIMER\_GET\_TIME                                  C     | SUBROUTINE TIMER\_GET\_TIME
753  C     | o Query system timer routines.                              C     | o Query system timer routines.
754  C     *==========================================================*  C     *==========================================================*
755  C     | Routine returns total elapsed time for program so far.      C     | Routine returns total elapsed time for program so far.
756  C     | Three times are returned that conventionally are used as    C     | Three times are returned that conventionally are used as
757  C     | user time, system time and wall-clock time. Not all these  C     | user time, system time and wall-clock time. Not all these
758  C     | numbers are available on all machines.                      C     | numbers are available on all machines.
759  C     *==========================================================*  C     *==========================================================*
760    
761  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
# Line 783  C     executable code below. Line 788  C     executable code below.
788        Real*4 actual, tarray(2)        Real*4 actual, tarray(2)
789  # elif (defined TARGET_T3E || defined TARGET_CRAY_VECTOR)  # elif (defined TARGET_T3E || defined TARGET_CRAY_VECTOR)
790        real second, secondr        real second, secondr
791        external second, secondr        external second, secondr
792  # else  # else
793  #  ifdef HAVE_ETIME  #  ifdef HAVE_ETIME
794        Real*4 etime        Real*4 etime
# Line 830  CCE107 Fixed for AIX and UNICOS Line 835  CCE107 Fixed for AIX and UNICOS
835        wallClockTime = wtime        wallClockTime = wtime
836  #  elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))  #  elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))
837        wallClockTime = MPI_Wtime()        wallClockTime = MPI_Wtime()
838  #  else        #  else
839        wallClockTime = timenow()        wallClockTime = timenow()
840  #  endif  #  endif
841  # endif  # endif
# Line 838  CCE107 Fixed for AIX and UNICOS Line 843  CCE107 Fixed for AIX and UNICOS
843    
844        RETURN        RETURN
845        END        END
       
   
   
846    
847    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
848  CBOP  CBOP
   
849  C     !ROUTINE: TIMER_PRINTALL  C     !ROUTINE: TIMER_PRINTALL
850    
851  C     !INTERFACE:  C     !INTERFACE:
# Line 852  C     !INTERFACE: Line 854  C     !INTERFACE:
854    
855  C     !DESCRIPTION:  C     !DESCRIPTION:
856  C     *==========================================================*  C     *==========================================================*
857  C     | SUBROUTINE TIMER\_PRINTALL                                  C     | SUBROUTINE TIMER\_PRINTALL
858  C     | o Print timer information                                  C     | o Print timer information
859  C     *==========================================================*  C     *==========================================================*
860  C     | Request print out of table of timing from all timers.      C     | Request print out of table of timing from all timers.
861  C     *==========================================================*  C     *==========================================================*
862    
863  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
# Line 863  C     myThreadId :: This threads number Line 865  C     myThreadId :: This threads number
865        INTEGER myThreadId        INTEGER myThreadId
866  CEOP  CEOP
867    
868        CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,        CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,
869       &                   myThreadId )       &                   myThreadId )
870  C  C
871        RETURN        RETURN
872        END        END
873    
874    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
875  CBOP  CBOP
876  C     !ROUTINE: TIMER_START  C     !ROUTINE: TIMER_START
877    
# Line 890  C Line 893  C
893  C  C
894        RETURN        RETURN
895        END        END
896    
897    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
898  CBOP  CBOP
899  C     !ROUTINE: TIMER_STOP  C     !ROUTINE: TIMER_STOP
900    
# Line 911  C Line 916  C
916  C  C
917        RETURN        RETURN
918        END        END
919  C***********************************************************************  
920    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
921    
922  #ifdef USE_PAPI  #ifdef USE_PAPI
923  CCE107 Initialization of common block for PAPI timers  CCE107 Initialization of common block for PAPI timers
# Line 927  CCE107 Initialization of common block fo Line 933  CCE107 Initialization of common block fo
933       $     values1(nmaxevents, maxTimers, MAX_NO_THREADS),       $     values1(nmaxevents, maxTimers, MAX_NO_THREADS),
934       $     values2(nmaxevents, maxTimers, MAX_NO_THREADS)       $     values2(nmaxevents, maxTimers, MAX_NO_THREADS)
935        COMMON /papivalues/ values, values1, values2        COMMON /papivalues/ values, values1, values2
936        DATA values, values1, values2 /size*0/        DATA values, values1, values2 /size*0/
937        END        END
938  #endif  #endif
939  #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)  #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)

Legend:
Removed from v.1.28  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22