Optimization of work distribution using one-dimensional bin packing algorithm_4.Attachment

The source code of this article is written based on the first version of the Bin Packing tool. There is the latest version with improved functions, so please refer to it together.

One-dimensional Bin Packing Tool Recent Changes (as of March 21, 2021)

5. Attachment

5.1. Excel VBA based tool source code

Bin Packing implemented with Excel VBA is implemented purely with VBA code without external library or package, so the amount of source code is rather long. Most of the algorithms are implemented in the CPacker class, so take a look at this class first.

1차원 Bin Packing 알고리즘을 활용한 작업 배분 최적화 소스코드 화면
Source code screen for optimizing work distribution using one-dimensional bin packing algorithm

5.1.1. Run sheet source code

This is the code corresponding to the click event of the “Run BinPacking” button.

Use Excel's Range object to pass the list's base range and option values to the RunBinPacking procedure. Here, for Range, the object defined by the name was mainly used. (Example: Range(“MaxBinSize”)) If you define Range as a name, there is no need to change the source code even if the reference address changes. .

Private Sub cmdRunBinPacking_Click()
    RunBinPacking aBaseRange:=Range("B2").Address, _
                  aMaxBinSize:=Range("MaxBinSize").Value, _
                  aSizeBaseColumn:=Range("SizeBaseClolumn").Value, _
                  aIsItemSort:=Range("ItemSize내림차순정렬여부").Value
End Sub

5.1.2. modFactory module source code

It is responsible for creating an instance of the class. Classes in VBA cannot override constructors with parameters. A module implemented by Factory Pattern is used instead of a constructor.

aPackingType of the CreatePacker procedure is an enumeration variable that indicates the Bin Packing algorithm processing type. There are four possible values: ptNextFit, ptFirstFit, ptBestFit, and ptWorstFit.

Option Explicit

Public Function CreatePacker(aMaxBinSize As Long, aPackingType As PackingType) As CPacker
    Set CreatePacker = New CPacker
    CreatePacker.Init aMaxBinSize, aPackingType
End Function

Public Function CreateBin(aMaxBinSize As Long) As CBin
    Set CreateBin = New CBin
    CreateBin.Init aMaxBinSize
End Function

5.1.3. modControl module source code

It is responsible for managing the processing of the entire algorithm in the RunBinPacking procedure. The meaning of each parameter is as follows.

  • aBaseRange: Start range of input data (string such as “B2”)
  • aMaxBinSize: constraint the maximum size of one bin (an integer such as 80, 10000, etc.)
  • aSizeBaseColumn: The name of the bin size base column selected in the option (a string such as “C”)
  • aIsItemSort: Whether to execute descending sort (True/False value)
Option Explicit

