Mar 03, 2018 Added more features. And continued polishing.
Mar 05, 2018 Added the Mode calculation.
----
I've started a similar CodeBank thread before, but I'm now thinking I went too complex, as there was no interest. Just looking around earlier today, I saw a request under a CodeBank entry by The Trick. At this point, I've addressed all the requests made by CreativeDreamer.
Basically, I've just provided some one-sample statistical functions. I've also made a decision on how to handle missing values. I've struggled with this in VB6. One option is certainly the use of Variant. However, I've never been terribly happy with that option. Therefore, I've decided on sticking with Double arrays for my data, and using the IEEE Double NaN value to denote missing values. This can be seen in the code.
Now, for the uninitiated, NaN values can be a bit tricky. They're somewhat similar to the Null value, but even more restrictive. Once you get a NaN, you can continue to do math with it, but the results will be NaN (similar to Null in Variants). However, you can't do Boolean comparisons with a NaN. In other words, they'll crash if used in an If statement. Therefore, anyone using these functions, needs to develop a practice of checking return values with the IsNan() function. This will keep you out of trouble.
Now, most of what I did is straight-forward. However, I did dip into calculating a p-value (and confidence intervals), which requires "distributions". I've leaned on the ALGLIB project to derive my PDF (probability distribution function [not portable document format]) and CDF (cumulative distrubution function) values.
The first part doesn't require this though. I've attached a complete project. If you're interested, focus first on the modSimpleStats module. Here's the part of that module that doesn't use distributions. It's stand-alone:
And here's a continuation of that module, but this part does require distributions:
And, as stated, complete "run-able" project is attached. I've also designed a bit of a user-interface just for testing. Here's a sample of that:
![Name: Stats.jpg
Views: 12
Size: 44.2 KB]()
Please feel free to make additional requests, and I'll possibly add them.
Take Care,
Elroy
Mar 05, 2018 Added the Mode calculation.
----
I've started a similar CodeBank thread before, but I'm now thinking I went too complex, as there was no interest. Just looking around earlier today, I saw a request under a CodeBank entry by The Trick. At this point, I've addressed all the requests made by CreativeDreamer.
Basically, I've just provided some one-sample statistical functions. I've also made a decision on how to handle missing values. I've struggled with this in VB6. One option is certainly the use of Variant. However, I've never been terribly happy with that option. Therefore, I've decided on sticking with Double arrays for my data, and using the IEEE Double NaN value to denote missing values. This can be seen in the code.
Now, for the uninitiated, NaN values can be a bit tricky. They're somewhat similar to the Null value, but even more restrictive. Once you get a NaN, you can continue to do math with it, but the results will be NaN (similar to Null in Variants). However, you can't do Boolean comparisons with a NaN. In other words, they'll crash if used in an If statement. Therefore, anyone using these functions, needs to develop a practice of checking return values with the IsNan() function. This will keep you out of trouble.
Now, most of what I did is straight-forward. However, I did dip into calculating a p-value (and confidence intervals), which requires "distributions". I've leaned on the ALGLIB project to derive my PDF (probability distribution function [not portable document format]) and CDF (cumulative distrubution function) values.
The first part doesn't require this though. I've attached a complete project. If you're interested, focus first on the modSimpleStats module. Here's the part of that module that doesn't use distributions. It's stand-alone:
Code:
Option Explicit
'
' List of "helper" procedures:
' NaN
' IsNaN
' ChangeMissingToNaN
' DblDims
' SortData
' FilterNaNs
'
' List is statistics procedures:
' Min
' Max
' Count
' Sum
' Mean
' Mode
' SumSq
' SumSqDiff
' VariancePop or MeanSqPop
' VarianceSamp or MeanSqSamp
' StDevPop
' StDevSamp
' StErr
' OneSampleStudentT
' OneSampleTTestPValue
' OneSampleConfInt
'
' Quantile
' Percentile
' Quartile
' Median
' Range
' InterQuartileRange
'
'
Private Declare Sub GetMem1 Lib "msvbvm60.dll" (ByRef Source As Any, ByRef Dest As Any)
Private Declare Sub GetMem2 Lib "msvbvm60.dll" (ByRef Source As Any, ByRef Dest As Any)
Private Declare Sub GetMem4 Lib "msvbvm60.dll" (ByRef Source As Any, ByRef Dest As Any)
Private Declare Sub GetMem8 Lib "msvbvm60.dll" (ByRef Source As Any, ByRef Dest As Any)
Private Declare Function ArrPtr Lib "msvbvm60.dll" Alias "VarPtr" (ptr() As Any) As Long
'
' *******************************************
' *******************************************
'
' We start with some "helper" functions.
'
' *******************************************
' *******************************************
Public Function NaN() As Double
' Math can be done on these, but nothing changes.
' They can NOT be used in "if NaN = NaN Then", or an overflow will result. Use IsNaN().
'
Const bb7 As Byte = &HF8
Const bb8 As Byte = &HFF
'
GetMem1 bb7, ByVal VarPtr(NaN) + 6&
GetMem1 bb8, ByVal VarPtr(NaN) + 7&
End Function
Public Function IsNaN(D As Double) As Boolean
' Infinity also returns TRUE, but we shouldn't be running across infinities.
'
Static bb(1 To 8) As Byte
Const bb7 As Byte = &HF0 ' High 4 bits of byte #7. \
Const bb8 As Byte = &H7F ' Low 7 bits of byte #8. / If all on, it's NaN (or Inf if all other non-sign bits are zero).
'
GetMem8 D, bb(1)
IsNaN = ((bb(7) And bb7) = bb7) And ((bb(8) And bb8) = bb8)
End Function
Public Sub FilterNaNs(dIn() As Double, dOut() As Double)
' Done as a SUB to reduce memory load.
'
Dim i As Long
Dim ptr As Long
'
Erase dOut ' Make sure we start clean.
If DblDims(dIn) <> 1 Then Exit Sub
ReDim dOut(LBound(dIn) To UBound(dIn))
ptr = LBound(dIn) - 1&
For i = LBound(dIn) To UBound(dIn)
If Not IsNaN(dIn(i)) Then
ptr = ptr + 1&
dOut(ptr) = dIn(i)
End If
Next i
If ptr < LBound(dIn) Then Erase dOut: Exit Sub ' No valid data.
If ptr <> UBound(dOut) Then ReDim Preserve dOut(LBound(dOut) To ptr)
End Sub
Public Sub ChangeMissingToNaN(D() As Double, Optional MissingValue As Double = 0&)
' This changes the array "in place" to save memory.
' Just call: ChangeMissingToNaN YourArray
' Or: Call ChangeMissingToNaN(YourArray, MissingValue)
'
Dim i As Long
'
If DblDims(D) <> 1 Then Exit Sub
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then If D(i) = MissingValue Then D(i) = NaN
Next i
End Sub
Public Function DblDims(D() As Double) As Integer
' Returns the number of dimensions in an array, or 0 if not dimmed.
' Works on both Static and Dynamic arrays.
Dim pSA As Long
'
GetMem4 ByVal ArrPtr(D), pSA
If pSA <> 0& Then GetMem2 ByVal pSA, DblDims
End Function
Public Sub SortData(D() As Double, Optional Descending As Boolean = False)
' This sort is performed "in place" with d() to preserve memory usage, so be sure to make a copy if you want to save the original order.
' Also, this sort algorithm is not designed to work with NaNs in the data, so be sure to filter them before using.
'
Dim dComp As Double
Dim dSwap As Double
'
Dim iJumps() As Long
Dim iMkr As Long
Dim iLp1 As Long
Dim iLp2 As Long
Dim iTmp As Long
Dim iJmp As Long
Dim iCnt As Long
Dim iLbd As Long
'
If DblDims(D) <> 1 Then Exit Sub ' Must be a one-dimensional array.
iCnt = UBound(D) - LBound(D) + 1&
If iCnt < 2& Then Exit Sub ' Must have something to sort.
' Setup.
iLbd = LBound(D)
ReDim iJumps(99&)
iJumps(0&) = 1&: iJumps(1&) = 4&: iJumps(2&) = 13&
iMkr = 0&
Do While iJumps(iMkr + 2&) < iCnt
iMkr = iMkr + 1&
If iMkr + 2& > UBound(iJumps) Then ReDim Preserve iJumps(LBound(iJumps) To UBound(iJumps) + 100&)
iJumps(iMkr + 2&) = 3& * iJumps(iMkr + 1&) + 1&
Loop
' We do this test here to keep speed up (not doing test in the loop).
If Descending Then
For iLp1 = iMkr To 0& Step -1&
iJmp = iJumps(iLp1)
For iLp2 = iJmp To iCnt - 1&
iTmp = iLp2 - iJmp
dComp = D(iLp2 + iLbd)
Do While dComp > D(iTmp + iLbd)
dSwap = D(iTmp + iJmp + iLbd): D(iTmp + iJmp + iLbd) = D(iTmp + iLbd): D(iTmp + iLbd) = dSwap
iTmp = iTmp - iJmp: If iTmp < 0& Then Exit Do
Loop
D(iTmp + iJmp + iLbd) = dComp
Next iLp2
Next iLp1
Else
For iLp1 = iMkr To 0& Step -1&
iJmp = iJumps(iLp1)
For iLp2 = iJmp To iCnt - 1&
iTmp = iLp2 - iJmp
dComp = D(iLp2 + iLbd)
Do While dComp < D(iTmp + iLbd)
dSwap = D(iTmp + iJmp + iLbd): D(iTmp + iJmp + iLbd) = D(iTmp + iLbd): D(iTmp + iLbd) = dSwap
iTmp = iTmp - iJmp: If iTmp < 0& Then Exit Do
Loop
D(iTmp + iJmp + iLbd) = dComp
Next iLp2
Next iLp1
End If
End Sub
' *******************************************
' *******************************************
'
' And now, just some simple statistics.
'
' *******************************************
' *******************************************
Public Function Mode(D() As Double, Optional BracketWidth As Double = 1#, Optional ModeCountOut As Long) As Double
' In some sense, the Mode is the most complex of the measures of central tendency, especially when dealing with continuous data.
' The BracketWidth is effectively a rounding directive.
' The bracket width will be the center of the bracket. For instance, with BracketWidth = 1#, brackets would be:
' -.5 to .5 : .5 to 1.5 : 1.5 to 2.5 : etcetera.
' When the mode is found, the return value will be some multiple of ModeCountOut.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
' If the distribution is bi-modal (or more), NaN is returned.
'
' The Optional ModeCountOut is an output with the number of values having the value of the mode.
' If multi-modal, this number is still returned with the count. This provides a way to see if the distribution is multi-modal.
'
Dim d2() As Double
Dim i As Long
Dim iCntNew As Double
Dim bMultiModal As Boolean
Dim dPrev As Double
'
If BracketWidth <= 0# Then Error 6
Mode = NaN
ModeCountOut = 0&
FilterNaNs D, d2
If DblDims(d2) <> 1 Then Exit Function
' Round all to bracket centers.
For i = LBound(d2) To UBound(d2)
d2(i) = Round(d2(i) / BracketWidth) * BracketWidth
Next i
SortData d2
' Find the mode.
dPrev = d2(LBound(d2))
ModeCountOut = 0&
iCntNew = 1&
For i = LBound(d2) + 1 To UBound(d2)
If d2(i) = dPrev Then
iCntNew = iCntNew + 1&
Else
Select Case iCntNew
Case Is < ModeCountOut ' We found a bracket with fewer than the previous, so reset and start again.
iCntNew = 1&
Case Is = ModeCountOut ' Might be bi-modal. Set flag and start again.
bMultiModal = True
iCntNew = 1&
Case Is > ModeCountOut ' Found a new mode. Not bi-modal. Save, and start again.
bMultiModal = False
ModeCountOut = iCntNew
iCntNew = 1&
Mode = dPrev
End Select
dPrev = d2(i)
End If
Next i
' Be sure to process the last bracket.
Select Case iCntNew
Case Is = ModeCountOut ' Bi-modal. Set flag.
bMultiModal = True
Case Is > ModeCountOut ' Found a new mode.
bMultiModal = False
ModeCountOut = iCntNew
Mode = dPrev
End Select ' If iCntNew < ModeCountOut Then we don't mess with this last bracket.
' Check for multi-modal and get out.
If bMultiModal Then Mode = NaN
End Function
Public Function Range(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim t As Double
'
t = Min(D)
If IsNaN(t) Then Range = NaN: Exit Function
Range = Max(D) - t ' If there's a Min, there has to be a Max.
End Function
Public Function InterQuartileRange(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim t As Double
'
t = Quartile(D, 1&)
If IsNaN(t) Then InterQuartileRange = NaN: Exit Function
InterQuartileRange = Quartile(D, 3&) - t ' If there's a first-quartile, there'll always be a third quartile.
End Function
Public Function Min(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim i As Long, j As Long
'
Min = NaN
If DblDims(D) <> 1 Then Exit Function
' Find a number to start with.
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then Min = D(i): Exit For
Next i
If i > UBound(D) Then Exit Function ' If we ran off the loop, there were no valid numbers.
' Now we must check the rest to make sure we've got the min.
For j = i + 1& To UBound(D)
If Not IsNaN(D(j)) Then If Min > D(j) Then Min = D(j)
Next j
End Function
Public Function Max(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim i As Long, j As Long
'
Max = NaN
If DblDims(D) <> 1 Then Exit Function
' Find a number to start with.
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then Max = D(i): Exit For
Next i
If i > UBound(D) Then Exit Function ' If we ran off the loop, there were no valid numbers.
' Now we must check the rest to make sure we've got the min.
For j = i + 1& To UBound(D)
If Not IsNaN(D(j)) Then If Max < D(j) Then Max = D(j)
Next j
End Function
Public Function ValidCount(D() As Double) As Long
' Returns 0 if not dimensioned.
' Skips any NaNs and INFs in the array.
'
Dim i As Long
'
If DblDims(D) <> 1 Then Exit Function
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then ValidCount = ValidCount + 1&
Next i
End Function
Public Function Sum(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim i As Long
Dim cnt As Long
'
If DblDims(D) <> 1 Then Sum = NaN: Exit Function
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then
cnt = cnt + 1
Sum = Sum + D(i)
End If
Next i
If cnt = 0& Then Sum = NaN
End Function
Public Function Mean(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim cnt As Long
'
cnt = ValidCount(D)
If cnt = 0& Then Mean = NaN: Exit Function
Mean = Sum(D) / cnt
End Function
Public Function Quartile(D() As Double, TheQuartile As Long) As Double
' There are three quartile cuts: 1st, 2nd (Median), and 3rd.
' Therefore, TheQuartile must = 1, 2, or 3.
'
If TheQuartile < 1& Or TheQuartile > 3& Then Error 6
Quartile = Quantile(D, TheQuartile / 4#)
End Function
Public Function Median(D() As Double) As Double
' The median is just the 50th percentile.
'
Median = Quantile(D, 0.5)
End Function
Public Function Percentile(D() As Double, Optional ThePercentile As Long = 0.5) As Double
' This is essentially the same as a Quantile, but percentages are used instead of proportions.
' Also, only integers are allowed for the percentages.
' ThePercentile must be: 0 <= CutProportion <= 100.
'
Percentile = Quantile(D, ThePercentile / 100#)
End Function
Public Function Quantile(D() As Double, Optional CutProportion As Double = 0.5) As Double
' This is essentially the same as a percentile, but it allows for any floating-point cut.
' This uses a distribution-free approach, and linear interpolation between two closest points.
' The CutProportion must be: 0 <= CutProportion <= 1.
'
Dim ds() As Double ' Don't tamper with original data sorting, so we make a copy.
Dim cnt As Long
Dim lo As Long
Dim hi As Long
Dim ptr As Double
'
If CutProportion < 0# Or CutProportion > 1# Then Error 6
FilterNaNs D, ds
If DblDims(ds) <> 1 Then Quantile = NaN: Exit Function
cnt = UBound(ds) - LBound(ds) + 1
If cnt = 1 Then Quantile = ds(LBound(ds)): Exit Function ' If cnt=1 then all quantiles are that single value.
SortData ds
'
ptr = CutProportion * (cnt - 1)
lo = Int(ptr) + LBound(ds)
hi = -Int(-ptr) + LBound(ds)
' Interpolate. This works, even if lo=hi.
Quantile = ds(lo) + (ds(hi) - ds(lo)) * (ptr + LBound(ds) - lo)
End Function
Public Function SumSq(D() As Double) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim i As Long
Dim cnt As Long
'
If DblDims(D) <> 1 Then SumSq = NaN: Exit Function
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then
cnt = cnt + 1&
SumSq = SumSq + D(i) * D(i)
End If
Next i
If cnt <> 0 Then SumSq = NaN
End Function
Public Function SumSqDiff(D() As Double) As Double
' This one is the sum-of-squared-differences-from-the-mean.
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim i As Long
Dim M As Double
'
M = Mean(D)
If IsNaN(M) Then SumSqDiff = NaN: Return
For i = LBound(D) To UBound(D)
If Not IsNaN(D(i)) Then
SumSqDiff = SumSqDiff + (D(i) - M) * (D(i) - M)
End If
Next i
End Function
Public Function VariancePop(D() As Double) As Double
' See MeanSqPop for notes.
VariancePop = MeanSqPop(D)
End Function
Public Function MeanSqPop(D() As Double) As Double
' Mean of squared differences based on POPULATION of numbers.
' This is also know as the VARIANCE.
' This one is for population (all items counted).
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
Dim cnt As Long
'
cnt = ValidCount(D)
If cnt = 0& Then MeanSqPop = NaN: Exit Function
MeanSqPop = SumSqDiff(D) / cnt
End Function
Public Function VarianceSamp(D() As Double) As Double
' See MeanSqSamp for notes.
VarianceSamp = MeanSqSamp(D)
End Function
Public Function MeanSqSamp(D() As Double) As Double
' Mean of squared differences based on SAMPLE of numbers.
' This is also know as the VARIANCE.
' This one is for sample of items (sampled from some population).
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate for SAMPLE.
'
Dim cnt As Long
'
cnt = ValidCount(D)
If cnt < 2& Then MeanSqSamp = NaN: Exit Function
MeanSqSamp = SumSqDiff(D) / (cnt - 1&)
End Function
Public Function StDevPop(D() As Double) As Double
' Standard deviation based on POPULATION of numbers.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are no valid numbers, NaN is returned.
'
StDevPop = MeanSqPop(D)
If IsNaN(StDevPop) Then Exit Function
StDevPop = Sqr(StDevPop)
End Function
Public Function StDevSamp(D() As Double) As Double
' Standard deviation based on SAMPLE of numbers.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate for SAMPLE.
'
StDevSamp = MeanSqSamp(D)
If IsNaN(StDevSamp) Then Exit Function
StDevSamp = Sqr(StDevSamp)
End Function
Public Function StErr(D() As Double) As Double
' Standard error of the mean (aka, standard error).
' This has no population equivalent.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate.
'
StErr = MeanSqSamp(D)
If IsNaN(StErr) Then Exit Function
StErr = Sqr(StErr / ValidCount(D))
End Function
Public Function OneSampleStudentT(D() As Double, Optional TestVal As Double = 0&) As Double
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate.
'
Dim se As Double
'
se = StErr(D)
If IsNaN(se) Then OneSampleStudentT = NaN: Exit Function
OneSampleStudentT = (Mean(D) - TestVal) / se
End Function
Code:
' *******************************************
' *******************************************
'
' From here down requires the distributions.
' Most of which were developed from the ALGLIB project.
'
' *******************************************
' *******************************************
Public Function OneSampleTTestPValue(d() As Double, Optional TestVal As Double = 0&, Optional Tails As Long = 2&) As Double
' A T-test can be performed either ONE-tailed or TWO-tailed.
' This returns the p value, the probability of observing these data if the null hypothesis is true.
' If you specify ONE-tailed, you should evaluate the mean, and only consider changes in ONE-DIRECTION from your TestVal as statistically significant.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate.
'
Dim t As Double
'
If Tails < 1& Or Tails > 2& Then Error 6
t = OneSampleStudentT(d, TestVal)
If IsNaN(t) Then OneSampleTTestPValue = NaN: Exit Function
OneSampleTTestPValue = (1# - StudentTCdf(t, CountN(d) - 1&)) * Tails
End Function
Public Sub OneSampleConfInt(d() As Double, LoValOut As Double, HiValOut As Double, Optional pCrit As Double = 0.05, Optional Tails As Long = 2&)
' As with a T-test, confidence intervals can be constructed either ONE-tailed or TWO-tailed.
' However, if you specify ONE-tailed, you should either use LoValOut or HiValOut, but not both.
' If TWO-tailed is specified, you would use both LoValOut and HiValOut to construct your confidence interval.
'
' pCrit is the equivalent p-value for your confidence intervals.
' For instance, for a 95% CI, we'd specify pCrit = .05.
' for a 90% CI, we'd specify pCrit = .10.
' pCrit must be in the range of 0 < pCrit < .5 for TWO-tailed; and 0 < pCrit < 1 for ONE-Tailed.
'
' Returns NaN if d() isn't dimensioned.
' Skips any NaNs and INFs in the array.
' If there are less than 2 valid numbers, NaN is returned. Valid N must be > 1 to calculate.
'
Dim cnt As Long
Dim tCrit As Double
Dim se As Double
Dim M As Double
'
' Validations.
If Tails < 1& Or Tails > 2& Then Error 6
If pCrit <= 0# Then Error 6
If pCrit >= 1# Then Error 6
If Tails = 2& And pCrit >= 0.5 Then Error 6
'
cnt = CountN(d)
If cnt < 2& Then LoValOut = NaN: HiValOut = NaN: Exit Sub
tCrit = StudentTCdfInv(1# - (pCrit / Tails), cnt - 1&)
se = StErr(d)
M = Mean(d)
'
LoValOut = M - tCrit * se
HiValOut = M + tCrit * se
End Sub
Please feel free to make additional requests, and I'll possibly add them.
Take Care,
Elroy