Skip to content

Commit

Permalink
Trying to get counters working
Browse files Browse the repository at this point in the history
  • Loading branch information
Srinath Vadlamani committed Jan 2, 2013
1 parent f53d02e commit f74f186
Show file tree
Hide file tree
Showing 2 changed files with 103 additions and 0 deletions.
71 changes: 71 additions & 0 deletions gfortQp.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
module IFWIN

use ISO_C_BINDING

implicit none

private

public QueryPerformanceCounter

interface

function QueryPerformanceCounter(lpPerformanceCount) &

bind(C, name='QueryPerformanceCounter')

import

implicit none

!gcc attributes stdcall :: QueryPerformanceCounter

integer(C_INT) QueryPerformanceCounter

integer(C_INT64_T) lpPerformanceCount

end function QueryPerformanceCounter

end interface

public QueryPerformanceFrequency

interface

function QueryPerformanceFrequency(lpFrequency) &

bind(C, name='QueryPerformanceFrequency')

import

implicit none

!gcc attributes stdcall :: QueryPerformanceFrequency

integer(C_INT) QueryPerformanceFrequency

integer(C_INT64_T) lpFrequency

end function QueryPerformanceFrequency

end interface

end module IFWIN
program test

use IFWIN

use ISO_C_BINDING

implicit none

integer(C_INT64_T) lpFrequency, lpPerformanceCount

integer(C_INT) ll
ll = QueryPerformanceFrequency(lpFrequency)

ll = QueryPerformanceCounter(lpPerformanceCount)

write(*,*) lpFrequency, lpPerformanceCount

end program test
32 changes: 32 additions & 0 deletions queryPerform.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
SUBROUTINE use_QueryPerform (elapse)
!
! Returns the total elapsed time in seconds
! based on QueryPerformanceCounter
! This is the fastest and most accurate timing routine
!
real*8, intent (out) :: elapse
!
STDCALL QUERYPERFORMANCECOUNTER 'QueryPerformanceCounter' (REF):LOGICAL*4
STDCALL QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4
!
real*8 :: freq = 1
logical*4 :: first = .true.
integer*8 :: start = 0
integer*8 :: num
logical*4 :: ll
!
! Calibrate this time using QueryPerformanceFrequency
if (first) then
num = 0
ll = QueryPerformanceFrequency (num)
freq = 1.0d0 / dble (num)
start = 0
ll = QueryPerformanceCounter (start)
first = .false.
end if
!
num = 0
ll = QueryPerformanceCounter (num)
elapse = dble (num-start) * freq
return
end

0 comments on commit f74f186

Please sign in to comment.