Public Sub RunBinPacking(aBaseRange As String, aMaxBinSize As Long, _
                         aSizeBaseColumn As String, aIsItemSort As Boolean)
    Application.ScreenUpdating = False
    Application.Calculation = xlCalculationManual

    Dim oBaseRange As Range, lCurRow As Long, oBinItem As CBinItem
    Dim oInputItemCol As CBinItemCollection: Set oInputItemCol = New CBinItemCollection
    Set oBaseRange = Range(aBaseRange)
    Dim sSizeBaseColumn As String, lSizeColumnOffset As Long
    sSizeBaseColumn = aSizeBaseColumn 'Range("SizeBaseClolumn")
    lSizeColumnOffset = Range(oBaseRange, sSizeBaseColumn & "2").Columns.Count - 1

    'Build up the BinItem List Collection
    lCurRow = 0
    For lCurRow = 0 To oBaseRange.CurrentRegion.Rows.Count
        If Trim(oBaseRange.Offset(lCurRow, 0).Value) = "" Then Exit For
        Set oBinItem = New CBinItem
        oBinItem.m_sName = oBaseRange.Offset(lCurRow, 0).Value  'Item Name
        oBinItem.m_lSize = oBaseRange.Offset(lCurRow, lSizeColumnOffset).Value 'Item Size 기준 컬럼의 값(예: KB, MB 등)
        oInputItemCol.Add oBinItem, oBinItem.m_sName
    Next lCurRow

    'Item Size로 내림차순 정렬 처리
    If aIsItemSort Then
        DoLog "정렬 전 --> " + oInputItemCol.GetString
        Set oInputItemCol = oInputItemCol.Sort
        DoLog "정렬 후 --> " + oInputItemCol.GetString
    End If

    Dim lMaxBinSize As Long
    Dim oPackerNextFit As CPacker, oPackerFirstFit As CPacker
    Dim oPackerWorstFit As CPacker, oPackerBestFit As CPacker
    lMaxBinSize = aMaxBinSize

    'NextFit
    Set oPackerNextFit = CreatePacker(lMaxBinSize, ptNextFit)
    oPackerNextFit.DoPacking oInputItemCol
    oPackerNextFit.DoOutput Worksheets("Next Fit")
    Set oPackerNextFit = Nothing

    'FirstFit
    Set oPackerFirstFit = CreatePacker(lMaxBinSize, ptFirstFit)
    oPackerFirstFit.DoPacking oInputItemCol
    oPackerFirstFit.DoOutput Worksheets("First Fit")
    Set oPackerFirstFit = Nothing

    'WorstFit
    Set oPackerWorstFit = CreatePacker(lMaxBinSize, ptWorstFit)
    oPackerWorstFit.DoPacking oInputItemCol
    oPackerWorstFit.DoOutput Worksheets("Worst Fit")
    Set oPackerWorstFit = Nothing

    'BestFit
    Set oPackerBestFit = CreatePacker(lMaxBinSize, ptBestFit)
    oPackerBestFit.DoPacking oInputItemCol
    oPackerBestFit.DoOutput Worksheets("Best Fit")
    Set oPackerBestFit = Nothing

    Worksheets("Result Summary").Activate
    Worksheets("Result Summary").Range("E1") = lMaxBinSize
    DoEvents

    Application.Calculation = xlCalculationAutomatic
    Application.ScreenUpdating = True
End Sub

5.1.4. modUtil module source code

It is responsible for common functions such as logging and converting required time into string format. Logging uses the Windows API OutputDebugString.

Option Explicit
#Const DEBUGMODE = 1

#If VBA7 Then 'For 64 Bit Systems
    Public Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As LongPtr)
    Private Declare PtrSafe Sub OutputDebugString Lib "kernel32" Alias "OutputDebugStringA" (ByVal lpOutputString As String)
#Else 'For 32 Bit Systems
    Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
    Private Declare Sub OutputDebugString Lib "kernel32" Alias "OutputDebugStringA" (ByVal lpOutputString As String)
#End If

'OutputDebugString API를 이용한 Debug Message 출력
'DebugView등을 이용하여 메시지 View 가능함
Public Sub DoLog(aMsg As String)
    #If DEBUGMODE >= 1 Then
        OutputDebugString "[Bin] " & aMsg
    #End If
End Sub

Function GetTimeString(dTime As Double) As String
  Dim H As Integer, M As Integer, S As Integer, MS As Integer, dMS As Double, sMS As String

  H = Int(dTime / 3600)
  M = Int(dTime / 60) Mod 60
  S = Int(dTime Mod 60)
  dMS = (dTime - Int(dTime))
  'MS = dMS * 10 ^ (Len(CStr(dMS)) - 2)
  sMS = Mid(CStr(dMS), 3, Len(dMS))

GetTimeString = Format(H, "00") & ":" & Format(M, "00") & ":" & Format(S, "00") & "." & sMS

End Function

5.1.5. CPacker class source code

