Summing Dynamically Varying Columns using VBA - excel

I need to calculate the sum of values in each column and store it in an array. Please note that the number of columns are not fixed. It varies dynamically. This is where I am totally stuck. This is just a part of a huge function I am writing.
In the below code, the "Column H" that I am summing is a variable one. I mean the number of columns to calculate sum is based on the value of Val(i).
For Eg: If Val(0) = 10, then I need to calculate sum of all numbers starting from column H till column Q, and storing sum of each column in an array, i.e.sum(0) = sum of column H; sum(1) = sum of column I; and so on.
The point where I am stuck is to increment the column, i.e. after summing "Column H" in the next iteration it should sum elements in "column I"----> (Sum(i + k) = Application.WorksheetFunction.Sum(Range("H2"))
I have tried something like below:
Dim i, j, k, l, MaxVal As Integer
Dim objNewSheet As Worksheet
Dim Sum(0 To 1000) As Double
k = 0
For i = 0 To (MaxVal-1)
Set objNewSheet = ActiveWorkbook.Sheets("Sheet" & (i+1))
objNewSheet.Select
For j = 0 To Val(i)
Sum(i + k) = Application.WorksheetFunction.Sum(Range("H2"))
k = k + j
Next j
Next i

As Tim mentions, you can use the Resize method to modify the size of your Range.
Dim rng as Range: Set rng = Range("H2")
Sum(i + k) = Application.WorksheetFunction.Sum(rng.Resize(1, j))
The above should create a new range that is j columns wide.
I add a Range variable because they are easier to work with (IMO) that the constants like Range("H2"). You can use MsgBox rng.Resize(1,j).Address to view the new range's address.
Here are a few other points you may want to consider:
You have not declared your variables correctly, unless you truly
intend for i, j, k, l as Variant. You could do:
Dim i#, j#, k#, l#, MaxValue# (shorthand notation) or
Dim i as Integer, j as Integer, k as Integer, l as Integer, MaxValue as Integer
Otherwise, unless you specify a type for each variable, they will be Variant.
For readability, you may want to avoid naming variables after reserved or semi-reserved keywords or existing functions like Sum. I would rename that variable to mySum or sumArray or something else which will obviously indicate to future users that this is a variable, not a function.
I mention in my comment above that initially dimensioning your array variable with an upper-bound of 1000 is kind of clunky, and will obviously fail if you ever encounter a need for a larger array. This may not be the case, but it's still a clunky way of dimensioning an array. I would suggest Dim mySum() as Double and then ReDim the variable later in the code, perhaps using ReDim Preserve if it needs to be truly dynamic at run-time.
UPDATE
Here is a simple example, your code is only a snippet/incomplete, so I cannot use it, but this example should illustrate how this works.
Option Base 1
Sub Test()
Dim i As Integer
Dim rng As Range
Dim mySum() As Double
'## The initial range ##'
Set rng = Range("H2")
'## Do an iterative loop ##'
For i = 1 To 4
'## Resize the range within the iteration ##'
Set rng = rng.Resize(1, i) '<-- change the 1 in this line to the number of rows in the column that needs to be summed'
'## Ensure the array is properly dimensioned ##'
ReDim Preserve mySum(i)
'## Store the calculation in the array ##'
mySum(i) = Application.WorksheetFunction.Sum(rng)
Next
End Sub

Related

VBA "Variable required. Can't assign to this expression" error - Goal-seek analysis

I'm a beginner with VBA and by no means a programmer. I am trying to write a macro which iterates through cells in a row and carries out goal-seek analysis on multiple cells. I could not use any built-in functions from Excel because goal-seek analysis is only possible for one cell and not many.
My macro should iterate through a specific range of cells in a row (from columns A to E) while carrying out goal-seek analysis. I could not get this to work without a loop or through using something like For Each Row In Range so I tried creating an array of letters for the second loop to work.
However, when I run the program I get a "Variable required. Can't assign to this expression" error. Could someone point out what I'm doing wrong or if I could do something more efficiently?
Thank you
Sub CommandButton1_Click()
Dim c As String
c = "ABCDE"
'Create array of letters to iterate through cells in a row
Dim i, j As Long
Dim c_array() As String
ReDim c_array(Len(c) - 1)
For j = 1 To Len(c)
c_array(j - 1) = Mid$(c, j, 1)
Next
'Goal seek analysis
For i = 0 To (Len(c_array) - 1)
Cells(3, c_array(i)).GoalSeek Goal:=Cells(2, "G"), ChangingCell:=Cells(2, c_array(i))
Next i
End Sub
Dim i, j As Long does only declare j As Long but i As Variant. In VBA you need to specify a type for every variable:
Dim i As Long, j As Long
The issue you get is Len(c_array) where it is defined as array Dim c_array() As String. Len does not work with arrays. If you want to know the upper or lower bound of the array you need to use LBound and Ubound:
For i = LBound(c_array) To UBound(c_array)
But actually there is no need to put the data into an array. You can use the string directly:
Const c As String = "ABCD"
Dim i As Long
For i = 1 To Len(c)
Dim Col As String
Col = Mid$(c, i, 1)
Cells(3, Col).GoalSeek Goal:=Cells(2, "G"), ChangingCell:=Cells(2, Col)
Next i
Or even better use column numbers instead of their letters if they are consecutive.
ABCD is column 1 to 4:
Dim iCol As Long
For iCol = 1 To 4
Cells(3, iCol).GoalSeek Goal:=Cells(2, "G"), ChangingCell:=Cells(2, iCol)
Next iCol

How to count number of occurrences of a value and the value of adjacent cell in a range

Edit: This question has been re-worked to provide better clarity of my problem.
There's 2 factors to my question.
First Factor: I have a validation list in a sheet called "Admin Sheet". In that list are 'Tasks'.
I would like to cross reference those tasks in the "list", against those contained in a range (rangeString) taken from another sheet and count the number of 'Occurrences' for each item.
i.e. Task 1 appears 3 times, Task 2 appears 1 time, etc etc..
Factor 2: For each item within the list I would also like to gather the number of 'Hours' spent on that task.
For example:
Task 1 may appear 3 times on 3 different rows within the range. On each row in another column are the hours spent on that particular task. I would like to 'Sum' those hours from the 3 rows and I'd like to do this for all the 'Tasks'.
Note: The range is variable and will change daily.
Note: The columns that contain the info are: 'F' - Tasks and 'K' for Hours.
My current attempt at just capturing 'one' Task and its Hours associated with it:
Dim PaintWWArray() As Variant
Dim PHoursCnt As Long
Set srchRng = ActiveSheet.Range(rangeString)
Set rngfindValue = srchRng.find(what:="AD PAINTING W/W", Lookat:=xlPart)
'Find all the Tasks and Hours
If Not rngfindValue Is Nothing Then
rngFirstAddress = rngfindValue.Address
Do
PaintWWCnt = PaintWWCnt + 1
PHoursCnt = rngfindValue.Offset(0, 4).Value
ReDim Preserve PaintWWArray(PHoursCnt)
PaintWWArray(PHoursCnt) = PHoursCnt
Set rngfindValue = srchRng.FindNext(rngfindValue)
Loop Until rngfindValue Is Nothing Or rngfindValue.Address = rngFirstAddress
PWWSum = Application.WorksheetFunction.Sum(PaintWWArray)
MsgBox PWWSum
End If
Once I have collected the number of 'Occurrences' for each Task and the Sum of the hours for each task, I want to pass them into another sheet.
Worksheets("Weekly Data").Range("C6").Value = PaintWWCnt
Worksheets("Weekly Data").Range("D6").Value = PWWSum
I hope this is clearer...
I would suggest using a Dictionary.
Assuming you want to count all words:
Dim myDict
Set myDict = CreateObject("Scripting.Dictionary")
' Go through the array
For Each addDuty In arr
' If you only want to count specific words, add in IF statement here
myDict(addDuty) = myDict(addDuty) + 1
Next addDuty
If you only want to count words in an exiting set, it becomes slightly more elaborate.
It's not entirely clear what you want to achieve but the code below should give you the data you need. It's very fast. Please try it.
Private Sub STO_Answer()
' 024
' this procedure requires a reference to be set to
' Microsoft Scripting Runtime
Dim Counter As Scripting.Dictionary ' store task names and their count
Dim Arr As Variant ' an array of the data in Rng
Dim CellVal As Variant ' temporary storage of each cell value
Dim R As Long ' row counter
Dim Key As Variant ' a dictionary Key
Arr = ActiveSheet.Range("C2:D27").Value ' change to name the sheet
' adjust the range to suit
Set Counter = New Scripting.Dictionary
With Counter
For R = 1 To UBound(Arr) ' loop through all rows
AddToCounter Arr(R, 1), Counter ' first column of cell range
AddToCounter Arr(R, 2), Counter ' second column of cell range
Next R
For Each Key In Counter.Keys
Debug.Print Key, Counter.Item(Key)
Next Key
End With
End Sub
Private Sub AddToCounter(CellVal As Variant, _
Counter As Scripting.Dictionary)
' 024
With Counter
If .Exists(CellVal) Then
.Item(CellVal) = .Item(CellVal) + 1
Else
.Add CellVal, 1
End If
End With
End Sub
A Dictionary is a data structure which holds two related values. Here it's used to hold the task name and the number of times it occurs. Make sure you enable the reference to Microsoft Scripting Runtime in Tools > References. You don't specify if there is any relationship- between the tasks in the first column and the second. The above code counts both independently for now.
The result is printed to the Immediate Window. Of course, you might use this result in any other way in your code. Your question doesn't cover your intentions.
You won't be able to escape from the necessity to present your count in some way forever. As it turns out, there is only one efficient way to do it. This one:-
All duties are in column A and all added duties are in row 2.
Of course, you might use rather elaborate VBA to do the counting but Excel has a better way using a worksheet function. In order to set up COUNTIF() to work I created two named ranges as follows.
["Duties"] =OFFSET(Sheet2!$C$2,0,0,COUNTA(Sheet2!$C:$C)-1)
and
["AddDuties"] =OFFSET(Duties,0,1)
Sheet2!$C$2 is where my data started. Replace with the first cell of the first column of your data range. COUNTA(Sheet2!$C:$C)-1 makes this range dynamic. The function counts how many entries there are in that same column, -1 because the count would include a caption (modify if you have more or fewer headers).
AddDuties is simply defined as "same as Duties" but removed by one column to the right. You could move it elsewhere. As you add or delete rows in the column of Duties, AddDuties expands or contracts right along.
Now the formula in B3 is shown below. It's copied down and across as required. Please observe the $ signs.
[B3] =COUNTIFS(Duties,$A3,AddDuties,B$2)
This will probably generate a lot of zeroes. It did in my example and I didn't like them. Therefore I formatted B3 with the Custom cell format 0;; before copying to the other cells, which hides them.
Now this list would automatically update as you make entries in your data. You will never have to run code and the list will always be ready.
Finally, one recommendation. All your added duties, like "AD PAINITNG H/R", are hard to type correctly. Therefore the user should select them from a validation drop-down when entering them in the data. Most probably, you already have a list somewhere which feeds such drop-downs. The captions in the count list must be taken from the same source. But that creates redundancy. The better way is to make the list in B2:H2 of the count list the "original". Name the range and make it dynamic and you will never have to think about this subject again.
i think a better approach would be to use for each loops, this way you won't have to hardcode the conditions via IfElse. If you have the values in column A of a sheet and wants to go through those values and get their adjacent value in column B, you can use For Each looping to go through each values defined in A to get B.
just to add, regarding on counting of occurrence, you can define a counter that would add up for each occurrence of a unique value in column A.
I do not have time to wait for clarifications I asked... I prepared a piece of code, starting from the assumption that your strings to be counted are in column "F:F", and the value to be calculated is in column "K:K". The processing result is dropped on the last available column of the active pages, starting from row 2. If you prefer some relevant headers for the two involved columns, this can be easily automated. I used "Tasks and "Time...
It is able to deal with as many 'task' strings you will have in the future.
I commented the code lines, where I thought you do not understand what they do:
Sub CountOccurrencesAndValues()
Dim sh As Worksheet, rngF As Range, arrOcc As Variant, lastRow As Long, lastCol As Long
Dim arr As Variant, arrFin As Variant, countI As Long, valH As Double, j As Long, k As Long, i As Long
Set sh = ActiveSheet
lastRow = sh.Range("F" & Rows.count).End(xlUp).Row
lastCol = sh.UsedRange.Columns.count + 1
Set rngF = sh.Range("F2:F" & lastRow) 'the range where from to extract the unique values
arr = sh.Range("F2:K" & lastRow) 'the array to be processed
'Extract the unique values. Use for that a not used column:
rngF.AdvancedFilter Action:=xlFilterCopy, CopyToRange:=sh.Cells(1, lastCol), Unique:=True
'Put the unique values (sttrings) in an array:
arrOcc = sh.Range(sh.Cells(1, lastCol), sh.Cells(sh.Cells(Rows.count, lastCol).End(xlUp).Row, lastCol)).value
'Clear the temporary used array:
sh.Range(sh.Cells(1, lastCol), sh.Cells(sh.Cells(Rows.count, lastCol).End(xlUp).Row, lastCol)).Clear
ReDim arrFin(1 To UBound(arrOcc, 1), 1 To 3)
k = 1
'Processing the range by iteration:
For i = 1 To UBound(arrOcc, 1)
For j = 1 To UBound(arr, 1)
If arr(j, 1) = arrOcc(i, 1) Then
'count the occurrences and the value
countI = countI + 1: valH = valH + arr(j, 6)
End If
Next j
'put the data in the final array
arrFin(k, 1) = arrOcc(i, 1): arrFin(k, 2) = countI: arrFin(k, 3) = valH
countI = 0: valH = 0: k = k + 1
Next i
'Drop the data from array in the last available column:
'sh.Cells(1, lastCol).value = "Tasks": sh.Cells(1, lastCol + 1).value = "Count": sh.Cells(1, lastCol + 2).value = "Time"
'sh.Cells(2, lastCol).Resize(UBound(arrFin, 1), UBound(arrFin, 2)).value = arrFin
Dim ws As Worksheet
Set ws = Worksheets("Weekly Data")
'Drop the data from array in "Weekly Data" worksheet:
ws.Range("C6").value = "Tasks": ws.Range("D6").value = "Count": ws.Range("E6").value = "Time"
ws.Range("C7").Resize(UBound(arrFin, 1), UBound(arrFin, 2)).value = arrFin
End Sub

Non-contiguous For Each loop per row instead of column

I have a non-contiguous selection spanning rows and columns, and I want to do a For Each loop on it. Excel VBA does this by looping firstly down column 1, then 2,3 etc.; but I want it to loop along the row first instead.
(My sheet looks something like the picture below, I need to loop down the selection (version) each column in turn, and retrieve the Doc. No. and other information. The number of rows and version columns in the sheet is not fixed).
Short of writing a fairly large Sort function and creating an array of references, I was wondering if there was a 'built-in' way to do this?
I don't need code, just an explanation.
The order in which a For Each iterates an object collection is implementation-dependent (IOW blame Excel, not VBA) and, while likely deterministic & predictable, there is nothing in its specification that guarantees a specific iteration order. So VBA code written to iterate an object collection, should not be written with the assumption of a specific iteration order, since that's something that can very well change between versions of the type library involved (here Excel's).
It's very unclear what the shape of your Range / Selection is, but if you need to iterate the selected cells in a specific order, then a For Each loop should not be used, at least not for iterating the cells per se.
Since the ranges are not contiguous, the Range will have multiple Areas; you'll want to iterate the Selection.Areas, and for each selected area, iterate the cells in a particular order. For Each is, by far, the most efficient way to iterate an object collection, which Range.Areas is.
Debug.Assert TypeOf Selection Is Excel.Range
Dim currentArea As Range
For Each currentArea In Selection.Areas
'todo
Next
Instead of nesting the loops, make a separate procedure that takes the currentArea as a parameter - that procedure is where you'll be iterating the individual cells:
Private Sub ProcessContiguousArea(ByVal area As Range)
Dim currentRow As Long
For currentRow = 1 To area.Rows.Count
Debug.Print area.Cells(currentRow, 1).Address
Next
End Sub
Now the outer loop looks like this:
Debug.Assert TypeOf Selection Is Excel.Range
Dim currentArea As Range
For Each currentArea In Selection.Areas
ProcessContiguousArea currentArea
Next
The ProcessContiguousArea procedure is free to do whatever it needs to do with a given contiguous area, using a For loop to iterate the range by rows, without needing to care for the actual address of the selected area: using Range.Cells(RowIndex, ColumnIndex), row 1 / column 1 represents the top-left cell of that range, regardless of where that range is located in the worksheet.
Non-selected cells can be accessed with Range.Offset:
Debug.Print area.Cells(currentRow, 1).Offset(ColumnOffset:=10).Address
The top-left cell's row of the area on the worksheet is returned by area.Row, and the top-left cell's column of the area on the worksheet is retrieved with area.Column.
Non-Contiguous
By looping through the rows first (i), you will get the 'By Row sequence' e.g. A1,B1,C1, ...
The Code
Sub NonContiguous()
Dim i As Long
Dim j As Long
Dim k As Long
With Selection
For k = 1 To .Areas.Count
With .Areas(k)
For i = .Row To .Rows.Count + .Row - 1
For j = .Column To .Columns.Count + .Column - 1
Debug.Print .Parent.Cells(i, j).Address & " = " _
& .Parent.Cells(i, j)
Next
Next
End With
Next
End With
End Sub
This is based on urdearboy's suggestion:
1. loop over columns
2. within a column, loop over cells
Sub disjoint()
Dim r As Range, rInt As Range
Dim nLastColumn As Long
Dim nFirstColumn As Long, msg As String
Dim N As Long
Set r = Range("C3,C9,E6,E13,E15,G1,G2,G3,G4")
nFirstColumn = Columns.Count
nLastColumn = 0
msg = ""
For Each rr In r
N = rr.Column
If N < nFirstColumn Then nFirstColumn = N
If N > nLastColumn Then nLastColumn = N
Next rr
For N = nFirstColumn To nLastColumn
Set rInt = Intersect(Columns(N), r)
If rInt Is Nothing Then
Else
For Each rr In rInt
msg = msg & vbCrLf & rr.Address(0, 0)
Next rr
End If
Next N
MsgBox msg
End Sub

