File indexing completed on 2018-03-02 18:36:14 UTC
view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
1511bdc7b0 Alis*0001 #include "CPP_EEOPTIONS.h"
c23f4a1c98 Cons*0002 #ifdef USE_LIBHPM
0003 # include "f_hpm.h"
0004 #endif
1511bdc7b0 Alis*0005
0006
0007
0008
0009
0010
0011
0012
0013
0014
0015
0016
ff43152480 Patr*0017
0018
0019
0f82b218cd Jean*0020
4c563c2ee9 Chri*0021
0022
0023
0024
0f82b218cd Jean*0025 INTEGER FUNCTION TIMER_INDEX (
1511bdc7b0 Alis*0026 I name,timerNames,maxTimers,nTimers )
18e2723366 Alis*0027 IMPLICIT NONE
4c563c2ee9 Chri*0028
0029
0030
0f82b218cd Jean*0031
0032
4c563c2ee9 Chri*0033
0f82b218cd Jean*0034
0035
4c563c2ee9 Chri*0036
0037
0038
0039
0040
0041
0042
0043
1511bdc7b0 Alis*0044 INTEGER maxTimers
0045 INTEGER nTimers
0046 CHARACTER*(*) name
0047 CHARACTER*(*) timerNames(maxTimers)
4c563c2ee9 Chri*0048
0049
0050
0051
1511bdc7b0 Alis*0052 INTEGER I
4c563c2ee9 Chri*0053
1511bdc7b0 Alis*0054
0055 TIMER_INDEX = 0
0056 IF ( name .EQ. ' ' ) THEN
0057 TIMER_INDEX = -1
0058 ELSE
0059 DO 10 I = 1, nTimers
0060 IF ( name .NE. timerNames(I) ) GOTO 10
0061 TIMER_INDEX = I
0062 GOTO 11
0063 10 CONTINUE
0064 11 CONTINUE
0065 ENDIF
0066 RETURN
0067 END
0068
0f82b218cd Jean*0069
4c563c2ee9 Chri*0070
0071
0072
0073
1511bdc7b0 Alis*0074 SUBROUTINE TIMER_CONTROL ( name , action , callProc , myThreadId )
4c563c2ee9 Chri*0075 IMPLICIT NONE
0076
0077
0078
2b4c849245 Ed H*0079
1511bdc7b0 Alis*0080
4c563c2ee9 Chri*0081
1511bdc7b0 Alis*0082
0083
0084
4c563c2ee9 Chri*0085
0086
0087
1511bdc7b0 Alis*0088 #include "SIZE.h"
0089 #include "EEPARAMS.h"
0090 #include "EESUPPORT.h"
0091 INTEGER TIMER_INDEX
0092 INTEGER IFNBLNK
0093 INTEGER ILNBLNK
0094 EXTERNAL TIMER_INDEX
0095 EXTERNAL IFNBLNK
0096 EXTERNAL ILNBLNK
4c563c2ee9 Chri*0097
0098
0099
0100
0101
0102
0103 CHARACTER*(*) name
0104 CHARACTER*(*) action
0105 CHARACTER*(*) callProc
0106 INTEGER myThreadId
1511bdc7b0 Alis*0107
4c563c2ee9 Chri*0108
0109
0110
1511bdc7b0 Alis*0111 INTEGER maxTimers
0112 INTEGER maxString
fbb427d468 Andr*0113 PARAMETER ( maxTimers = 50 )
1511bdc7b0 Alis*0114 PARAMETER ( maxString = 80 )
4c563c2ee9 Chri*0115
0f82b218cd Jean*0116
4c563c2ee9 Chri*0117
0118
0119
0120
0121
0f82b218cd Jean*0122
4c563c2ee9 Chri*0123
0124
0125
0126
1511bdc7b0 Alis*0127 INTEGER timerStarts( maxTimers , MAX_NO_THREADS)
0128 SAVE timerStarts
0129 INTEGER timerStops ( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0130 SAVE timerStops
1511bdc7b0 Alis*0131 Real*8 timerUser ( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0132 SAVE timerUser
1511bdc7b0 Alis*0133 Real*8 timerWall ( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0134 SAVE timerWall
1511bdc7b0 Alis*0135 Real*8 timerSys ( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0136 SAVE timerSys
1511bdc7b0 Alis*0137 Real*8 timerT0User( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0138 SAVE timerT0User
1511bdc7b0 Alis*0139 Real*8 timerT0Wall( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0140 SAVE timerT0Wall
1511bdc7b0 Alis*0141 Real*8 timerT0Sys ( maxTimers , MAX_NO_THREADS)
0f82b218cd Jean*0142 SAVE timerT0Sys
1511bdc7b0 Alis*0143 INTEGER timerStatus( maxTimers , MAX_NO_THREADS)
0144 SAVE timerStatus
0145 INTEGER timerNameLen( maxTimers , MAX_NO_THREADS)
0146 SAVE timerNameLen
0147 CHARACTER*(maxString) timerNames( maxTimers , MAX_NO_THREADS)
0148 SAVE timerNames
0149 INTEGER nTimers(MAX_NO_THREADS)
0150 CHARACTER*(maxString) tmpName
0151 CHARACTER*(maxString) tmpAction
0152 INTEGER iTimer
0153 INTEGER ISTART
0154 INTEGER IEND
0155 INTEGER STOPPED
0156 PARAMETER ( STOPPED = 0 )
0157 INTEGER RUNNING
0158 PARAMETER ( RUNNING = 1 )
0159 CHARACTER*(*) STOP
0160 PARAMETER ( STOP = 'STOP' )
0161 CHARACTER*(*) START
0162 PARAMETER ( START = 'START' )
0163 CHARACTER*(*) PRINT
0164 PARAMETER ( PRINT = 'PRINT' )
0165 CHARACTER*(*) PRINTALL
0166 PARAMETER ( PRINTALL = 'PRINTALL' )
008ba3ca0d Cons*0167 #if defined(USE_PAPI) || defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined (USE_PCL)
c23f4a1c98 Cons*0168 CHARACTER*(*) INIT
0169 PARAMETER ( INIT = 'INIT' )
008ba3ca0d Cons*0170 #ifdef USE_PAPI
c23f4a1c98 Cons*0171 INTEGER nmaxevents
0172 PARAMETER (nmaxevents = 18)
008ba3ca0d Cons*0173 INTEGER neventsmax, nevents
0174 SAVE neventsmax, nevents
c23f4a1c98 Cons*0175 INTEGER*8 values(nmaxevents, maxTimers , MAX_NO_THREADS),
0176 $ values1(nmaxevents, maxTimers, MAX_NO_THREADS),
0177 $ values2(nmaxevents, maxTimers, MAX_NO_THREADS)
0178 COMMON /papivalues/ values, values1, values2
008ba3ca0d Cons*0179 #include <fpapi.h>
0180 CHARACTER(13) EventName
0181 INTEGER EventCode(nmaxevents)
0182 INTEGER Check, EventSet
c23f4a1c98 Cons*0183 INTEGER papiunit
008ba3ca0d Cons*0184 SAVE EventCode, EventSet
0f82b218cd Jean*0185 INTEGER j
008ba3ca0d Cons*0186 #else
0187 #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
0188 #include <pclh.f>
0189 INTEGER nmaxevents
0190 PARAMETER (nmaxevents = 61)
0191 INTEGER flags, res, nevents
0192 INTEGER*8 descr
0193 CHARACTER*22 pcl_counter_name(0:nmaxevents-1)
0194 #ifdef USE_PCL
0195 INTEGER pcl_counter_list(nmaxevents)
0196 INTEGER*8 i_result(nmaxevents, maxTimers, MAX_NO_THREADS)
0197 INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)
0198 INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)
0199 REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)
0f82b218cd Jean*0200 INTEGER j
008ba3ca0d Cons*0201 #else
0202 INTEGER pcl_counter_list(5), alt_counter_list(5)
0203 INTEGER*8 i_result(5)
0204 REAL*8 fp_result(5)
0205 SAVE alt_counter_list
0206 DATA alt_counter_list /PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
0207 $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO/
0208 #endif
0209 COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
0210 $ flags, nevents
0211 COMMON /pclnames/ pcl_counter_name
0212 INTEGER pclunit
0213 #endif
0214 #endif
c23f4a1c98 Cons*0215 #endif
0f82b218cd Jean*0216 INTEGER I
1511bdc7b0 Alis*0217 Real*8 userTime
0218 Real*8 systemTime
0219 Real*8 wallClockTime
0220 CHARACTER*(MAX_LEN_MBUF) msgBuffer
0221 DATA nTimers /MAX_NO_THREADS*0/
0222 SAVE nTimers
4c563c2ee9 Chri*0223
1511bdc7b0 Alis*0224
0225 ISTART = IFNBLNK(name)
0226 IEND = ILNBLNK(name)
0227 IF ( IEND - ISTART + 1 .GT. maxString ) GOTO 901
0228 IF ( ISTART .NE. 0 ) THEN
0229 tmpName = name(ISTART:IEND)
0230 CALL UCASE( tmpName )
0231 ELSE
0232 tmpName = ' '
0233 ENDIF
0234 ISTART = IFNBLNK(action)
0235 IEND = ILNBLNK(action)
0236 IF ( ISTART .EQ. 0 ) GOTO 902
0237 IF ( IEND - ISTART + 1 .GT. maxString ) GOTO 903
0238 tmpAction = action(ISTART:IEND)
0239 CALL UCASE( tmpAction )
0240
46dc4f419b Chri*0241 iTimer=TIMER_INDEX(tmpName,timerNames(1,myThreadId),
0242 & maxTimers,nTimers(myThreadId))
1511bdc7b0 Alis*0243
0244 IF ( tmpAction .EQ. START ) THEN
0245 IF ( iTimer .EQ. 0 ) THEN
0246 IF ( nTimers(myThreadId) .EQ. maxTimers ) GOTO 904
0247 nTimers(myThreadId) = nTimers(myThreadId) + 1
0248 iTimer = nTimers(myThreadId)
0249 timerNames(iTimer,myThreadId) = tmpName
0f82b218cd Jean*0250 timerNameLen(iTimer,myThreadId) =
46dc4f419b Chri*0251 & ILNBLNK(tmpName)-IFNBLNK(tmpName)+1
1511bdc7b0 Alis*0252 timerUser(iTimer,myThreadId) = 0.
0253 timerSys (iTimer,myThreadId) = 0.
0254 timerWall(iTimer,myThreadId) = 0.
0255 timerStarts(iTimer,myThreadId) = 0
0256 timerStops (iTimer,myThreadId) = 0
0257 timerStatus(iTimer,myThreadId) = STOPPED
0258 ENDIF
0259 IF ( timerStatus(iTimer,myThreadId) .NE. RUNNING ) THEN
0260 CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )
0261 timerT0User(iTimer,myThreadId) = userTime
0262 timerT0Sys(iTimer,myThreadId) = systemTime
0263 timerT0Wall(iTimer,myThreadId) = wallClockTime
0264 timerStatus(iTimer,myThreadId) = RUNNING
0f82b218cd Jean*0265 timerStarts(iTimer,myThreadId) =
46dc4f419b Chri*0266 & timerStarts(iTimer,myThreadId)+1
c23f4a1c98 Cons*0267 #ifdef USE_PAPI
008ba3ca0d Cons*0268
c23f4a1c98 Cons*0269 call PAPIF_read(EventSet, values1(1,iTimer,myThreadId), Check)
008ba3ca0d Cons*0270 #else
0271 #ifdef USE_PCL
0272
0273 res = PCLread(descr, i_result1(1,iTimer,myThreadId),
0274 $ fp_result(1,iTimer,myThreadId), nevents)
0275 #endif
c23f4a1c98 Cons*0276 #endif
1511bdc7b0 Alis*0277 ENDIF
c23f4a1c98 Cons*0278 #ifdef USE_LIBHPM
5ecfcdf53f Cons*0279 #ifdef TARGET_BGL
0280 CALL f_hpmstart((myThreadId-1)*100+iTimer,tmpName)
0281 #else
c23f4a1c98 Cons*0282 CALL f_hpmtstart((myThreadId-1)*100+iTimer,tmpName)
0283 #endif
5ecfcdf53f Cons*0284 #endif
1511bdc7b0 Alis*0285 ELSEIF ( tmpAction .EQ. STOP ) THEN
0286 IF ( iTimer .EQ. 0 ) GOTO 905
c23f4a1c98 Cons*0287 #ifdef USE_LIBHPM
5ecfcdf53f Cons*0288 #ifdef TARGET_BGL
0289 CALL f_hpmstop((myThreadId-1)*100+iTimer)
0290 #else
c23f4a1c98 Cons*0291 CALL f_hpmtstop((myThreadId-1)*100+iTimer)
0292 #endif
5ecfcdf53f Cons*0293 #endif
1511bdc7b0 Alis*0294 IF ( timerStatus(iTimer,myThreadId) .EQ. RUNNING ) THEN
c23f4a1c98 Cons*0295 #ifdef USE_PAPI
0296
0297 call PAPIF_read(EventSet, values2(1,iTimer,myThreadId), Check)
008ba3ca0d Cons*0298 #else
0299 #ifdef USE_PCL
0300
0301 res = PCLread(descr, i_result2(1,iTimer,myThreadId),
0302 $ fp_result(1,iTimer,myThreadId), nevents)
0303 #endif
c23f4a1c98 Cons*0304 #endif
1511bdc7b0 Alis*0305 CALL TIMER_GET_TIME( userTime, systemTime, wallClockTime )
0f82b218cd Jean*0306 timerUser(iTimer,myThreadId) =
0307 & timerUser(iTimer,myThreadId) +
1511bdc7b0 Alis*0308 & userTime -
0309 & timerT0User(iTimer,myThreadId)
0f82b218cd Jean*0310 timerSys (iTimer,myThreadId) =
0311 & timerSys(iTimer,myThreadId) +
1511bdc7b0 Alis*0312 & systemTime -
0313 & timerT0Sys(iTimer,myThreadId)
0f82b218cd Jean*0314 timerWall(iTimer,myThreadId) =
0315 & timerWall(iTimer,myThreadId) +
1511bdc7b0 Alis*0316 & wallClockTime -
0317 & timerT0Wall(iTimer,myThreadId)
c23f4a1c98 Cons*0318 #ifdef USE_PAPI
0319 do i=1,nevents
0320 values(i,iTimer,myThreadId) = values(i,iTimer,myThreadId) +
0321 $ values2(i,iTimer,myThreadId) - values1(i,iTimer,myThreadId)
0322 enddo
008ba3ca0d Cons*0323 #else
0324 #ifdef USE_PCL
0325 do i=1,nevents
0326 i_result(i,iTimer,myThreadId) = i_result(i,iTimer
0327 $ ,myThreadId) + i_result2(i,iTimer,myThreadId) -
0328 $ i_result1(i,iTimer,myThreadId)
0329 enddo
0330 #endif
c23f4a1c98 Cons*0331 #endif
1511bdc7b0 Alis*0332 timerStatus(iTimer,myThreadId) = STOPPED
0f82b218cd Jean*0333 timerStops (iTimer,myThreadId) =
46dc4f419b Chri*0334 & timerStops (iTimer,myThreadId)+1
1511bdc7b0 Alis*0335 ENDIF
008ba3ca0d Cons*0336 #if defined (USE_PAPI) || defined (USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
c23f4a1c98 Cons*0337 ELSEIF ( tmpAction .EQ. INIT ) THEN
008ba3ca0d Cons*0338 #ifdef USE_PAPI
0f82b218cd Jean*0339
0340
c23f4a1c98 Cons*0341
0342 Check = PAPI_VER_CURRENT
0343 call PAPIF_library_init(Check)
0344 if (Check .NE. PAPI_VER_CURRENT) then
0345 WRITE(msgBuffer,*) "PAPI Library Version is out of Date"
0346 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0347 & SQUEEZE_RIGHT,myThreadId)
0348 CALL ABORT
0349 endif
008ba3ca0d Cons*0350 call PAPIF_num_counters(neventsmax)
c23f4a1c98 Cons*0351 if (neventsmax .GT. nmaxevents) then
0352 WRITE(msgBuffer,*) "Fix the nmaxevents in the code to ",
0f82b218cd Jean*0353 $ neventsmax
c23f4a1c98 Cons*0354 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0355 & SQUEEZE_RIGHT,myThreadId)
0356 CALL ABORT
0357 endif
0358 _BEGIN_MASTER(myThreadId)
0359 CALL mdsFindUnit (papiunit, myThreadId)
0360 OPEN(UNIT=papiunit,FILE='data.papi',STATUS='OLD')
0361 read(papiunit,*) nevents
0362
0363 if (nevents .gt. neventsmax) then
0364 nevents = neventsmax
0365 WRITE(msgBuffer,*)
0f82b218cd Jean*0366 $ "resetting the number of PAPI events to the maximum"
c23f4a1c98 Cons*0367 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
008ba3ca0d Cons*0368 & SQUEEZE_RIGHT,myThreadId)
c23f4a1c98 Cons*0369 endif
0370 do i = 1,nevents
008ba3ca0d Cons*0371 read(papiunit,*) EventName
0372 if ((EventName .eq. 'PAPI_FLOPS') .or.
0373 $ (EventName .eq. 'PAPI_IPS')) then
0374 WRITE(msgBuffer,*) "Abort
0375 $ ,EventName
0376 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0377 & SQUEEZE_RIGHT,myThreadId)
0378 CALL ABORT
0379 endif
0380
0381 call PAPIF_event_name_to_code(EventName, EventCode(i), Check)
c23f4a1c98 Cons*0382 end do
0383 close(papiunit)
0384 _END_MASTER(myThid)
0385 EventSet = PAPI_NULL
0386 call PAPIF_create_eventset(EventSet, Check)
0387 do i = 1,nevents
0388 call PAPIF_add_event(EventSet, EventCode(i), Check)
0389 if (Check .NE. PAPI_OK) then
0390 CALL PAPIF_event_code_to_name(EventCode(i), EventName,
0391 $ Check)
0392 WRITE(msgBuffer,*) "Abort After PAPIF_add_event: ",
0393 $ EventName
0394 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0395 & SQUEEZE_RIGHT,myThreadId)
0396 CALL ABORT
0397 endif
0398 enddo
0399
0400 call PAPIF_start(EventSet, Check)
008ba3ca0d Cons*0401 #else
0402 #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
0403
0404
0405 res = PCLinit(descr)
0406
0407 #ifdef USE_PCL
0408 _BEGIN_MASTER(myThreadId)
0409 CALL mdsFindUnit (pclunit, myThreadId)
0410 OPEN(UNIT=pclunit,FILE='data.pcl',STATUS='OLD')
0411 read(pclunit,*) nevents
0412
0413 if (nevents .gt. nmaxevents) then
0414 nevents = nmaxevents
0415 WRITE(msgBuffer,*)
0f82b218cd Jean*0416 $ "resetting the number of PCL events to the maximum"
008ba3ca0d Cons*0417 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0418 & SQUEEZE_RIGHT,myThreadId)
0419 endif
0420 do i = 1,nevents
0421 read(pclunit,*) pcl_counter_list(i)
0422 if ((pcl_counter_list(i) .ge. PCL_MFLOPS) .or.
0423 $ (pcl_counter_list(i) .lt. 1)) then
0424 if ((pcl_counter_list(i) .ge. PCL_MFLOPS) .and.
0425 $ (pcl_counter_list(i) .le. nmaxevents)) then
0426 WRITE(msgBuffer,*)
0427 $ "Abort
0428 $ pcl_counter_name(pcl_counter_list(i))
0429 else
0430 WRITE(msgBuffer,*)
0431 $ "Abort
0432 $ pcl_counter_list(i)
0433 endif
0434 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0435 & SQUEEZE_RIGHT,myThreadId)
0436 CALL ABORT
0437 endif
0438 enddo
0439 close(pclunit)
0440 _END_MASTER(myThid)
0441
0442 do i = 1,nevents
0443
0444 res = PCLquery(descr, pcl_counter_list, i, flags)
0445 IF(res .NE. PCL_SUCCESS) THEN
0446 WRITE(msgBuffer,*) "Abort
0447 $ , pcl_counter_name(pcl_counter_list(i))
0448 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0449 & SQUEEZE_RIGHT,myThreadId)
0450 CALL ABORT
0451 endif
0452 enddo
0453 #else
0454 do i = 1,5
0455
0456 res = PCLquery(descr, pcl_counter_list, nevents+1, flags)
0457 if ((res .ne. PCL_SUCCESS) .and. (i .lt. 5)) then
0458 pcl_counter_list(nevents+1) = alt_counter_list(i+1)
0459 else
0460 if (i .lt. 5) then
0461 nevents = nevents + 1
0462 endif
0463 endif
0464 enddo
0465 if (nevents .eq. 0) then
0466 WRITE(msgBuffer,*)
0467 $ "No PCL rate events supported: Please recompile
0468 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0469 & SQUEEZE_RIGHT,myThreadId)
0470 CALL ABORT
0471 endif
0472 #endif
0473
0474
0475 res = PCLstart(descr, pcl_counter_list, nevents, flags)
0476 IF(res .NE. PCL_SUCCESS) THEN
0477 WRITE(msgBuffer,*) "PCL counting failed - please recompile
0478 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
0479 & SQUEEZE_RIGHT,myThreadId)
0480 CALL ABORT
0481 ENDIF
0482 #endif
0483 #endif
c23f4a1c98 Cons*0484 #endif
1511bdc7b0 Alis*0485 ELSEIF ( tmpAction .EQ. PRINT ) THEN
0486 IF ( iTimer .EQ. 0 ) GOTO 905
0487 WRITE(msgBuffer,*)
0488 & ' Seconds in section "',
46dc4f419b Chri*0489 & timerNames(iTimer,myThreadId)(1:timerNameLen(iTimer,myThreadId))
0490 & ,'":'
0491 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0492 & SQUEEZE_RIGHT,myThreadId)
0493 WRITE(msgBuffer,*) ' User time:',
0494 & timerUser(iTimer,myThreadId)
0495 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0496 & SQUEEZE_RIGHT,myThreadId)
0497 WRITE(msgBuffer,*) ' System time:',
0498 & timerSys(iTimer,myThreadId)
0499 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0500 & SQUEEZE_RIGHT,myThreadId)
0501 WRITE(msgBuffer,*) ' Wall clock time:',
0502 & timerWall(iTimer,myThreadId)
0503 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0504 & SQUEEZE_RIGHT,myThreadId)
0505 WRITE(msgBuffer,*) ' No. starts:',
0506 & timerStarts(iTimer,myThreadId)
0507 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0508 & SQUEEZE_RIGHT,myThreadId)
0509 WRITE(msgBuffer,*) ' No. stops:',
0510 & timerStops(iTimer,myThreadId)
0511 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0512 & SQUEEZE_RIGHT,myThreadId)
c23f4a1c98 Cons*0513 #ifdef USE_PAPI
0514 do i = 1,nevents
0515 call PAPIF_event_code_to_name(EventCode(i), EventName, Check)
008ba3ca0d Cons*0516 WRITE(msgBuffer,71) Eventname,
0517 $ values(i,iTimer,myThreadId)/timerUser(iTimer,myThreadId)
0518 $ ,values(i,iTimer,myThreadId)/timerWall(iTimer,myThreadId
0519 $ ),1.D0*values(i,iTimer,myThreadId)
0520 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0521 & SQUEEZE_RIGHT,myThreadId)
0522 enddo
0523 #else
0524 #ifdef USE_PCL
0525 do i = 1,nevents
0526 WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(i)),
0527 $ i_result(i,iTimer,myThreadId)/timerUser(iTimer
0528 $ ,myThreadId),i_result(i,iTimer,myThreadId)
0529 $ /timerWall(iTimer,myThreadId),1.D0*i_result(i,iTimer
0530 $ ,myThreadId)
c23f4a1c98 Cons*0531 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0532 & SQUEEZE_RIGHT,myThreadId)
0533 enddo
0534 #endif
008ba3ca0d Cons*0535 #endif
1511bdc7b0 Alis*0536 ELSEIF ( tmpAction .EQ. PRINTALL ) THEN
0537 DO 10 I = 1, nTimers(myThreadId)
0538 WRITE(msgBuffer,*) ' Seconds in section "',
46dc4f419b Chri*0539 & timerNames(I,myThreadId)(1:timerNameLen(I,myThreadId))
0540 & ,'":'
0541 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0542 & SQUEEZE_RIGHT,myThreadId)
0543 WRITE(msgBuffer,*) ' User time:',
0544 & timerUser(I,myThreadId)
0545 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0546 & SQUEEZE_RIGHT,myThreadId)
0547 WRITE(msgBuffer,*) ' System time:',
0548 & timerSys(I,myThreadId)
0549 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0550 & SQUEEZE_RIGHT,myThreadId)
0551 WRITE(msgBuffer,*) ' Wall clock time:',
0552 & timerWall(I,myThreadId)
0553 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0554 & SQUEEZE_RIGHT,myThreadId)
0555 WRITE(msgBuffer,*) ' No. starts:',
0556 & timerStarts(I,myThreadId)
0557 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0558 & SQUEEZE_RIGHT,myThreadId)
0559 WRITE(msgBuffer,*) ' No. stops:',
0560 & timerStops(I,myThreadId)
0561 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0562 & SQUEEZE_RIGHT,myThreadId)
c23f4a1c98 Cons*0563 #ifdef USE_PAPI
0564 do j = 1,nevents
0565 call PAPIF_event_code_to_name(EventCode(j), EventName, Check)
008ba3ca0d Cons*0566 WRITE(msgBuffer,71) Eventname,
0567 $ values(j,I,myThreadId)/timerUser(I,myThreadId),
0568 $ values(j,I,myThreadId)/timerWall(I,myThreadId),
0f82b218cd Jean*0569 $ 1.D0*values(j,I,myThreadId)
008ba3ca0d Cons*0570 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0571 & SQUEEZE_RIGHT,myThreadId)
0572 enddo
0573 #else
0574 #ifdef USE_PCL
0575 do j = 1,nevents
0576 WRITE(msgBuffer,71) pcl_counter_name(pcl_counter_list(j)),
0577 $ i_result(j,I,myThreadId)/timerUser(I,myThreadId)
0578 $ ,i_result(j,I,myThreadId)/timerWall(I,myThreadId),1.D0
0f82b218cd Jean*0579 $ *i_result(j,I,myThreadId)
c23f4a1c98 Cons*0580 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
0581 & SQUEEZE_RIGHT,myThreadId)
0582 enddo
0583 #endif
008ba3ca0d Cons*0584 #endif
1511bdc7b0 Alis*0585 10 CONTINUE
0586 ELSE
0587 GOTO 903
0588 ENDIF
0589
0590 1000 CONTINUE
0591
0592 RETURN
0593 901 CONTINUE
0594 WRITE(msgBuffer,'(A)')
0595 &' '
68a9a7a26d Jean*0596 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0597 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0598 WRITE(msgBuffer,*)
0599 &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
68a9a7a26d Jean*0600 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0601 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0602 WRITE(msgBuffer,*)
0603 &'procedure: "',callProc,'".'
68a9a7a26d Jean*0604 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0605 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0606 WRITE(msgBuffer,*)
0607 &'Timer name "',name(ISTART:IEND),'" is invalid.'
68a9a7a26d Jean*0608 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0609 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0610 WRITE(msgBuffer,*)
0611 &' Names must have fewer than',maxString+1,' characters.'
68a9a7a26d Jean*0612 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0613 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0614 WRITE(msgBuffer,*)
0615 &'*******************************************************'
68a9a7a26d Jean*0616 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0617 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0618 GOTO 1000
0619 902 CONTINUE
0620 WRITE(msgBuffer,*)
0621 &' '
68a9a7a26d Jean*0622 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0623 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0624 WRITE(msgBuffer,*)
0625 &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
68a9a7a26d Jean*0626 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0627 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0628 WRITE(msgBuffer,*)
0629 &'procedure: "',callProc,'".'
68a9a7a26d Jean*0630 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0631 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0632 WRITE(msgBuffer,*)
0633 &' No timer action specified.'
68a9a7a26d Jean*0634 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0635 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0636 WRITE(msgBuffer,*)
0637 &' Valid actions are:'
68a9a7a26d Jean*0638 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0639 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0640 WRITE(msgBuffer,*)
0641 &' "START", "STOP", "PRINT" and "PRINTALL".'
68a9a7a26d Jean*0642 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0643 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0644 WRITE(msgBuffer,*)
0645 &'*******************************************************'
68a9a7a26d Jean*0646 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0647 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0648 GOTO 1000
0649 903 CONTINUE
0650 WRITE(msgBuffer,*)
0651 &' '
68a9a7a26d Jean*0652 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0653 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0654 WRITE(msgBuffer,*)
0655 &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
68a9a7a26d Jean*0656 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0657 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0658 WRITE(msgBuffer,*)
0659 &'procedure: "',callProc,'".'
68a9a7a26d Jean*0660 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0661 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0662 WRITE(msgBuffer,*)
0663 &'Timer action"',name(ISTART:IEND),'" is invalid.'
68a9a7a26d Jean*0664 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0665 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0666 WRITE(msgBuffer,*)
0667 &' Valid actions are:'
68a9a7a26d Jean*0668 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0669 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0670 WRITE(msgBuffer,*)
0671 &' "START", "STOP", "PRINT" and "PRINTALL".'
68a9a7a26d Jean*0672 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0673 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0674 WRITE(msgBuffer,*)
0675 &'*******************************************************'
68a9a7a26d Jean*0676 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0677 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0678 GOTO 1000
0679 904 CONTINUE
0680 WRITE(msgBuffer,*)
0681 &' '
68a9a7a26d Jean*0682 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0683 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0684 WRITE(msgBuffer,*)
0685 &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
68a9a7a26d Jean*0686 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0687 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0688 WRITE(msgBuffer,*)
0689 &'procedure: "',callProc,'".'
68a9a7a26d Jean*0690 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0691 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0692 WRITE(msgBuffer,*)
0693 &'Timer "',name(ISTART:IEND),'" cannot be created.'
68a9a7a26d Jean*0694 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0695 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0696 WRITE(msgBuffer,*)
0697 &' Only ',maxTimers,' timers are allowed.'
68a9a7a26d Jean*0698 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0699 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0700 WRITE(msgBuffer,*)
0701 &'*******************************************************'
68a9a7a26d Jean*0702 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0703 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0704 GOTO 1000
0705 905 CONTINUE
0706 WRITE(msgBuffer,*)
0707 &' '
68a9a7a26d Jean*0708 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0709 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0710 WRITE(msgBuffer,*)
0711 &'*** WARNING WARNING WARNING WARNING WARNING WARNING ***'
68a9a7a26d Jean*0712 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0713 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0714 WRITE(msgBuffer,*)
0715 &'procedure: "',callProc,'".'
68a9a7a26d Jean*0716 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0717 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0718 WRITE(msgBuffer,*)
0719 &'Timer name is blank.'
68a9a7a26d Jean*0720 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0721 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0722 WRITE(msgBuffer,*)
0723 &' A name must be used with "START", "STOP" or "PRINT".'
68a9a7a26d Jean*0724 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0725 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0726 WRITE(msgBuffer,*)
0727 &'*******************************************************'
68a9a7a26d Jean*0728 CALL PRINT_MESSAGE(msgBuffer,errorMessageUnit,
46dc4f419b Chri*0729 & SQUEEZE_RIGHT,myThreadId)
1511bdc7b0 Alis*0730 GOTO 1000
c23f4a1c98 Cons*0731
ec7b4bf650 Jean*0732 #if (defined USE_PAPI) || (defined USE_PCL)
c23f4a1c98 Cons*0733 71 FORMAT(A,' per sec ',D13.7,' ',D13.7,', number ', D13.7)
ec7b4bf650 Jean*0734 #endif
0735
1511bdc7b0 Alis*0736 END
0737
0f82b218cd Jean*0738
4c563c2ee9 Chri*0739
0740
0741
0742
0f82b218cd Jean*0743 SUBROUTINE TIMER_GET_TIME(
0744 O userTime,
0745 O systemTime,
1511bdc7b0 Alis*0746 O wallClockTime )
18e2723366 Alis*0747 IMPLICIT NONE
4c563c2ee9 Chri*0748
0749
0750
0f82b218cd Jean*0751
0752
4c563c2ee9 Chri*0753
0f82b218cd Jean*0754
0755
0756
0757
4c563c2ee9 Chri*0758
0759
0760
0761
0762
0763
0584962966 Chri*0764
1511bdc7b0 Alis*0765 Real*8 userTime
0766 Real*8 systemTime
0767 Real*8 wallClockTime
4c563c2ee9 Chri*0768
0584962966 Chri*0769
0770
0771
0772 #ifdef IGNORE_TIME
0773
0774 userTime = 0.
0775 systemTime = 0.
0776 wallClockTime = 0.
0777
50b31ef7a3 Cons*0778 #else
4c563c2ee9 Chri*0779
0584962966 Chri*0780
0781
0782
5ecfcdf53f Cons*0783 # if defined (TARGET_AIX) || defined (TARGET_BGL)
0584962966 Chri*0784 Real*4 etime_
0785 Real*8 timenow
0786 external etime_, timenow
0787 Real*4 actual, tarray(2)
329ab22289 Chri*0788 # elif (defined TARGET_T3E || defined TARGET_CRAY_VECTOR)
900679fae2 Jean*0789 real second, secondr
0f82b218cd Jean*0790 external second, secondr
0584962966 Chri*0791 # else
9e3c812741 Jean*0792 # ifdef HAVE_ETIME_FCT
0793 Real*4 etime
0794 EXTERNAL etime
0795 Real*4 actual, tarray(2)
0796 # elif (defined HAVE_ETIME_SBR)
0584962966 Chri*0797 Real*4 actual, tarray(2)
0798 # else
0799 Real*8 csystemtime, cusertime
0800 external csystemtime, cusertime
0801 # endif
0802 # if defined HAVE_CLOC
1511bdc7b0 Alis*0803 Real*8 wtime
0584962966 Chri*0804 # elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))
0805
cc353c2c58 Jean*0806 # else
0807 Real*8 timenow
0584962966 Chri*0808 external timenow
0809 # endif /* HAVE_CLOC */
0810 # endif
4c563c2ee9 Chri*0811
0812
0584962966 Chri*0813
1511bdc7b0 Alis*0814
5ecfcdf53f Cons*0815
0816 # if defined(TARGET_AIX) || defined(TARGET_BGL)
0817 ACTUAL = ETIME_(TARRAY)
0818 userTime = TARRAY(1)
0819 systemTime = TARRAY(2)
ff43152480 Patr*0820 wallClockTime = timenow()
0584962966 Chri*0821 # elif (defined (TARGET_T3E) || defined (TARGET_CRAY_VECTOR))
50b31ef7a3 Cons*0822 userTime = SECOND()
ff43152480 Patr*0823 systemTime = 0.
50b31ef7a3 Cons*0824 wallClockTime = SECONDR()
0584962966 Chri*0825 # else
9e3c812741 Jean*0826 # ifdef HAVE_ETIME_FCT
0827 actual = etime(tarray)
0828 userTime = tarray(1)
0829 systemTime = tarray(2)
0830 # elif (defined HAVE_ETIME_SBR)
f68522ca81 Jean*0831 call etime(tarray,actual)
0584962966 Chri*0832 userTime = tarray(1)
0833 systemTime = tarray(2)
0834 # else
0835 userTime = cusertime()
0836 systemTime = csystemtime()
0837 # endif
0838 # if defined HAVE_CLOC
0839 CALL cloc(wTime)
50b31ef7a3 Cons*0840 wallClockTime = wtime
0584962966 Chri*0841 # elif (defined (ALLOW_USE_MPI) && defined (USE_MPI_WTIME))
0842 wallClockTime = MPI_Wtime()
0f82b218cd Jean*0843 # else
0584962966 Chri*0844 wallClockTime = timenow()
0845 # endif
0846 # endif
0847 #endif
4b08b6ee66 Ed H*0848
1511bdc7b0 Alis*0849 RETURN
0850 END
0851
0f82b218cd Jean*0852
4c563c2ee9 Chri*0853
0854
0855
0856
1511bdc7b0 Alis*0857 SUBROUTINE TIMER_PRINTALL( myThreadId )
18e2723366 Alis*0858 IMPLICIT NONE
4c563c2ee9 Chri*0859
0860
0861
0f82b218cd Jean*0862
0863
4c563c2ee9 Chri*0864
0f82b218cd Jean*0865
4c563c2ee9 Chri*0866
0867
0868
0869
1511bdc7b0 Alis*0870 INTEGER myThreadId
4c563c2ee9 Chri*0871
0872
0f82b218cd Jean*0873 CALL TIMER_CONTROL( ' ', 'PRINTALL', 'TIMER_PRINTALL' ,
46dc4f419b Chri*0874 & myThreadId )
1511bdc7b0 Alis*0875
0876 RETURN
0877 END
4c563c2ee9 Chri*0878
0f82b218cd Jean*0879
4c563c2ee9 Chri*0880
0881
0882
0883
1511bdc7b0 Alis*0884 SUBROUTINE TIMER_START ( string , myThreadId )
18e2723366 Alis*0885 IMPLICIT NONE
4c563c2ee9 Chri*0886
0887
0888
0889
0890
0891
0892
1511bdc7b0 Alis*0893 CHARACTER*(*) string
0894 INTEGER myThreadId
4c563c2ee9 Chri*0895
1511bdc7b0 Alis*0896
0897 CALL TIMER_CONTROL( string, 'START', 'TIMER_START' , myThreadId)
0898
0899 RETURN
0900 END
0f82b218cd Jean*0901
0902
4c563c2ee9 Chri*0903
0904
0905
0906
c23f4a1c98 Cons*0907 SUBROUTINE TIMER_STOP ( string , myThreadId )
18e2723366 Alis*0908 IMPLICIT NONE
4c563c2ee9 Chri*0909
0910
0911
0912
0913
0914
0915
1511bdc7b0 Alis*0916 CHARACTER*(*) string
0917 INTEGER myThreadId
4c563c2ee9 Chri*0918
1511bdc7b0 Alis*0919
0920 CALL TIMER_CONTROL( string, 'STOP', 'TIMER_STOP' , myThreadId )
0921
0922 RETURN
0923 END
0f82b218cd Jean*0924
0925
c23f4a1c98 Cons*0926
0927 #ifdef USE_PAPI
0928
0929 BLOCK DATA setpapivalues
0930 #include "EEPARAMS.h"
0931 INTEGER maxTimers
fbb427d468 Andr*0932 PARAMETER (maxTimers = 50)
c23f4a1c98 Cons*0933 INTEGER nmaxevents
0934 PARAMETER (nmaxevents = 18)
0935 INTEGER size
0936 PARAMETER (size = 3*nmaxevents*maxTimers*MAX_NO_THREADS)
0937 INTEGER*8 values(nmaxevents, maxTimers , MAX_NO_THREADS),
0938 $ values1(nmaxevents, maxTimers, MAX_NO_THREADS),
0939 $ values2(nmaxevents, maxTimers, MAX_NO_THREADS)
0940 COMMON /papivalues/ values, values1, values2
0f82b218cd Jean*0941 DATA values, values1, values2 /size*0/
c23f4a1c98 Cons*0942 END
0943 #endif
008ba3ca0d Cons*0944 #if defined(USE_PCL_FLOPS_SFP) || defined(USE_PCL_FLOPS) || defined(USE_PCL)
0945
0946 BLOCK DATA setpclnames
0947 INTEGER nmaxevents
0948 PARAMETER (nmaxevents = 61)
0949 CHARACTER*22 pcl_counter_name(0:nmaxevents-1)
0950 COMMON /pclnames/ pcl_counter_name
0951 DATA pcl_counter_name(0) /'PCL_L1CACHE_READ'/
0952 DATA pcl_counter_name(1) /'PCL_L1CACHE_WRITE'/
0953 DATA pcl_counter_name(2) /'PCL_L1CACHE_READWRITE'/
0954 DATA pcl_counter_name(3) /'PCL_L1CACHE_HIT'/
0955 DATA pcl_counter_name(4) /'PCL_L1CACHE_MISS'/
0956 DATA pcl_counter_name(5) /'PCL_L1DCACHE_READ'/
0957 DATA pcl_counter_name(6) /'PCL_L1DCACHE_WRITE'/
0958 DATA pcl_counter_name(7) /'PCL_L1DCACHE_READWRITE'/
0959 DATA pcl_counter_name(8) /'PCL_L1DCACHE_HIT'/
0960 DATA pcl_counter_name(9) /'PCL_L1DCACHE_MISS'/
0961 DATA pcl_counter_name(10) /'PCL_L1ICACHE_READ'/
0962 DATA pcl_counter_name(11) /'PCL_L1ICACHE_WRITE'/
0963 DATA pcl_counter_name(12) /'PCL_L1ICACHE_READWRITE'/
0964 DATA pcl_counter_name(13) /'PCL_L1ICACHE_HIT'/
0965 DATA pcl_counter_name(14) /'PCL_L1ICACHE_MISS'/
0966 DATA pcl_counter_name(15) /'PCL_L2CACHE_READ'/
0967 DATA pcl_counter_name(16) /'PCL_L2CACHE_WRITE'/
0968 DATA pcl_counter_name(17) /'PCL_L2CACHE_READWRITE'/
0969 DATA pcl_counter_name(18) /'PCL_L2CACHE_HIT'/
0970 DATA pcl_counter_name(19) /'PCL_L2CACHE_MISS'/
0971 DATA pcl_counter_name(20) /'PCL_L2DCACHE_READ'/
0972 DATA pcl_counter_name(21) /'PCL_L2DCACHE_WRITE'/
0973 DATA pcl_counter_name(22) /'PCL_L2DCACHE_READWRITE'/
0974 DATA pcl_counter_name(23) /'PCL_L2DCACHE_HIT'/
0975 DATA pcl_counter_name(24) /'PCL_L2DCACHE_MISS'/
0976 DATA pcl_counter_name(25) /'PCL_L2ICACHE_READ'/
0977 DATA pcl_counter_name(26) /'PCL_L2ICACHE_WRITE'/
0978 DATA pcl_counter_name(27) /'PCL_L2ICACHE_READWRITE'/
0979 DATA pcl_counter_name(28) /'PCL_L2ICACHE_HIT'/
0980 DATA pcl_counter_name(29) /'PCL_L2ICACHE_MISS'/
0981 DATA pcl_counter_name(30) /'PCL_TLB_HIT'/
0982 DATA pcl_counter_name(31) /'PCL_TLB_MISS'/
0983 DATA pcl_counter_name(32) /'PCL_ITLB_HIT'/
0984 DATA pcl_counter_name(33) /'PCL_ITLB_MISS'/
0985 DATA pcl_counter_name(34) /'PCL_DTLB_HIT'/
0986 DATA pcl_counter_name(35) /'PCL_DTLB_MISS'/
0987 DATA pcl_counter_name(36) /'PCL_CYCLES'/
0988 DATA pcl_counter_name(37) /'PCL_ELAPSED_CYCLES'/
0989 DATA pcl_counter_name(38) /'PCL_INTEGER_INSTR'/
0990 DATA pcl_counter_name(39) /'PCL_FP_INSTR'/
0991 DATA pcl_counter_name(40) /'PCL_LOAD_INSTR'/
0992 DATA pcl_counter_name(41) /'PCL_STORE_INSTR'/
0993 DATA pcl_counter_name(42) /'PCL_LOADSTORE_INSTR'/
0994 DATA pcl_counter_name(43) /'PCL_INSTR'/
0995 DATA pcl_counter_name(44) /'PCL_JUMP_SUCCESS'/
0996 DATA pcl_counter_name(45) /'PCL_JUMP_UNSUCCESS'/
0997 DATA pcl_counter_name(46) /'PCL_JUMP'/
0998 DATA pcl_counter_name(47) /'PCL_ATOMIC_SUCCESS'/
0999 DATA pcl_counter_name(48) /'PCL_ATOMIC_UNSUCCESS'/
1000 DATA pcl_counter_name(49) /'PCL_ATOMIC'/
1001 DATA pcl_counter_name(50) /'PCL_STALL_INTEGER'/
1002 DATA pcl_counter_name(51) /'PCL_STALL_FP'/
1003 DATA pcl_counter_name(52) /'PCL_STALL_JUMP'/
1004 DATA pcl_counter_name(53) /'PCL_STALL_LOAD'/
1005 DATA pcl_counter_name(54) /'PCL_STALL_STORE'/
1006 DATA pcl_counter_name(55) /'PCL_STALL'/
1007 DATA pcl_counter_name(56) /'PCL_MFLOPS'/
1008 DATA pcl_counter_name(57) /'PCL_IPC'/
1009 DATA pcl_counter_name(58) /'PCL_L1DCACHE_MISSRATE'/
1010 DATA pcl_counter_name(59) /'PCL_L2DCACHE_MISSRATE'/
1011 DATA pcl_counter_name(60) /'PCL_MEM_FP_RATIO'/
1012 END
1013
1014 #ifdef USE_PCL
1015
1016 BLOCK DATA setpcls
1017 #include "EEPARAMS.h"
1018 INTEGER maxTimers
fbb427d468 Andr*1019 PARAMETER (maxTimers = 50)
008ba3ca0d Cons*1020 INTEGER nmaxevents
1021 PARAMETER (nmaxevents = 61)
1022 INTEGER size
1023 PARAMETER (size = nmaxevents*maxTimers*MAX_NO_THREADS)
1024 INTEGER PCL_CYCLES, PCL_MODE_USER_SYSTEM
1025 PARAMETER (PCL_CYCLES=36, PCL_MODE_USER_SYSTEM=3)
1026 INTEGER pcl_counter_list(nmaxevents)
1027 INTEGER flags, nevents
1028 INTEGER*8 i_result(nmaxevents, maxTimers, MAX_NO_THREADS)
1029 INTEGER*8 i_result1(nmaxevents, maxTimers, MAX_NO_THREADS)
1030 INTEGER*8 i_result2(nmaxevents, maxTimers, MAX_NO_THREADS)
1031 INTEGER*8 descr
1032 REAL*8 fp_result(nmaxevents, maxTimers, MAX_NO_THREADS)
1033 COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
1034 $ flags, nevents
1035 DATA fp_result /size*0.0D0/
1036 DATA i_result /size*0/
1037 DATA i_result1 /size*0/
1038 DATA i_result2 /size*0/
1039 DATA descr /0/
1040 DATA nevents /nmaxevents/
1041 DATA pcl_counter_list /nmaxevents*PCL_CYCLES/
1042 DATA flags /PCL_MODE_USER_SYSTEM/
1043 END
1044 #else
1045
1046 BLOCK DATA setpcls
1047 INTEGER PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
1048 $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO
1049 PARAMETER (PCL_MFLOPS=56, PCL_IPC=57, PCL_L1DCACHE_MISSRATE=58,
1050 $ PCL_L2DCACHE_MISSRATE=59, PCL_MEM_FP_RATIO=60)
1051 INTEGER PCL_MODE_USER_SYSTEM
1052 PARAMETER (PCL_MODE_USER_SYSTEM=3)
1053 INTEGER pcl_counter_list(5), flags, nevents
1054 INTEGER*8 i_result(5), descr
1055 REAL*8 fp_result(5)
1056 COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
1057 $ flags, nevents
1058 DATA fp_result /5*0.0D0/
1059 DATA i_result /5*0/
1060 DATA descr /0/
1061 DATA nevents /0/
1062 DATA pcl_counter_list /PCL_MFLOPS, PCL_IPC, PCL_L1DCACHE_MISSRATE,
1063 $ PCL_L2DCACHE_MISSRATE, PCL_MEM_FP_RATIO/
1064 DATA flags /PCL_MODE_USER_SYSTEM/
1065 END
1066 #endif
1067 #endif