Implement a bin packing algorithm that fills the input data to an appropriate place among the existing bin list or creates and fills new bins. The main variables, procedures, and functions are as follows.

  • The list of Bin objects is managed as the m_oBinCol collection variable, and the sum of the remaining space of each Bin object is managed as the lRemainSizeSum variable.
  • Init procedure: Set the maximum size of the bin and the type of filling algorithm (Next Fit, First Fit, Best Fit, Worst Fit).
    Add procedure: Add the Bin object passed as a parameter to the m_oBinCol collection variable and create a name as “Bin_ 5 digits of sequence number”.
  • DoPacking procedure: Fills the Item list passed as a parameter to the Bin object list.
  • GetNewBin function: Creates a new Bin object using the CreateBin function of the modFactory module.
  • GetBinNextFit function: Selects a suitable bin to fill the BinItem passed as a parameter with the Next Fit algorithm or creates a new one and returns it.
  • GetBinFirstFit function: Selects a suitable bin to fill the BinItem passed as a parameter with the First Fit algorithm or creates a new one and returns it.
  • GetBinWorstFit function: Selects a suitable bin to fill the BinItem passed as a parameter with the Worst Fit algorithm or creates a new one and returns it.
  • GetBinBestFit function: Selects a suitable bin to fill the BinItem passed as a parameter with the Best Fit algorithm or creates a new one and returns it.
  • PackToBin procedure: Fills BinItems by calling the appropriate function according to the set algorithm type.
  • DoOutput procedure: Outputs the result of Bin Packing processing to the specified sheet.
Option Explicit

Public m_oBinCol As Collection
Public m_dElapsedTime As Double
Public Enum PackingType
    ptNextFit
    ptFirstFit
    ptBestFit
    ptWorstFit
End Enum

Private m_lMaxBinSize As Long
Private m_lLastBinIndex As Long
Private m_PackingType As PackingType
Private m_lCompareCount As Long '비교연산의 횟수 누적
Private m_lRemainSizeSum As Long '잔여공간 합계
Private m_oTimer As CTimer

Private Sub Class_Initialize()
    Set m_oBinCol = New Collection
    Set m_oTimer = New CTimer
    m_lLastBinIndex = 1
    m_lCompareCount = 0
End Sub

Private Sub Class_Terminate()
    Set m_oBinCol = Nothing
    Set m_oTimer = Nothing
End Sub

Public Sub Init(aMaxBinSize As Long, aPackingType As PackingType)
    m_lMaxBinSize = aMaxBinSize
    m_PackingType = aPackingType
End Sub

'입력자료 목록을 입력으로 전체 채우기 실행
Public Sub DoPacking(aInputItemCol As CBinItemCollection)
    Dim oBinItem As CBinItem
    m_oTimer.StartCounter
    For Each oBinItem In aInputItemCol.m_oBinItemCol
        Me.PackToBin oBinItem
    Next
    Me.m_dElapsedTime = m_oTimer.TimeElapsed
End Sub

'한 Item 채우기
Public Sub PackToBin(oBinItem As CBinItem)
    Dim oBin As CBin
    'Select Case ePackingType
    Select Case m_PackingType
        Case ptNextFit
            Set oBin = GetBinNextFit(oBinItem)
        Case ptFirstFit
            Set oBin = GetBinFirstFit(oBinItem)
        Case ptWorstFit
            Set oBin = GetBinWorstFit(oBinItem)
        Case ptBestFit
            Set oBin = GetBinBestFit(oBinItem)
    End Select
    oBin.AddBinItem oBinItem
End Sub


Public Sub Add(oBin As CBin)
    m_oBinCol.Add oBin
    oBin.m_lIndex = m_oBinCol.Count
    'oBin.m_sName = "Bin" + CStr(m_oBinCol.Count)
    oBin.m_sName = "Bin_" + Format(CStr(m_oBinCol.Count), "00000")
End Sub

Public Function GetNewBin() As CBin
    Dim oBin As CBin
    'Set oBin = New CBin
    Set oBin = CreateBin(m_lMaxBinSize)
    Me.Add oBin
    Set GetNewBin = oBin
End Function

'NextFit
Public Function GetBinNextFit(oBinItem As CBinItem) As CBin
    Dim oBin As CBin, oResult As CBin
    If m_oBinCol.Count = 0 Then
        '첫번째 실행인 경우
        Set oResult = GetNewBin
        m_lLastBinIndex = 1
    Else
        Set oBin = m_oBinCol(m_lLastBinIndex)
        m_lCompareCount = m_lCompareCount + 1
        If oBin.IsAbleToAdd(oBinItem) Then
            Set oResult = oBin
        Else
            Set oResult = GetNewBin
            m_lLastBinIndex = oResult.m_lIndex
        End If
    End If
    Set GetBinNextFit = oResult