How to assign an Excel Range to a 2D array?

Could you please say- how a Excel Range("G2:AA1000") can be assigned to a 2D array? If possible how to return back that 2D array to the same range after performing some operation on that 2D array?After assignment a Range to an 2D array,How each row will be identified from that 2D matrix?
Thanks,
There is an easy way to make changes to an area using an array, and write it out to the same place, or somewhere else.
This example code will copy data from one area to another, using an array:
Sub example()
Dim testdata()
testdata = Range("A1:B13")
Range("D1:E13") = testdata ' simple copy
Range("G1") = testdata ' copy only 1 cell
Range("I1:K22") = testdata 'try to copy too much
End Sub
The testdata array starts from 1, and will extend to the number of columns and rows specified in the range. In this case, testdata(1,1) refers to the data obtained from A1, testdata(1,2) refers to B1, finishing up with testdata(13,1) referring to A13, and testdata(13,2) referring to B13.
Setting the range equal to the array in the next line copies the array into the specified location.
If the area is smaller than the original array, it will copy only enough of the array to fill that space, so Range("D1")=testdata will only place one cell on the sheet.
If you specify a larger area, then #N/A will fill the area that is not in the space covered by array elements, so Range("A1:A3")=testdata will fill A1 and A2 with data from the array, but A3 will have #N/A
Result of example program:
Note: A1:B13 is the original data, which gets copied with the subsequent range(??)=testdata
Here's a worked-out example of reading a range of data from a worksheet, operating on the array, and then writing it back out to the same worksheet.
Sub RangeArray()
Dim Rng As Range
Dim Arr()
Dim ArrItem
Dim i As Long, j As Long
Dim rUB as Long, cUB as Long
Set Rng = Worksheets("Sheet1").Range("A1:G19")
rUB = Rng.Rows.Count 'Row upper bound
cUB = Rng.Columns.Count ' Column upper bound
ReDim Arr(1 To rUB, 1 To cUB)
'Read worksheet range into array
For i = 1 To rUB
For j = 1 to cUB
Arr(i, j) = Rng.Cells(i, j).Value
Next
Next
'Do something to array
For i = 1 To rUB
For j = 1 To cUB
If i <> j Then
Arr(i, j) = Arr(i, j) / (i * j)
End If
Next
Next
'Write array back to worksheet
Set Rng = Worksheets("Sheet1").Range("I1")
For i = 1 To rUB
For j = 1 To cUB
Rng.Offset(i - 1, j - 1).Value = Arr(i, j)
Next
Next
End Sub
Yes, an Excel range can be assigned to a 2D array in one single assignment. In C++/CLI it looks like this:
cli::array<Object^, 2>^ arrData = safe_cast<cli::array<Object^, 2>^>(rg->Value[Excel::XlRangeValueDataType::xlRangeValueDefault]);
In c# or visual basic it would look considerably simpler (see here for example https://www.automateexcel.com/vba/assign-range-to-array/, btw in dotnet the object is now playing the role of the variant data type). Note that it must be a two dimensional array and the returned array has a one-based indexing, and not a zero based indexing.
For large data sets this method is a lot faster than the looping. The looping generates lots of COM objects. I compared the two methods with a 33000 row Excel range and the data import into the array was almost instantaneous while with the looping it took very long and it heated up the CPU.
One way to loop through a range is to use the For...Next loop with the Cells property. Using the Cells property, you can substitute the loop counter (or other variables or expressions) for the cell index numbers. In the following example, the variable counter is substituted for the row index. The procedure loops through the range C1:C20, setting to 0 (zero) any number whose absolute value is less than 0.01.
Sub RoundToZero1()
For Counter = 1 To 20
Set curCell = Worksheets("Sheet1").Cells(Counter, 3)
If Abs(curCell.Value) < 0.01 Then curCell.Value = 0
Next Counter
End Sub

