High resolution timer - danielep71/VBA-PERFORMANCE GitHub Wiki

[Home]] ](/danielep71/VBA-PERFORMANCE/wiki/[[Class-cPerformanceMonitor)


While the APIs Functions we have seen so far are accurate enough for most operations, they do not provide the maximum possible resolution. If the hardware handles high-resolution counters, we can get a better result with specific API Functions.

The QueryPerformnceCounter (QPC) is a high-resolution hardware counter that can measure brief periods with high precision and low overhead.

Most modern PCs include a high-resolution timer (HRT), which updates thousands of times per second and is accessible through APIs. The HRT has two important pieces of information:

  • the number of elapsed counts;
  • the number of counts per second.

If we know that a given process takes 100 counts and the frequency of the HRT is 250,000 counts per second, the elapsed time is 0.0004 (100 / 250,000) seconds or 4 microseconds.

The HRT’s precision level will vary depending on the CPU and cannot be changed. It is fixed at system boot.

5.1. QPC and QPF

The two useful functions are QueryPerformanceCounter (QPC) and QueryPerformanceFrequency (QPF):

  • QPC uses a hardware counter. It is independent of, and isn't synchronized to, any external time reference. QPC returns the current value of the computer’s performance counter. This will be the whole number representing the number of “counts” (similar to the number of ticks on a very fast clock). Hardware timers consist of three parts. The characteristics of these three components determine the resolution, precision, accuracy, and stability of QPC;
    • a tick generator
    • a counter that counts the ticks
    • and a means of retrieving the counter value.
  • QPF returns the number of Ticks per second (10,000,000 on this test machine).

The tick interval, or period, is the reciprocal of 10,000,000, which is 0.0000001 (100 nanoseconds).

Therefore, each tick represents the passing of 100 nanoseconds. Time intervals smaller than 100 nanoseconds can't be measured on this machine.

5.2 API Declaration

The win32api.txt file shows these definitions using the data type LARGE_INTEGER

QPC and QPF

Declare Function QueryPerformanceCounter Lib "kernel32" Alias _
    "QueryPerformanceCounter" (lpPerformanceCount As LARGE_INTEGER) As Long
Declare Function QueryPerformanceFrequency Lib "kernel32" Alias _
    "QueryPerformanceFrequency" (lpFrequency As LARGE_INTEGER) As Long

If we use this declaration as it is, VBA will give us a compile error: “User-defined type not defined”.

A LARGE_INTEGER represents a 64-bit signed integer value, usually made up of two Longs.

VBA for 32-bit Excel doesn’t have a 64-bit integer (the long integer only has 32-bits).

VBA for 64-bit Excel introduces the LongLong data type, which is 64-bit. In a 32-bit environment it means that we are forced to process the most significant and least significant parts of those numbers separately, which results in a large amount of less efficient code.

How to manage Large Integer

Private Type LARGE_INTEGER
    LowPart As Long
    HighPart As Long
End Type

Private m_CounterStart As LARGE_INTEGER`
Private m_CounterEnd As LARGE_INTEGER`
Private m_crFrequency As Double`
Private Const TWO_32 = 4294967296# ' = 256# * 256# * 256# * 256#`

Private Function LI2Double(LI As LARGE_INTEGER) As Double
    Dim Low As Double
    Low = LI.LowPart
    If Low < 0 Then
        Low = Low + TWO_32
    End If
    LI2Double = LI.HighPart * TWO_32 + Low
End Function

Private Sub Class_Initialize()
    Dim PerfFrequency As LARGE_INTEGER
    QueryPerformanceFrequency PerfFrequency
    m_crFrequency = LI2Double(PerfFrequency)
End Sub

Public Sub StartCounter()
    QueryPerformanceCounter m_CounterStart
End Sub

Property Get TimeElapsed() As Double
    Dim crStart As Double
    Dim crStop As Double
    QueryPerformanceCounter m_CounterEnd
    crStart = LI2Double(m_CounterStart)
    crStop = LI2Double(m_CounterEnd)
    TimeElapsed = 1000# * (crStop - crStart) / m_crFrequency
End Property

Fortunately, there is a way that solves the problem quite well.

If we want to use the HRT regardless of Excel bitness, instead of using LARGE_INTEGER, we can use the Currency data type. After all, Currency values are nothing more than 64-bit integers that VBA scales by a factor of 10,000 whenever we assign them a value and re-read them.

To use currency variables instead of LARGE_INTEGER values, we need alias functions:

QPC and QPF API with Currency data type

#If VBA7 Then
    Private Declare PtrSafe Function GetFrequency Lib "kernel32" _
        Alias "QueryPerformanceFrequency" (ByRef Frequency As _
        Currency) As LongPtr
    Private Declare PtrSafe Function GetTime Lib "kernel32" _
        Alias "QueryPerformanceCounter" (ByRef counter As Currency) _
        As LongPtr
#Else
    Private Declare Function GetFrequency Lib "kernel32" _
        Alias "QueryPerformanceFrequency" (ByRef Frequency As _
        Currency) As Long
    Private Declare Function GetTime Lib "kernel32" _
        Alias "QueryPerformanceCounter" (ByRef Counter As Currency) _
        As Long
#End If

Conversion between 64-bit integers and floating point (double) can cause loss of precision because the floating-point mantissa can't represent all possible integral values.

5.3 Typical use

It would be appropriate to invoke QPF once, at the beginning of the program (or at the class initialization), to extract the internal frequency of the high-resolution timer.

Then we can invoke the QPC as many times as we want: each call returns the value of the internal counter.

For example, by extracting the value of the internal counter at the beginning and at the end of the portion of code we want to measure and subtracting the first value from the last, we will get the number of Ticks spent in the meantime.

To convert this value in seconds, divide the value obtained by the frequency determined above. The following is a code snippet that demonstrates how to use these two API functions:

Example:

Private Sub Command1_Click()
    Dim Frequency As Currency
    Dim startTime As Currency
    Dim endTime As Currency
    Dim Result As Double
'Gets the frequency counter
'Returns zero if the hardware does not handle high-resolution performance counters.
    If QueryPerformanceFrequencyAny(Frequency) = 0 Then
        MsgBox "This computer doesn't support high-resolution timers", vbCritical
        Exit Sub
    End If
'Start measurement
    QueryPerformanceCounterAny startTime
'Insert at this point the code to be measured, for example...
    Dim i As Long
        For i = 1 To 1000000
        Next
'Ends the measurement.
    QueryPerformanceCounterAny endTime
'A factor scales both the dividend and the divisor by
'10,000 so you don't need to scale the result.
    Result = (endTime - startTime) / Frequency
'Show the result
    MsgBox Result
End Sub

Clearly, it is not even necessary to consider the scale factor 10,000, as the same factor already scales both operators of the division, so it is possible (and must) ignore it.

The API call itself takes a small amount of time to complete. For accurate timings, you could take this delay into account (even if it is usually very small) using the class method “Overhead”.

5.4. Rollover

QPC reads the performance counter and returns the total number of ticks since the Windows operating system was started, including when the machine was in a sleep state such as standby, hibernate, or connected in standby.

The reset is at least 100 years from the most recent system boot and potentially longer based on the underlying hardware timer used.

Rollover isn't a concern.

5.5. Accuracy and Resolution

The results are:

  1. Method 5 - 00:00:01 - 000 ms - 465 µs - 100 ns
  2. Method 5 - 00:00:01 - 000 ms - 637 µs - 600 ns
  3. Method 5 - 00:00:01 - 000 ms - 476 µs - 300 ns
  4. Method 5 - 00:00:01 - 001 ms - 168 µs - 700 ns
  5. Method 5 - 00:00:01 - 000 ms - 636 µs - 600 ns
  6. Method 5 - 00:00:01 - 000 ms - 798 µs - 000 ns
  7. Method 5 - 00:00:01 - 000 ms - 884 µs - 300 ns
  8. Method 5 - 00:00:01 - 000 ms - 436 µs - 000 ns
  9. Method 5 - 00:00:01 - 000 ms - 369 µs - 100 ns
  10. Method 5 - 00:00:01 - 000 ms - 798 µs - 600 ns
  11. Method 5 - 00:00:01 - 001 ms - 304 µs - 400 ns
  12. Method 5 - 00:00:01 - 000 ms - 523 µs - 500 ns
  13. Method 5 - 00:00:01 - 000 ms - 382 µs - 000 ns
  14. Method 5 - 00:00:01 - 000 ms - 661 µs - 600 ns
  15. Method 5 - 00:00:01 - 000 ms - 779 µs - 400 ns
  16. Method 5 - 00:00:01 - 000 ms - 266 µs - 100 ns
  17. Method 5 - 00:00:01 - 000 ms - 720 µs - 900 ns
  18. Method 5 - 00:00:01 - 000 ms - 859 µs - 600 ns
  19. Method 5 - 00:00:01 - 001 ms - 035 µs - 100 ns
  20. Method 5 - 00:00:01 - 000 ms - 269 µs - 200 ns

Accuracy is up to 1 millisecond.

Using the NextTick Function, the results do not improve (ticks are so fast that it is not even possible to trigger them).

  1. Method 5 - 00:00:01 - 000 ms - 328 µs - 400 ns
  2. Method 5 - 00:00:01 - 000 ms - 810 µs - 100 ns
  3. Method 5 - 00:00:01 - 000 ms - 802 µs - 300 ns
  4. Method 5 - 00:00:01 - 001 ms - 148 µs - 100 ns
  5. Method 5 - 00:00:01 - 000 ms - 448 µs - 300 ns
  6. Method 5 - 00:00:01 - 001 ms - 012 µs - 200 ns
  7. Method 5 - 00:00:01 - 001 ms - 050 µs - 000 ns
  8. Method 5 - 00:00:01 - 001 ms - 292 µs - 500 ns
  9. Method 5 - 00:00:01 - 001 ms - 062 µs - 700 ns
  10. Method 5 - 00:00:01 - 000 ms - 877 µs - 500 ns
  11. Method 5 - 00:00:01 - 001 ms - 004 µs - 500 ns
  12. Method 5 - 00:00:01 - 001 ms - 215 µs - 700 ns
  13. Method 5 - 00:00:01 - 000 ms - 275 µs - 000 ns
  14. Method 5 - 00:00:01 - 000 ms - 473 µs - 800 ns
  15. Method 5 - 00:00:01 - 001 ms - 106 µs - 200 ns
  16. Method 5 - 00:00:01 - 000 ms - 255 µs - 800 ns
  17. Method 5 - 00:00:01 - 000 ms - 493 µs - 500 ns
  18. Method 5 - 00:00:01 - 000 ms - 574 µs - 300 ns
  19. Method 5 - 00:00:01 - 000 ms - 226 µs - 000 ns
  20. Method 5 - 00:00:01 - 001 ms - 262 µs - 400 ns

Accuracy is up to 1 millisecond.

Resolution is up to hundreds of nanoseconds.

5.6. What Microsoft says

Guidance for acquiring time stamps (https://learn.microsoft.com/en-us/windows/win32/sysinfo/acquiring-high-resolution-time-stamps?redirectedfrom=MSDN#faq_about_programming_with_qpc_and_tsc)

  • When you need time stamps with a resolution of 1 microsecond or better and don’t need the time stamps to be synchronized to an external time reference, choose QueryPerformanceCounter, KeQueryPerformanceCounter, or KeQueryInterruptTimePrecise. When you need UTC-synchronized time stamps with a resolution of 1 microsecond or better, choose GetSystemTimePreciseAsFileTime or KeQuerySystemTimePrecise.
  • QPC is typically the best method to use to time-stamp events and measure small time intervals that occur on the same system or virtual machine.

[Home]] ](/danielep71/VBA-PERFORMANCE/wiki/[[Class-cPerformanceMonitor)