End Function

'FirstFit
Public Function GetBinFirstFit(oBinItem As CBinItem) As CBin
    Dim oBin As CBin, bFound As Boolean, lCurBinIndex As Long, oResult As CBin
    bFound = False
    '항상 처음 Bin부터 확인하여 추가할 수 있는 Bin return
    For lCurBinIndex = 1 To m_oBinCol.Count
    'For Each oBin In m_oBinCol
        Set oBin = m_oBinCol(lCurBinIndex)
        m_lCompareCount = m_lCompareCount + 1
        If oBin.IsAbleToAdd(oBinItem) Then
            bFound = True
            Set oResult = oBin
            Exit For
        End If
    Next
    If Not bFound Then
        Set oResult = GetNewBin
    End If
    Set GetBinFirstFit = oResult
End Function

'WorstFit
Public Function GetBinWorstFit(oBinItem As CBinItem) As CBin
    Dim oBin As CBin, bFound As Boolean, lCurBinIndex As Long, oResult As CBin
    Dim lMaxRemainSize As Long, lMaxRemainSizeBinIndex As Long
    lMaxRemainSize = 0: lMaxRemainSizeBinIndex = 0
    '모든 Bin중에서 남은 Size가 가장 크고 oBinItem을 추가할 수 있는 Bin을 return
    '추가할 수 있는 Bin이 없으면 새 Bin을 생성
    For lCurBinIndex = 1 To m_oBinCol.Count
        '남은 Size가 가장 큰 Bin 찾기
        Set oBin = m_oBinCol(lCurBinIndex)
        m_lCompareCount = m_lCompareCount + 1
        If lMaxRemainSize < oBin.m_lRemainSize Then
            lMaxRemainSize = oBin.m_lRemainSize
            lMaxRemainSizeBinIndex = lCurBinIndex
        End If
    Next

    bFound = False
    m_lCompareCount = m_lCompareCount + 1
    If lMaxRemainSizeBinIndex > 0 Then
        Set oBin = m_oBinCol(lMaxRemainSizeBinIndex)
        If oBinItem.m_lSize <= oBin.m_lRemainSize Then
            bFound = True
            Set oResult = oBin
        End If
    End If
    If Not bFound Then
        Set oResult = GetNewBin
    End If
    Set GetBinWorstFit = oResult
End Function

'BestFit
Public Function GetBinBestFit(oBinItem As CBinItem) As CBin
    Dim oBin As CBin, bFound As Boolean, lCurBinIndex As Long, oResult As CBin
    Dim lMinRemainSize As Long, lMinRemainSizeBinIndex As Long
    lMinRemainSize = m_lMaxBinSize
    lMinRemainSizeBinIndex = 0
    '모든 Bin중에서 남은 Size가 가장 적으면서 oBinItem을 추가할 수 있는 Bin을 return
    '추가할 수 있는 Bin이 없으면 새 Bin을 생성
    For lCurBinIndex = 1 To m_oBinCol.Count
        'oBinItem을 추가할 수 있는 Bin중 남은 Size가 가장 작은 Bin 찾기
        Set oBin = m_oBinCol(lCurBinIndex)
        m_lCompareCount = m_lCompareCount + 1
        If oBin.m_lRemainSize >= oBinItem.m_lSize And _
           lMinRemainSize > oBin.m_lRemainSize Then
            lMinRemainSize = oBin.m_lRemainSize
            lMinRemainSizeBinIndex = lCurBinIndex
        End If
    Next

    bFound = False
    m_lCompareCount = m_lCompareCount + 1
    If lMinRemainSizeBinIndex > 0 Then
        Set oBin = m_oBinCol(lMinRemainSizeBinIndex)
        bFound = True
        Set oResult = oBin
    End If
    If Not bFound Then
        Set oResult = GetNewBin
    End If
    Set GetBinBestFit = oResult
End Function

