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

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

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


Revision 1.26 - (hide annotations) (download)
Thu Jan 11 17:44:18 2007 UTC (17 years, 4 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint58w_post, checkpoint58v_post, checkpoint58u_post
Changes since 1.25: +4 -4 lines
Expand the max number of timers from 40 to 50

1 molod 1.26 C $Header: /u/gcmpack/MITgcm/eesupp/src/timers.F,v 1.25 2006/10/12 20:27:45 jmc Exp $
2 edhill 1.13 C $Name: $
3 adcroft 1.1
4     #include "CPP_EEOPTIONS.h"
5 ce107 1.20 #ifdef USE_LIBHPM
6     # include "f_hpm.h"
7     #endif
8 adcroft 1.1
9     C-- File utils.F: General purpose support routines
10     C-- Contents
11     C-- TIMER_INDEX - Returns index associated with timer name.
12     C-- M TIMER_CONTROL - Implements timer functions for given machine.
13     C-- TIMER_PRINT - Print CPU timer statitics.
14     C-- TIMER_PRINTALL - Prints all CPU timers statistics.
15     C-- TIMER_START - Starts CPU timer for code section.
16     C-- TIMER_STOP - Stop CPU tier for code section.
17     C-- Routines marked "M" contain specific machine dependent code.
18     C-- Routines marked "U" contain UNIX OS calls.
19    
20 heimbach 1.12 CGG Modified following A. Biastoch for use with SP3. Is backwards
21     CGG compatible. G. Gebbie, gebbie@mit.edu, 20 Oct 2001, Scripps.
22    
23 cnh 1.10 CBOP
24     C !ROUTINE: TIMER_INDEX
25    
26     C !INTERFACE:
27 adcroft 1.1 INTEGER FUNCTION TIMER_INDEX (
28     I name,timerNames,maxTimers,nTimers )
29 adcroft 1.5 IMPLICIT NONE
30 cnh 1.10
31     C !DESCRIPTION:
32     C *==========================================================*
33 edhill 1.16 C | FUNCTION TIMER\_INDEX
34 cnh 1.10 C | o Timing support routine.
35     C *==========================================================*
36     C | Return index in timer data structure of timer named
37     C | by the function argument "name".
38     C *==========================================================*
39    
40     C !INPUT/OUTPUT PARAMETERS:
41     C == Routine arguements ==
42     C maxTimers :: Total number of timers allowed
43     C nTimers :: Current number of timers
44     C name :: Name of timer to find
45     C timerNames :: List of valid timer names
46 adcroft 1.1 INTEGER maxTimers
47     INTEGER nTimers
48     CHARACTER*(*) name
49     CHARACTER*(*) timerNames(maxTimers)
50 cnh 1.10
51     C !LOCAL VARIABLES:
52     C == Local variables ==
53     C I :: Index variable
54 adcroft 1.1 INTEGER I
55 cnh 1.10 CEOP
56 adcroft 1.1 C
57     TIMER_INDEX = 0
58     IF ( name .EQ. ' ' ) THEN
59     TIMER_INDEX = -1
60     ELSE
61     DO 10 I = 1, nTimers
62     IF ( name .NE. timerNames(I) ) GOTO 10
63     TIMER_INDEX = I
64     GOTO 11
65     10 CONTINUE
66     11 CONTINUE
67     ENDIF
68     RETURN
69     END
70    
71 cnh 1.10 CBOP
72     C !ROUTINE: TIMER_CONTROL
73    
74     C !INTERFACE:
75 adcroft 1.1 SUBROUTINE TIMER_CONTROL ( name , action , callProc , myThreadId )
76 cnh 1.10 IMPLICIT NONE
77    
78     C !DESCRIPTION:
79     C *==========================================================*
80 edhill 1.16 C | SUBROUTINE TIMER\_CONTROL |
81 adcroft 1.1 C | o Timing routine. |
82 cnh 1.10 C *==========================================================*
83 adcroft 1.1 C | User callable interface to timing routines. Timers are |
84     C | created, stopped, started and queried only through this |
85     C | rtouine. |
86 cnh 1.10 C *==========================================================*
87    
88     C !USES:
89 adcroft 1.1 #include "SIZE.h"
90     #include "EEPARAMS.h"
91     #include "EESUPPORT.h"
92     INTEGER TIMER_INDEX
93     INTEGER IFNBLNK
94     INTEGER ILNBLNK
95     EXTERNAL TIMER_INDEX
96     EXTERNAL IFNBLNK
97     EXTERNAL ILNBLNK
98 cnh 1.10
99     C !INPUT/OUTPUT PARAMETERS:
100     C name :: name of the timer
101     C action :: operation to perform with this timer
102     C callProc :: procedure calling this routine
103     C myThreadId :: instance number of this thread
104     CHARACTER*(*) name
105     CHARACTER*(*) action
106     CHARACTER*(*) callProc
107     INTEGER myThreadId
108 adcroft 1.1 C
109 cnh 1.10 C !LOCAL VARIABLES:
110     C maxTimers :: Total numer of timer allowed
111     C maxString :: Max length of a timer name
112 adcroft 1.1 INTEGER maxTimers
113     INTEGER maxString
114 molod 1.26 PARAMETER ( maxTimers = 50 )
115 adcroft 1.1 PARAMETER ( maxString = 80 )
116 cnh 1.10 C timerStarts :: Timer counters for each timer and each thread
117     C timerStops
118     C timerUser
119     C timerWall
120     C timerSys
121     C timerT0User
122     C timerT0Wall
123     C timerT0Sys
124     C timerStatus :: START/STOP/RUNNING Status of the timer
125     C timerNameLen :: Length of timer name
126     C timerNames :: Table of timer names
127     C nTimers :: Number of active timers
128 adcroft 1.1 INTEGER timerStarts( maxTimers , MAX_NO_THREADS)
129     SAVE timerStarts
130     INTEGER timerStops ( maxTimers , MAX_NO_THREADS)
131     SAVE timerStops
132     Real*8 timerUser ( maxTimers , MAX_NO_THREADS)
133     SAVE timerUser
134     Real*8 timerWall ( maxTimers , MAX_NO_THREADS)
135     SAVE timerWall
136     Real*8 timerSys ( maxTimers , MAX_NO_THREADS)
137     SAVE timerSys
138     Real*8 timerT0User( maxTimers , MAX_NO_THREADS)
139     SAVE timerT0User
140     Real*8 timerT0Wall( maxTimers , MAX_NO_THREADS)
141     SAVE timerT0Wall
142     Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)
143     SAVE timerT0Sys
144     INTEGER timerStatus( maxTimers , MAX_NO_THREADS)
145     SAVE timerStatus
146     INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)
147     SAVE timerNameLen
148     CHARACTER*(maxString) timerNames( maxTimers , MAX_NO_THREADS)
149     SAVE timerNames
150     INTEGER nTimers(MAX_NO_THREADS)
151     CHARACTER*(maxString) tmpName
152     CHARACTER*(maxString) tmpAction
153     INTEGER iTimer
154     INTEGER ISTART
155     INTEGER IEND
156     INTEGER STOPPED
157     PARAMETER ( STOPPED = 0 )
158     INTEGER RUNNING
159     PARAMETER ( RUNNING = 1 )
160     CHARACTER*(*) STOP
161     PARAMETER ( STOP = 'STOP' )
162     CHARACTER*(*) START
163     PARAMETER ( START = 'START' )
164     CHARACTER*(*) PRINT
165     PARAMETER ( PRINT = 'PRINT' )
166     CHARACTER*(*) PRINTALL
167     PARAMETER ( PRINTALL = 'PRINTALL' )
168 ce107 1.21 #if defined(USE_PAPI) || defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined (USE_PCL)
169 ce107 1.20 CHARACTER*(*) INIT
170     PARAMETER ( INIT = 'INIT' )
171 ce107 1.21 #ifdef USE_PAPI
172 ce107 1.20 INTEGER nmaxevents
173     PARAMETER (nmaxevents = 18)
174 ce107 1.21 INTEGER neventsmax, nevents
175     SAVE neventsmax, nevents
176 ce107 1.20 INTEGER*8 values(nmaxevents, maxTimers , MAX_NO_THREADS),
177     $ values1(nmaxevents, maxTimers, MAX_NO_THREADS),
178     $ values2(nmaxevents, maxTimers, MAX_NO_THREADS)
179     COMMON /papivalues/ values, values1, values2
180 ce107 1.21 #include <fpapi.h>
181     CHARACTER(13) EventName
182     INTEGER EventCode(nmaxevents)
183     INTEGER Check, EventSet
184 ce107 1.20 INTEGER papiunit
185 ce107 1.21 SAVE EventCode, EventSet
186     #else
187     #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
188     #include <pclh.f>
189     INTEGER nmaxevents
190     PARAMETER (nmaxevents = 61)
191     INTEGER flags, res, nevents
192     INTEGER*8 descr
193     CHARACTER*22 pcl_counter_name(0:nmaxevents-1)
194     #ifdef USE_PCL
195     INTEGER pcl_counter_list(nmaxevents)
196     INTEGER*8 i_result(nmaxevents, maxTimers, MAX_NO_THREADS)
197     INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)
198     INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)
199     REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)
200     #else
201     INTEGER pcl_counter_list(5), alt_counter_list(5)
202     INTEGER*8 i_result(5)
203     REAL*8 fp_result(5)
204     SAVE alt_counter_list
205     DATA alt_counter_list /PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
206     $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO/
207     #endif
208     COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
209     $ flags, nevents
210     COMMON /pclnames/ pcl_counter_name
211     INTEGER pclunit
212     #endif
213     #endif
214 ce107 1.20 #endif
215     INTEGER I, J
216 adcroft 1.1 Real*8 userTime
217     Real*8 systemTime
218     Real*8 wallClockTime
219     CHARACTER*(MAX_LEN_MBUF) msgBuffer
220     DATA nTimers /MAX_NO_THREADS*0/
221     SAVE nTimers
222 cnh 1.10 CEOP
223 adcroft 1.1 C
224     ISTART = IFNBLNK(name)
225     IEND = ILNBLNK(name)
226     IF ( IEND - ISTART + 1 .GT. maxString ) GOTO 901
227     IF ( ISTART .NE. 0 ) THEN
228     tmpName = name(ISTART:IEND)
229     CALL UCASE( tmpName )
230     ELSE
231     tmpName = ' '
232     ENDIF
233     ISTART = IFNBLNK(action)
234     IEND = ILNBLNK(action)
235     IF ( ISTART .EQ. 0 ) GOTO 902
236     IF ( IEND - ISTART + 1 .GT. maxString ) GOTO 903
237     tmpAction = action(ISTART:IEND)
238     CALL UCASE( tmpAction )
239     C
240 cnh 1.4 iTimer=TIMER_INDEX(tmpName,timerNames(1,myThreadId),
241     & maxTimers,nTimers(myThreadId))
242 adcroft 1.1 C
243     IF ( tmpAction .EQ. START ) THEN
244     IF ( iTimer .EQ. 0 ) THEN
245     IF ( nTimers(myThreadId) .EQ. maxTimers ) GOTO 904
246     nTimers(myThreadId) = nTimers(myThreadId) + 1
247     iTimer = nTimers(myThreadId)
248     timerNames(iTimer,myThreadId) = tmpName
249 cnh 1.4 timerNameLen(iTimer,myThreadId) =
250     & ILNBLNK(tmpName)-IFNBLNK(tmpName)+1
251 adcroft 1.1 timerUser(iTimer,myThreadId) = 0.
252     timerSys (iTimer,myThreadId) = 0.
253     timerWall(iTimer,myThreadId) = 0.
254     timerStarts(iTimer,myThreadId) = 0
255     timerStops (iTimer,myThreadId) = 0
256     timerStatus(iTimer,myThreadId) = STOPPED
257     ENDIF
258     IF ( timerStatus(iTimer,myThreadId) .NE. RUNNING ) THEN
259     CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )
260     timerT0User(iTimer,myThreadId) = userTime
261     timerT0Sys(iTimer,myThreadId) = systemTime
262     timerT0Wall(iTimer,myThreadId) = wallClockTime
263     timerStatus(iTimer,myThreadId) = RUNNING
264 cnh 1.4 timerStarts(iTimer,myThreadId) =
265     & timerStarts(iTimer,myThreadId)+1
266 ce107 1.20 #ifdef USE_PAPI
267 ce107 1.21 CCE107 PAPI - Read event counts
268 ce107 1.20 call PAPIF_read(EventSet, values1(1,iTimer,myThreadId), Check)
269 ce107 1.21 #else
270     #ifdef USE_PCL
271     CCE107 PCL - Read event counts
272     res = PCLread(descr, i_result1(1,iTimer,myThreadId),
273     $ fp_result(1,iTimer,myThreadId), nevents)
274     #endif
275 ce107 1.20 #endif
276 adcroft 1.1 ENDIF
277 ce107 1.20 #ifdef USE_LIBHPM
278     CALL f_hpmtstart((myThreadId-1)*100+iTimer,tmpName)
279     #endif
280 adcroft 1.1 ELSEIF ( tmpAction .EQ. STOP ) THEN
281     IF ( iTimer .EQ. 0 ) GOTO 905
282 ce107 1.20 #ifdef USE_LIBHPM
283     CALL f_hpmtstop((myThreadId-1)*100+iTimer)
284     #endif
285 adcroft 1.1 IF ( timerStatus(iTimer,myThreadId) .EQ. RUNNING ) THEN
286 ce107 1.20 #ifdef USE_PAPI
287     CCE107 PAPI - Read event counts
288     call PAPIF_read(EventSet, values2(1,iTimer,myThreadId), Check)
289 ce107 1.21 #else
290     #ifdef USE_PCL
291     CCE107 PCL - Read event counts
292     res = PCLread(descr, i_result2(1,iTimer,myThreadId),
293     $ fp_result(1,iTimer,myThreadId), nevents)
294     #endif
295 ce107 1.20 #endif
296 adcroft 1.1 CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )
297 cnh 1.4 timerUser(iTimer,myThreadId) =
298     & timerUser(iTimer,myThreadId) +
299 adcroft 1.1 & userTime -
300     & timerT0User(iTimer,myThreadId)
301 cnh 1.4 timerSys (iTimer,myThreadId) =
302     & timerSys(iTimer,myThreadId) +
303 adcroft 1.1 & systemTime -
304     & timerT0Sys(iTimer,myThreadId)
305 cnh 1.4 timerWall(iTimer,myThreadId) =
306     & timerWall(iTimer,myThreadId) +
307 adcroft 1.1 & wallClockTime -
308     & timerT0Wall(iTimer,myThreadId)
309 ce107 1.20 #ifdef USE_PAPI
310     do i=1,nevents
311     values(i,iTimer,myThreadId) = values(i,iTimer,myThreadId) +
312     $ values2(i,iTimer,myThreadId) - values1(i,iTimer,myThreadId)
313     enddo
314 ce107 1.21 #else
315     #ifdef USE_PCL
316     do i=1,nevents
317     i_result(i,iTimer,myThreadId) = i_result(i,iTimer
318     $ ,myThreadId) + i_result2(i,iTimer,myThreadId) -
319     $ i_result1(i,iTimer,myThreadId)
320     enddo
321     #endif
322 ce107 1.20 #endif
323 adcroft 1.1 timerStatus(iTimer,myThreadId) = STOPPED
324 cnh 1.4 timerStops (iTimer,myThreadId) =
325     & timerStops (iTimer,myThreadId)+1
326 adcroft 1.1 ENDIF
327 ce107 1.21 #if defined (USE_PAPI) || defined (USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
328     ELSEIF ( tmpAction .EQ. INIT ) THEN
329 ce107 1.20 #ifdef USE_PAPI
330     CCE107 PAPI - Check PAPI version, find the maximum number of events and
331     C initialize the library, read the suggested events and create
332     C EventSet, prepare counter for use
333     Check = PAPI_VER_CURRENT
334     call PAPIF_library_init(Check)
335     if (Check .NE. PAPI_VER_CURRENT) then
336     WRITE(msgBuffer,*) "PAPI Library Version is out of Date"
337     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
338     & SQUEEZE_RIGHT,myThreadId)
339     CALL ABORT
340     endif
341 ce107 1.21 call PAPIF_num_counters(neventsmax)
342 ce107 1.20 if (neventsmax .GT. nmaxevents) then
343     WRITE(msgBuffer,*) "Fix the nmaxevents in the code to ",
344     $ neventsmax
345     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
346     & SQUEEZE_RIGHT,myThreadId)
347     CALL ABORT
348     endif
349     _BEGIN_MASTER(myThreadId)
350     CALL mdsFindUnit (papiunit, myThreadId)
351     OPEN(UNIT=papiunit,FILE='data.papi',STATUS='OLD')
352     read(papiunit,*) nevents
353     C reset to reasonable values
354     if (nevents .gt. neventsmax) then
355     nevents = neventsmax
356     WRITE(msgBuffer,*)
357     $ "resetting the number of PAPI events to the maximum"
358     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
359 ce107 1.21 & SQUEEZE_RIGHT,myThreadId)
360 ce107 1.20 endif
361     do i = 1,nevents
362 ce107 1.21 read(papiunit,*) EventName
363     if ((EventName .eq. 'PAPI_FLOPS') .or.
364     $ (EventName .eq. 'PAPI_IPS')) then
365     WRITE(msgBuffer,*) "Abort! Rate events are not supported:"
366     $ ,EventName
367     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
368     & SQUEEZE_RIGHT,myThreadId)
369     CALL ABORT
370     endif
371    
372     call PAPIF_event_name_to_code(EventName, EventCode(i), Check)
373 ce107 1.20 end do
374     close(papiunit)
375     _END_MASTER(myThid)
376     EventSet = PAPI_NULL
377     call PAPIF_create_eventset(EventSet, Check)
378     do i = 1,nevents
379     call PAPIF_add_event(EventSet, EventCode(i), Check)
380     if (Check .NE. PAPI_OK) then
381     CALL PAPIF_event_code_to_name(EventCode(i), EventName,
382     $ Check)
383     WRITE(msgBuffer,*) "Abort After PAPIF_add_event: ",
384     $ EventName
385     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
386     & SQUEEZE_RIGHT,myThreadId)
387     CALL ABORT
388     endif
389     enddo
390     CCE107 - Start counting events
391     call PAPIF_start(EventSet, Check)
392 ce107 1.21 #else
393     #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
394     CCE107 PCL - initialize the library, read the suggested events
395     C and check them
396     res = PCLinit(descr)
397    
398     #ifdef USE_PCL
399     _BEGIN_MASTER(myThreadId)
400     CALL mdsFindUnit (pclunit, myThreadId)
401     OPEN(UNIT=pclunit,FILE='data.pcl',STATUS='OLD')
402     read(pclunit,*) nevents
403     C reset to reasonable values
404     if (nevents .gt. nmaxevents) then
405     nevents = nmaxevents
406     WRITE(msgBuffer,*)
407     $ "resetting the number of PCL events to the maximum"
408     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
409     & SQUEEZE_RIGHT,myThreadId)
410     endif
411     do i = 1,nevents
412     read(pclunit,*) pcl_counter_list(i)
413     if ((pcl_counter_list(i) .ge. PCL_MFLOPS) .or.
414     $ (pcl_counter_list(i) .lt. 1)) then
415     if ((pcl_counter_list(i) .ge. PCL_MFLOPS) .and.
416     $ (pcl_counter_list(i) .le. nmaxevents)) then
417     WRITE(msgBuffer,*)
418     $ "Abort! Rate events are not relevant:",
419     $ pcl_counter_name(pcl_counter_list(i))
420     else
421     WRITE(msgBuffer,*)
422     $ "Abort! Events are not defined:",
423     $ pcl_counter_list(i)
424     endif
425     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
426     & SQUEEZE_RIGHT,myThreadId)
427     CALL ABORT
428     endif
429     enddo
430     close(pclunit)
431     _END_MASTER(myThid)
432    
433     do i = 1,nevents
434     CCE107 check to see that event are supported in the order asked
435     res = PCLquery(descr, pcl_counter_list, i, flags)
436     IF(res .NE. PCL_SUCCESS) THEN
437     WRITE(msgBuffer,*) "Abort! No support when adding event: "
438     $ , pcl_counter_name(pcl_counter_list(i))
439     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
440     & SQUEEZE_RIGHT,myThreadId)
441     CALL ABORT
442     endif
443     enddo
444     #else
445     do i = 1,5
446     CCE107 check to see which rate events are supported.
447     res = PCLquery(descr, pcl_counter_list, nevents+1, flags)
448     if ((res .ne. PCL_SUCCESS) .and. (i .lt. 5)) then
449     pcl_counter_list(nevents+1) = alt_counter_list(i+1)
450     else
451     if (i .lt. 5) then
452     nevents = nevents + 1
453     endif
454     endif
455     enddo
456     if (nevents .eq. 0) then
457     WRITE(msgBuffer,*)
458     $ "No PCL rate events supported: Please recompile!"
459     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
460     & SQUEEZE_RIGHT,myThreadId)
461     CALL ABORT
462     endif
463     #endif
464    
465     CCE107 - Start counting events
466     res = PCLstart(descr, pcl_counter_list, nevents, flags)
467     IF(res .NE. PCL_SUCCESS) THEN
468     WRITE(msgBuffer,*) "PCL counting failed - please recompile!"
469     CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
470     & SQUEEZE_RIGHT,myThreadId)
471     CALL ABORT
472     ENDIF
473     #endif
474     #endif
475 ce107 1.20 #endif
476 adcroft 1.1 ELSEIF ( tmpAction .EQ. PRINT ) THEN
477     IF ( iTimer .EQ. 0 ) GOTO 905
478     WRITE(msgBuffer,*)
479     & ' Seconds in section "',
480 cnh 1.4 & timerNames(iTimer,myThreadId)(1:timerNameLen(iTimer,myThreadId))
481     & ,'":'
482     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
483     & SQUEEZE_RIGHT,myThreadId)
484     WRITE(msgBuffer,*) ' User time:',
485     & timerUser(iTimer,myThreadId)
486     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
487     & SQUEEZE_RIGHT,myThreadId)
488     WRITE(msgBuffer,*) ' System time:',
489     & timerSys(iTimer,myThreadId)
490     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
491     & SQUEEZE_RIGHT,myThreadId)
492     WRITE(msgBuffer,*) ' Wall clock time:',
493     & timerWall(iTimer,myThreadId)
494     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
495     & SQUEEZE_RIGHT,myThreadId)
496     WRITE(msgBuffer,*) ' No. starts:',
497     & timerStarts(iTimer,myThreadId)
498     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
499     & SQUEEZE_RIGHT,myThreadId)
500     WRITE(msgBuffer,*) ' No. stops:',
501     & timerStops(iTimer,myThreadId)
502     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
503     & SQUEEZE_RIGHT,myThreadId)
504 ce107 1.20 #ifdef USE_PAPI
505     do i = 1,nevents
506     call PAPIF_event_code_to_name(EventCode(i), EventName, Check)
507 ce107 1.21 WRITE(msgBuffer,71) Eventname,
508     $ values(i,iTimer,myThreadId)/timerUser(iTimer,myThreadId)
509     $ ,values(i,iTimer,myThreadId)/timerWall(iTimer,myThreadId
510     $ ),1.D0*values(i,iTimer,myThreadId)
511     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
512     & SQUEEZE_RIGHT,myThreadId)
513     enddo
514     #else
515     #ifdef USE_PCL
516     do i = 1,nevents
517     WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(i)),
518     $ i_result(i,iTimer,myThreadId)/timerUser(iTimer
519     $ ,myThreadId),i_result(i,iTimer,myThreadId)
520     $ /timerWall(iTimer,myThreadId),1.D0*i_result(i,iTimer
521     $ ,myThreadId)
522 ce107 1.20 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
523     & SQUEEZE_RIGHT,myThreadId)
524     enddo
525     #endif
526 ce107 1.21 #endif
527 adcroft 1.1 ELSEIF ( tmpAction .EQ. PRINTALL ) THEN
528     DO 10 I = 1, nTimers(myThreadId)
529     WRITE(msgBuffer,*) ' Seconds in section "',
530 cnh 1.4 & timerNames(I,myThreadId)(1:timerNameLen(I,myThreadId))
531     & ,'":'
532     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
533     & SQUEEZE_RIGHT,myThreadId)
534     WRITE(msgBuffer,*) ' User time:',
535     & timerUser(I,myThreadId)
536     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
537     & SQUEEZE_RIGHT,myThreadId)
538     WRITE(msgBuffer,*) ' System time:',
539     & timerSys(I,myThreadId)
540     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
541     & SQUEEZE_RIGHT,myThreadId)
542     WRITE(msgBuffer,*) ' Wall clock time:',
543     & timerWall(I,myThreadId)
544     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
545     & SQUEEZE_RIGHT,myThreadId)
546     WRITE(msgBuffer,*) ' No. starts:',
547     & timerStarts(I,myThreadId)
548     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
549     & SQUEEZE_RIGHT,myThreadId)
550     WRITE(msgBuffer,*) ' No. stops:',
551     & timerStops(I,myThreadId)
552     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
553     & SQUEEZE_RIGHT,myThreadId)
554 ce107 1.20 #ifdef USE_PAPI
555     do j = 1,nevents
556     call PAPIF_event_code_to_name(EventCode(j), EventName, Check)
557 ce107 1.21 WRITE(msgBuffer,71) Eventname,
558     $ values(j,I,myThreadId)/timerUser(I,myThreadId),
559     $ values(j,I,myThreadId)/timerWall(I,myThreadId),
560     $ 1.D0*values(j,I,myThreadId)
561     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
562     & SQUEEZE_RIGHT,myThreadId)
563     enddo
564     #else
565     #ifdef USE_PCL
566     do j = 1,nevents
567     WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(j)),
568     $ i_result(j,I,myThreadId)/timerUser(I,myThreadId)
569     $ ,i_result(j,I,myThreadId)/timerWall(I,myThreadId),1.D0
570     $ *i_result(j,I,myThreadId)
571 ce107 1.20 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
572     & SQUEEZE_RIGHT,myThreadId)
573     enddo
574     #endif
575 ce107 1.21 #endif
576 adcroft 1.1 10 CONTINUE
577     ELSE
578     GOTO 903
579     ENDIF
580     C
581     1000 CONTINUE
582     C
583     RETURN
584     901 CONTINUE
585     WRITE(msgBuffer,'(A)')
586     &' '
587 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
588 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
589 adcroft 1.1 WRITE(msgBuffer,*)
590     &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
591 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
592 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
593 adcroft 1.1 WRITE(msgBuffer,*)
594     &'procedure: "',callProc,'".'
595 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
596 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
597 adcroft 1.1 WRITE(msgBuffer,*)
598     &'Timer name "',name(ISTART:IEND),'" is invalid.'
599 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
600 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
601 adcroft 1.1 WRITE(msgBuffer,*)
602     &' Names must have fewer than',maxString+1,' characters.'
603 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
604 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
605 adcroft 1.1 WRITE(msgBuffer,*)
606     &'*******************************************************'
607 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
608 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
609 adcroft 1.1 GOTO 1000
610     902 CONTINUE
611     WRITE(msgBuffer,*)
612     &' '
613 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
614 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
615 adcroft 1.1 WRITE(msgBuffer,*)
616     &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
617 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
618 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
619 adcroft 1.1 WRITE(msgBuffer,*)
620     &'procedure: "',callProc,'".'
621 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
622 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
623 adcroft 1.1 WRITE(msgBuffer,*)
624     &' No timer action specified.'
625 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
626 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
627 adcroft 1.1 WRITE(msgBuffer,*)
628     &' Valid actions are:'
629 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
630 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
631 adcroft 1.1 WRITE(msgBuffer,*)
632     &' "START", "STOP", "PRINT" and "PRINTALL".'
633 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
634 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
635 adcroft 1.1 WRITE(msgBuffer,*)
636     &'*******************************************************'
637 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
638 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
639 adcroft 1.1 GOTO 1000
640     903 CONTINUE
641     WRITE(msgBuffer,*)
642     &' '
643 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
644 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
645 adcroft 1.1 WRITE(msgBuffer,*)
646     &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
647 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
648 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
649 adcroft 1.1 WRITE(msgBuffer,*)
650     &'procedure: "',callProc,'".'
651 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
652 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
653 adcroft 1.1 WRITE(msgBuffer,*)
654     &'Timer action"',name(ISTART:IEND),'" is invalid.'
655 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
656 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
657 adcroft 1.1 WRITE(msgBuffer,*)
658     &' Valid actions are:'
659 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
660 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
661 adcroft 1.1 WRITE(msgBuffer,*)
662     &' "START", "STOP", "PRINT" and "PRINTALL".'
663 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
664 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
665 adcroft 1.1 WRITE(msgBuffer,*)
666     &'*******************************************************'
667 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
668 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
669 adcroft 1.1 GOTO 1000
670     904 CONTINUE
671     WRITE(msgBuffer,*)
672     &' '
673 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
674 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
675 adcroft 1.1 WRITE(msgBuffer,*)
676     &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
677 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
678 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
679 adcroft 1.1 WRITE(msgBuffer,*)
680     &'procedure: "',callProc,'".'
681 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
682 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
683 adcroft 1.1 WRITE(msgBuffer,*)
684     &'Timer "',name(ISTART:IEND),'" cannot be created.'
685 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
686 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
687 adcroft 1.1 WRITE(msgBuffer,*)
688     &' Only ',maxTimers,' timers are allowed.'
689 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
690 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
691 adcroft 1.1 WRITE(msgBuffer,*)
692     &'*******************************************************'
693 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
694 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
695 adcroft 1.1 GOTO 1000
696     905 CONTINUE
697     WRITE(msgBuffer,*)
698     &' '
699 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
700 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
701 adcroft 1.1 WRITE(msgBuffer,*)
702     &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
703 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
704 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
705 adcroft 1.1 WRITE(msgBuffer,*)
706     &'procedure: "',callProc,'".'
707 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
708 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
709 adcroft 1.1 WRITE(msgBuffer,*)
710     &'Timer name is blank.'
711 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
712 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
713 adcroft 1.1 WRITE(msgBuffer,*)
714     &' A name must be used with "START", "STOP" or "PRINT".'
715 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
716 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
717 adcroft 1.1 WRITE(msgBuffer,*)
718     &'*******************************************************'
719 jmc 1.22 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
720 cnh 1.4 & SQUEEZE_RIGHT,myThreadId)
721 adcroft 1.1 GOTO 1000
722 ce107 1.20
723     71 FORMAT(A,' per sec ',D13.7,' ',D13.7,', number ', D13.7)
724     72 FORMAT(A,D13.7)
725 adcroft 1.1 END
726    
727 cnh 1.10 CBOP
728     C !ROUTINE: TIMER_GET_TIME
729    
730     C !INTERFACE:
731 cnh 1.23 SUBROUTINE TIMER_GET_TIME(
732     O userTime,
733     O systemTime,
734 adcroft 1.1 O wallClockTime )
735 adcroft 1.5 IMPLICIT NONE
736 cnh 1.10
737     C !DESCRIPTION:
738     C *==========================================================*
739 edhill 1.16 C | SUBROUTINE TIMER\_GET\_TIME
740 cnh 1.10 C | o Query system timer routines.
741     C *==========================================================*
742     C | Routine returns total elapsed time for program so far.
743     C | Three times are returned that conventionally are used as
744     C | user time, system time and wall-clock time. Not all these
745     C | numbers are available on all machines.
746     C *==========================================================*
747    
748     C !INPUT/OUTPUT PARAMETERS:
749     C userTime :: User time returned
750     C systemTime :: System time returned
751     C wallClockTime :: Wall clock time returned
752 cnh 1.23
753 adcroft 1.1 Real*8 userTime
754     Real*8 systemTime
755     Real*8 wallClockTime
756 cnh 1.10
757 cnh 1.23 C The following was seriously hacked around by Mark Hadfield
758     C October 2006
759    
760     #ifdef IGNORE_TIME
761    
762     userTime = 0.
763     systemTime = 0.
764     wallClockTime = 0.
765    
766 ce107 1.18 #else
767 cnh 1.10
768 cnh 1.23 C Declarations follow the same preprocessor structure as the
769     C executable code below.
770    
771     # ifdef TARGET_AIX
772     Real*4 etime_
773     Real*8 timenow
774     external etime_, timenow
775     Real*4 actual, tarray(2)
776 cnh 1.24 # elif (defined TARGET_T3E || defined TARGET_CRAY_VECTOR)
777     real second, secondr
778     external second, secondr
779 cnh 1.23 # else
780     # ifdef HAVE_ETIME
781     Real*4 etime
782     EXTERNAL etime
783     Real*4 actual, tarray(2)
784     # else
785     Real*8 csystemtime, cusertime
786     external csystemtime, cusertime
787     # endif
788     # if defined HAVE_CLOC
789 adcroft 1.1 Real*8 wtime
790 cnh 1.23 # elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))
791     C No declarations necessary
792 jmc 1.25 # else
793     Real*8 timenow
794 cnh 1.23 external timenow
795     # endif /* HAVE_CLOC */
796     # endif
797 cnh 1.10 CEOP
798    
799 cnh 1.23 C Executable code
800 edhill 1.19
801 cnh 1.23 # ifdef TARGET_AIX
802     actual = ETIME_(tarray)
803     userTime = tarray(1)
804     systemTime = tarray(2)
805 heimbach 1.12 wallClockTime = timenow()
806 cnh 1.23 # elif (defined (TARGET_T3E) || defined (TARGET_CRAY_VECTOR))
807 ce107 1.18 userTime = SECOND()
808 heimbach 1.12 systemTime = 0.
809 ce107 1.18 wallClockTime = SECONDR()
810 cnh 1.23 # else
811     # ifdef HAVE_ETIME
812     actual = etime(tarray)
813     userTime = tarray(1)
814     systemTime = tarray(2)
815     # else
816     userTime = cusertime()
817     systemTime = csystemtime()
818     # endif
819     # if defined HAVE_CLOC
820     CALL cloc(wTime)
821     wallClockTime = wtime
822     # elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))
823     wallClockTime = MPI_Wtime()
824     # else
825     wallClockTime = timenow()
826     # endif
827     # endif
828 cnh 1.17 #endif
829 edhill 1.19
830 adcroft 1.1 RETURN
831     END
832 cnh 1.23
833    
834    
835 adcroft 1.1
836 cnh 1.10 CBOP
837    
838     C !ROUTINE: TIMER_PRINTALL
839    
840     C !INTERFACE:
841 adcroft 1.1 SUBROUTINE TIMER_PRINTALL( myThreadId )
842 adcroft 1.5 IMPLICIT NONE
843 cnh 1.10
844     C !DESCRIPTION:
845     C *==========================================================*
846 edhill 1.16 C | SUBROUTINE TIMER\_PRINTALL
847 cnh 1.10 C | o Print timer information
848     C *==========================================================*
849     C | Request print out of table of timing from all timers.
850     C *==========================================================*
851    
852     C !INPUT PARAMETERS:
853     C myThreadId :: This threads number
854 adcroft 1.1 INTEGER myThreadId
855 cnh 1.10 CEOP
856    
857 cnh 1.4 CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,
858     & myThreadId )
859 adcroft 1.1 C
860     RETURN
861     END
862 cnh 1.10
863     CBOP
864     C !ROUTINE: TIMER_START
865    
866     C !INTERFACE:
867 adcroft 1.1 SUBROUTINE TIMER_START ( string , myThreadId )
868 adcroft 1.5 IMPLICIT NONE
869 cnh 1.10
870     C !DESCRIPTION:
871     C Start timer named "string".
872    
873     C !INPUT PARAMETERS:
874     C string :: Name of timer
875     C myThreadId :: My thread number
876 adcroft 1.1 CHARACTER*(*) string
877     INTEGER myThreadId
878 cnh 1.10 CEOP
879 adcroft 1.1 C
880     CALL TIMER_CONTROL( string, 'START', 'TIMER_START' , myThreadId)
881     C
882     RETURN
883     END
884 cnh 1.10 CBOP
885     C !ROUTINE: TIMER_STOP
886    
887     C !INTERFACE:
888 ce107 1.20 SUBROUTINE TIMER_STOP ( string , myThreadId )
889 adcroft 1.5 IMPLICIT NONE
890 cnh 1.10
891     C !DESCRIPTION:
892     C Stop timer named "string".
893    
894     C !INPUT PARAMETERS:
895     C string :: Name of timer
896     C myThreadId :: My thread number
897 adcroft 1.1 CHARACTER*(*) string
898     INTEGER myThreadId
899 cnh 1.10 CEOP
900 adcroft 1.1 C
901     CALL TIMER_CONTROL( string, 'STOP', 'TIMER_STOP' , myThreadId )
902     C
903     RETURN
904     END
905     C***********************************************************************
906 ce107 1.20
907     #ifdef USE_PAPI
908     CCE107 Initialization of common block for PAPI timers
909     BLOCK DATA setpapivalues
910     #include "EEPARAMS.h"
911     INTEGER maxTimers
912 molod 1.26 PARAMETER (maxTimers = 50)
913 ce107 1.20 INTEGER nmaxevents
914     PARAMETER (nmaxevents = 18)
915     INTEGER size
916     PARAMETER (size = 3*nmaxevents*maxTimers*MAX_NO_THREADS)
917     INTEGER*8 values(nmaxevents, maxTimers , MAX_NO_THREADS),
918     $ values1(nmaxevents, maxTimers, MAX_NO_THREADS),
919     $ values2(nmaxevents, maxTimers, MAX_NO_THREADS)
920     COMMON /papivalues/ values, values1, values2
921     DATA values, values1, values2 /size*0/
922     END
923     #endif
924 ce107 1.21 #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
925     CCE107 Initialization of common block for PCL event names
926     BLOCK DATA setpclnames
927     INTEGER nmaxevents
928     PARAMETER (nmaxevents = 61)
929     CHARACTER*22 pcl_counter_name(0:nmaxevents-1)
930     COMMON /pclnames/ pcl_counter_name
931     DATA pcl_counter_name(0) /'PCL_L1CACHE_READ'/
932     DATA pcl_counter_name(1) /'PCL_L1CACHE_WRITE'/
933     DATA pcl_counter_name(2) /'PCL_L1CACHE_READWRITE'/
934     DATA pcl_counter_name(3) /'PCL_L1CACHE_HIT'/
935     DATA pcl_counter_name(4) /'PCL_L1CACHE_MISS'/
936     DATA pcl_counter_name(5) /'PCL_L1DCACHE_READ'/
937     DATA pcl_counter_name(6) /'PCL_L1DCACHE_WRITE'/
938     DATA pcl_counter_name(7) /'PCL_L1DCACHE_READWRITE'/
939     DATA pcl_counter_name(8) /'PCL_L1DCACHE_HIT'/
940     DATA pcl_counter_name(9) /'PCL_L1DCACHE_MISS'/
941     DATA pcl_counter_name(10) /'PCL_L1ICACHE_READ'/
942     DATA pcl_counter_name(11) /'PCL_L1ICACHE_WRITE'/
943     DATA pcl_counter_name(12) /'PCL_L1ICACHE_READWRITE'/
944     DATA pcl_counter_name(13) /'PCL_L1ICACHE_HIT'/
945     DATA pcl_counter_name(14) /'PCL_L1ICACHE_MISS'/
946     DATA pcl_counter_name(15) /'PCL_L2CACHE_READ'/
947     DATA pcl_counter_name(16) /'PCL_L2CACHE_WRITE'/
948     DATA pcl_counter_name(17) /'PCL_L2CACHE_READWRITE'/
949     DATA pcl_counter_name(18) /'PCL_L2CACHE_HIT'/
950     DATA pcl_counter_name(19) /'PCL_L2CACHE_MISS'/
951     DATA pcl_counter_name(20) /'PCL_L2DCACHE_READ'/
952     DATA pcl_counter_name(21) /'PCL_L2DCACHE_WRITE'/
953     DATA pcl_counter_name(22) /'PCL_L2DCACHE_READWRITE'/
954     DATA pcl_counter_name(23) /'PCL_L2DCACHE_HIT'/
955     DATA pcl_counter_name(24) /'PCL_L2DCACHE_MISS'/
956     DATA pcl_counter_name(25) /'PCL_L2ICACHE_READ'/
957     DATA pcl_counter_name(26) /'PCL_L2ICACHE_WRITE'/
958     DATA pcl_counter_name(27) /'PCL_L2ICACHE_READWRITE'/
959     DATA pcl_counter_name(28) /'PCL_L2ICACHE_HIT'/
960     DATA pcl_counter_name(29) /'PCL_L2ICACHE_MISS'/
961     DATA pcl_counter_name(30) /'PCL_TLB_HIT'/
962     DATA pcl_counter_name(31) /'PCL_TLB_MISS'/
963     DATA pcl_counter_name(32) /'PCL_ITLB_HIT'/
964     DATA pcl_counter_name(33) /'PCL_ITLB_MISS'/
965     DATA pcl_counter_name(34) /'PCL_DTLB_HIT'/
966     DATA pcl_counter_name(35) /'PCL_DTLB_MISS'/
967     DATA pcl_counter_name(36) /'PCL_CYCLES'/
968     DATA pcl_counter_name(37) /'PCL_ELAPSED_CYCLES'/
969     DATA pcl_counter_name(38) /'PCL_INTEGER_INSTR'/
970     DATA pcl_counter_name(39) /'PCL_FP_INSTR'/
971     DATA pcl_counter_name(40) /'PCL_LOAD_INSTR'/
972     DATA pcl_counter_name(41) /'PCL_STORE_INSTR'/
973     DATA pcl_counter_name(42) /'PCL_LOADSTORE_INSTR'/
974     DATA pcl_counter_name(43) /'PCL_INSTR'/
975     DATA pcl_counter_name(44) /'PCL_JUMP_SUCCESS'/
976     DATA pcl_counter_name(45) /'PCL_JUMP_UNSUCCESS'/
977     DATA pcl_counter_name(46) /'PCL_JUMP'/
978     DATA pcl_counter_name(47) /'PCL_ATOMIC_SUCCESS'/
979     DATA pcl_counter_name(48) /'PCL_ATOMIC_UNSUCCESS'/
980     DATA pcl_counter_name(49) /'PCL_ATOMIC'/
981     DATA pcl_counter_name(50) /'PCL_STALL_INTEGER'/
982     DATA pcl_counter_name(51) /'PCL_STALL_FP'/
983     DATA pcl_counter_name(52) /'PCL_STALL_JUMP'/
984     DATA pcl_counter_name(53) /'PCL_STALL_LOAD'/
985     DATA pcl_counter_name(54) /'PCL_STALL_STORE'/
986     DATA pcl_counter_name(55) /'PCL_STALL'/
987     DATA pcl_counter_name(56) /'PCL_MFLOPS'/
988     DATA pcl_counter_name(57) /'PCL_IPC'/
989     DATA pcl_counter_name(58) /'PCL_L1DCACHE_MISSRATE'/
990     DATA pcl_counter_name(59) /'PCL_L2DCACHE_MISSRATE'/
991     DATA pcl_counter_name(60) /'PCL_MEM_FP_RATIO'/
992     END
993    
994    
995     #ifdef USE_PCL
996     CCE107 Initialization of common block for PCL summary performance
997     BLOCK DATA setpcls
998     #include "EEPARAMS.h"
999     INTEGER maxTimers
1000 molod 1.26 PARAMETER (maxTimers = 50)
1001 ce107 1.21 INTEGER nmaxevents
1002     PARAMETER (nmaxevents = 61)
1003     INTEGER size
1004     PARAMETER (size = nmaxevents*maxTimers*MAX_NO_THREADS)
1005     INTEGER PCL_CYCLES, PCL_MODE_USER_SYSTEM
1006     PARAMETER (PCL_CYCLES=36, PCL_MODE_USER_SYSTEM=3)
1007     INTEGER pcl_counter_list(nmaxevents)
1008     INTEGER flags, nevents
1009     INTEGER*8 i_result(nmaxevents, maxTimers, MAX_NO_THREADS)
1010     INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)
1011     INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)
1012     INTEGER*8 descr
1013     REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)
1014     COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
1015     $ flags, nevents
1016     DATA fp_result /size*0.0D0/
1017     DATA i_result /size*0/
1018     DATA i_result1 /size*0/
1019     DATA i_result2 /size*0/
1020     DATA descr /0/
1021     DATA nevents /nmaxevents/
1022     DATA pcl_counter_list /nmaxevents*PCL_CYCLES/
1023     DATA flags /PCL_MODE_USER_SYSTEM/
1024     END
1025     #else
1026     CCE107 Initialization of common block for PCL summary performance
1027     BLOCK DATA setpcls
1028     INTEGER PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
1029     $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO
1030     PARAMETER (PCL_MFLOPS=56, PCL_IPC=57, PCL_L1DCACHE_MISSRATE=58,
1031     $ PCL_L2DCACHE_MISSRATE=59, PCL_MEM_FP_RATIO=60)
1032     INTEGER PCL_MODE_USER_SYSTEM
1033     PARAMETER (PCL_MODE_USER_SYSTEM=3)
1034     INTEGER pcl_counter_list(5), flags, nevents
1035     INTEGER*8 i_result(5), descr
1036     REAL*8 fp_result(5)
1037     COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
1038     $ flags, nevents
1039     DATA fp_result /5*0.0D0/
1040     DATA i_result /5*0/
1041     DATA descr /0/
1042     DATA nevents /0/
1043     DATA pcl_counter_list /PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
1044     $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO/
1045     DATA flags /PCL_MODE_USER_SYSTEM/
1046     END
1047     #endif
1048     #endif

  ViewVC Help
Powered by ViewVC 1.1.22