Excel MAXIF function or emulation?

I have a moderately sized dataset in excel from which I wish to extract the maximum value of the values in Column B, but those that correspond only to cells in Column A that satisfy certain criteria.
The desired functionality is similar to that of SUMIF or COUNTIF, but neither of those return data that is necessary. There isn't a MAXIF function; how do I emulate one?
You can use an array formula.In the cell in which you want the max calculated enter: =Max(If([test],[if true],[if false]) where you replace the values in square brackets with the test, what to return if true and what to return if false. For example:
=MAX(IF(MOD(A2:A25,2)=0,A2:A25,0)
In this formula I return the value in column A if the value divided by 2 has no remainder. Notice that I use a range of cells in my comparison and in the value if false rather than a single cell.
Now, while still editing the cell, hit Ctrl+Shift+Enter (hold down the Ctrl key and the Shift together and then hit enter).
This creates an array formula that acts on each value in the range.
EDIT BTW, did you want to do this programmatically or manually? If programmatically, then what environment are you using? VBA? C#?
EDIT If via VBA, you need to use the FormulaArray property and R1C1 references like so:
Range("A1").Select
Selection.FormulaArray = "=MAX(IF(MOD(R[1]C:R[24]C,2)=0,R[1]C:R[24]C,0))"
Array formulas don't work very well when you want to use dynamic or named ranges (e.g., "the maximum amount due for rows above the current row that have the same counterparty as the current row). If you don't want to use an array formula, you can always resort to VBA to do something like this:
Function maxIfs(maxRange As Range, criteriaRange As Range, criterion As Variant) As Variant
maxIfs = Empty
For i = 1 To maxRange.Cells.Count
If criteriaRange.Cells(i).Value = criterion Then
If maxIfs = Empty Then
maxIfs = maxRange.Cells(i).Value
Else
maxIfs = Application.WorksheetFunction.Max(maxIfs, maxRange.Cells(i).Value)
End If
End If
Next
End Function
A limitation with the code provided thus far is that you are restricted to 2 conditions. I decided to take this code further to not restrict the number of conditions for the MaxIfs function. Please see the code here:
Function MaxIfs(MaxRange As Range, ParamArray Criteria() As Variant) As Variant
Dim n As Long
Dim i As Long
Dim c As Long
Dim f As Boolean
Dim w() As Long
Dim k As Long
Dim z As Variant
'Error if less than 1 criteria
On Error GoTo ErrHandler
n = UBound(Criteria)
If n < 1 Then
'too few criteria
GoTo ErrHandler
End If
'Define k
k = 0
'Loop through cells of max range
For i = 1 To MaxRange.Count
'Start by assuming there is a match
f = True
'Loop through conditions
For c = 0 To n - 1 Step 2
'Does cell in criteria range match condition?
If Criteria(c).Cells(i).Value <> Criteria(c + 1) Then
f = False
End If
Next c
'Define z
z = MaxRange
'Were all criteria satisfied?
If f Then
k = k + 1
ReDim Preserve w(k)
w(k) = z(i, 1)
End If
Next i
MaxIfs = Application.Max(w)
Exit Function
ErrHandler:
MaxIfs = CVErr(xlErrValue)
End Function
This code allows 1 to multiple conditions.
This code was developed with reference to multiple code posted by Hans V over at Eileen's Lounge.
Happy coding
Diedrich

Resources