'결과 출력
Public Sub DoOutput(oResultSht As Worksheet)
    oResultSht.Activate
    Dim oResultBaseRange As Range, oBin As CBin, lCurRow As Long, oBinItem As CBinItem
    Set oResultBaseRange = oResultSht.Range("A2")
    'oResultBaseRange.End(xlDown).Resize(0, 2).Clear
    oResultBaseRange.Select
    Range(Selection, Selection.End(xlDown)).Select
    Selection.Resize(, 3).Select
    'Range(Selection, Selection.End(xlToRight)).Select
    Selection.ClearContents
    oResultBaseRange.Select
    lCurRow = 0
    oResultSht.Range("I1") = m_dElapsedTime '소요시간
    oResultSht.Range("J1").NumberFormatLocal = "@"
    oResultSht.Range("J1") = GetTimeString(m_dElapsedTime)
    oResultSht.Range("I2") = m_lCompareCount '비교횟수
    oResultSht.Range("I3") = GetRemainSizeSum '잔여공간합계
    oResultSht.Range("I4") = Me.m_oBinCol.Count * m_lMaxBinSize  '전체공간합계
    For Each oBin In Me.m_oBinCol
        For Each oBinItem In oBin.m_oBinItemCol.m_oBinItemCol
            oResultBaseRange.Offset(lCurRow, 0) = oBin.m_sName
            oResultBaseRange.Offset(lCurRow, 1) = oBinItem.m_sName
            oResultBaseRange.Offset(lCurRow, 2) = oBinItem.m_lSize
            lCurRow = lCurRow + 1
        Next
    Next
    Dim pt As PivotTable, sDataRange As String
    sDataRange = oResultSht.Name + "!R1C1:R" + CStr(oResultBaseRange.CurrentRegion.Rows.Count) + _
                 "C" + CStr(oResultBaseRange.CurrentRegion.Columns.Count)
    For Each pt In oResultSht.PivotTables
        pt.ChangePivotCache ActiveWorkbook.PivotCaches.Create(SourceType:=xlDatabase, SourceData:=sDataRange, Version:=xlPivotTableVersion14)
        pt.RefreshTable
    Next
    oResultBaseRange.Select
End Sub

'잔여공간 합계 계산후 return
Public Function GetRemainSizeSum() As Long
    m_lRemainSizeSum = 0
    Dim oBin As CBin
    For Each oBin In Me.m_oBinCol
        m_lRemainSizeSum = m_lRemainSizeSum + oBin.m_lRemainSize
    Next
    GetRemainSizeSum = m_lRemainSizeSum
End Function

5.1.6. CBin class source code

Implement individual bins.

  • Manage the items filled in the bin with the m_oBinItemCol collection variable.
  • Init procedure: Set the maximum size of the bin.
  • AddBinItem procedure: Adds an item to the m_oBinItemCol collection in the sense of filling the current bin. At this time, the size of the corresponding Item is added to the size of the current bin and managed with the m_lCurSize variable, and the size remaining after subtracting the size of the current bin from the maximum size of the bin is managed with the m_lRemainSize variable.
  • IsAbleToAdd: Determines whether the BinItem passed as a parameter can be filled in the current bin. True if the result of adding the size of the item to the size of the current bin is less than or equal to the maximum size.
Option Explicit

Public m_oBinItemCol As CBinItemCollection
Public m_lIndex As Long
Public m_sName As String
Public m_lCurSize As Long
Public m_lMaxSize As Long
Public m_lRemainSize As Long

Private Sub Class_Initialize()
    Set m_oBinItemCol = New CBinItemCollection
    m_lCurSize = 0
End Sub

Private Sub Class_Terminate()
    Set m_oBinItemCol = Nothing
End Sub

Public Sub Init(lMaxBinSize As Long)
    m_lMaxSize = lMaxBinSize
End Sub

Public Sub AddBinItem(oBinItem As CBinItem)
    m_oBinItemCol.Add oBinItem, oBinItem.m_sName
    m_lCurSize = m_lCurSize + oBinItem.m_lSize
    m_lRemainSize = m_lMaxSize - m_lCurSize
    If m_lRemainSize < 0 Then m_lRemainSize = 0
End Sub

Public Function IsAbleToAdd(oBinItem As CBinItem) As Boolean
    IsAbleToAdd = m_lCurSize + oBinItem.m_lSize <= m_lMaxSize
End Function

5.1.7. CBinItemCollection class source code

Implements a list of BinItems.

  • The list of BinItems is managed by the m_oBinItemCol collection variable.
  • Add procedure: Adds the item received as a parameter to the m_oBinItemCol collection.
  • Sort function: Returns a new collection that sorts the m_oBinItemCol collection in descending order of size of each Item.
  • GetString function: Returns the entire Item as a string in the format of [Name: Size].
Option Explicit

Public m_oBinItemCol As Collection

Private Sub Class_Initialize()
    Set m_oBinItemCol = New Collection
End Sub

Private Sub Class_Terminate()
    Set m_oBinItemCol = Nothing
End Sub

Public Sub Add(aBinItem As CBinItem, Optional aKey As String = "")
    m_oBinItemCol.Add aBinItem, IIf(aKey = "", aBinItem.m_sName, aKey)
End Sub

'BinItem의 Size로 내림차순 정렬
Public Function Sort() As CBinItemCollection
    Dim i As Long, j As Long, k As Long, bln As Boolean
    Dim lngCount As Long, arr() As Long, oSortedBinItemCol As CBinItemCollection
    lngCount = m_oBinItemCol.Count
    If lngCount > 0 Then
        ReDim arr(0 To lngCount - 1)
        For i = 0 To lngCount - 1: arr(i) = i + 1: Next

        For i = 1 To lngCount - 1
            k = arr(i)
            j = i - 1
            bln = False
            Do
                If m_oBinItemCol(arr(j)).CompareTo(m_oBinItemCol(k)) > 0 Then
                    arr(j + 1) = arr(j)
                    j = j - 1
                    If j < 0 Then bln = True
                Else
                    bln = True
                End If
            Loop Until bln
            arr(j + 1) = k
        Next
    End If

    Set oSortedBinItemCol = New CBinItemCollection
    For i = lngCount - 1 To 0 Step -1: oSortedBinItemCol.Add m_oBinItemCol(arr(i)): Next

    Set Sort = oSortedBinItemCol
End Function

'BinItem 목록을 문자열로 반환
Public Function GetString() As String
    Dim sResult As String, oBinItem As CBinItem
    For Each oBinItem In m_oBinItemCol
        sResult = sResult + "[" + oBinItem.m_sName + ":" + CStr(oBinItem.m_lSize) + "], "
    Next
    If Len(sResult) > 2 Then sResult = Left(sResult, Len(sResult) - 2)
    GetString = sResult
End Function

5.1.8. CBinItem class source code

Implement the Item to be put in the Bin.

  • Item name is m_sName and size is managed as m_lSize.
  • CompareTo function: Returns the result of comparing the size of the current Item and the item to be compared.
Option Explicit

Public m_sName  As String
Public m_lSize  As Long

'BinItem의 size 비교 함수
'   - parameter: 비교대상 BinItem(B)
'   - 비교기준: 자기자신 BinItem(A)
'Return 값(Long type)
'  0: 동일함 (A = B)
'  1: 비교대상 BinItem이 더 큼(A < B)
' -1: 자기자신 BinItem이 더 큼(A > B)
Public Function CompareTo(oBinItem As CBinItem) As Long
    Dim i As Long
 
    If Me.m_lSize = oBinItem.m_lSize Then
        i = 0
    ElseIf Me.m_lSize < oBinItem.m_lSize Then
        i = -1
    Else
        i = 1
    End If
 
    CompareTo = i
End Function

5.1.9. CTimer class source code

 It is used to accurately measure the execution time of each algorithm.

source: https://stackoverflow.com/questions/198409/how-do-you-test-running-time-of-vba-code

Option Explicit

Private Type LARGE_INTEGER
    lowpart As Long
    highpart As Long
End Type

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

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
    TimeElapsed = Round((crStop - crStart) / m_crFrequency, 4)
End Property

<< List of related articles >>

Leave a Reply

Your email address will not be published. Required fields are marked *

en_USEnglish