The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.
com/excel-vba-array/
1 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Static Array Dynamic Array
Dim arr(0 To 5) As Long Dim arr() As Long
Dim arr As Variant
See Declare above ReDim arr(0 To 5)As Variant
Dynamic Only ReDim Preserve arr(0 To 6)
arr(1) = 22 arr(1) = 22
total = arr(1) total = arr(1)
LBound(arr) LBound(arr)
Ubound(arr) Ubound(arr)
2 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Static Array Dynamic Array
For i = LBound(arr) To UBound(arr) For i = LBound(arr) To UBound(arr)
Next i Next i
Or Or
For i = LBound(arr,1) To For i = LBound(arr,1) To UBound(arr,1)
UBound(arr,1) Next i
Next i
For i = LBound(arr,1) To For i = LBound(arr,1) To UBound(arr,1)
UBound(arr,1) For j = LBound(arr,2) To UBound(arr,2)
For j = LBound(arr,2) To Next j
UBound(arr,2) Next i
Next j
Next i
Dim item As Variant Dim item As Variant
For Each item In arr For Each item In arr
Next item Next item
Sub MySub(ByRef arr() As Sub MySub(ByRef arr() As String)
String)
Function GetArray() As Function GetArray() As Long()
Long() Dim arr() As Long
Dim arr(0 To 5) As GetArray = arr
Long End Function
GetArray = arr
End Function
Dynamic only Dim arr() As Long
Arr = GetArray()
Erase arr Erase arr
*Resets all values to *Deletes array
default
Dynamic only Dim arr As Variant
arr =
Split("James:Earl:Jones",":")
Dim sName As String Dim sName As String
sName = Join(arr, ":") sName = Join(arr, ":")
3 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Static Array Dynamic Array
Dynamic only Dim arr As Variant
arr = Array("John", "Hazel",
"Fred")
Dynamic only Dim arr As Variant
arr = Range("A1:D2")
Same as Dynamic but array Dim arr As Variant
must be two dimensional Range("A5:D6") = arr
4 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
' Can only store 1 value at a time
Dim Student1 As Integer
Student1 = 55
5 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
6 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
7 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub StudentMarks()
With ThisWorkbook.Worksheets("Sheet1")
' Declare variable for each student
Dim Student1 As Integer
Dim Student2 As Integer
Dim Student3 As Integer
Dim Student4 As Integer
Dim Student5 As Integer
' Read student marks from cell
Student1 = .Range("C2").Offset(1)
Student2 = .Range("C2").Offset(2)
Student3 = .Range("C2").Offset(3)
Student4 = .Range("C2").Offset(4)
Student5 = .Range("C2").Offset(5)
' Print student marks
Debug.Print "Students Marks"
Debug.Print Student1
Debug.Print Student2
Debug.Print Student3
Debug.Print Student4
Debug.Print Student5
End With
End Sub
8 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
9 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub StudentMarksArr()
With ThisWorkbook.Worksheets("Sheet1")
' Declare an array to hold marks for 5 students
Dim Students(1 To 5) As Integer
' Read student marks from cells C3:C7 into array
Dim i As Integer
For i = 1 To 5
Students(i) = .Range("C2").Offset(i)
Next i
' Print student marks from the array
Debug.Print "Students Marks"
For i = LBound(Students) To UBound(Students)
Debug.Print Students(i)
Next i
End With
End Sub
10 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
' Variable
Dim Student As Integer
Dim Country As String
' Array
Dim Students(1 To 3) As Integer
Dim Countries(1 To 3) As String
' assign value to variable
Student1 = .Cells(1, 1)
' assign value to first item in array
Students(1) = .Cells(1, 1)
' Print variable value
Debug.Print Student1
' Print value of first student in array
Debug.Print Students(1)
11 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub DecArrayStatic()
' Create array with locations 0,1,2,3
Dim arrMarks1(0 To 3) As Long
' Defaults as 0 to 3 i.e. locations 0,1,2,3
Dim arrMarks2(3) As Long
' Create array with locations 1,2,3,4,5
Dim arrMarks1(1 To 5) As Long
' Create array with locations 2,3,4 ' This is rarely used
Dim arrMarks3(2 To 4) As Long
End Sub
12 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub DecArrayDynamic()
' Declare dynamic array
Dim arrMarks() As Long
' Set the size of the array when you are ready
ReDim arrMarks(0 To 5)
End Sub
13 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Need Help Using Arrays? Click here to get your FREE Cheat Sheet
(https://excelmacromastery.leadpages.co/leadbox
/143676f73f72a2%3A106f25298346dc/5655869022797824/)
Public Sub AssignValue()
' Declare array with locations 0,1,2,3
Dim arrMarks(0 To 3) As Long
' Set the value of position 0
arrMarks(0) = 5
' Set the value of position 3
arrMarks(3) = 46
' This is an error as there is no location 4
arrMarks(4) = 99
End Sub
14 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim arr1 As Variant
arr1 = Array("Orange", "Peach","Pear")
Dim arr2 As Variant
arr2 = Array(5, 6, 7, 8, 12)
15 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim s As String
s = "Red,Yellow,Green,Blue"
Dim arr() As String
arr = Split(s, ",")
16 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub ArrayLoops()
' Declare array
Dim arrMarks(0 To 5) As Long
' Fill the array with random numbers
Dim i As Long
For i = LBound(arrMarks) To UBound(arrMarks)
arrMarks(i) = 5 * Rnd
Next i
' Print out the values in the array
Debug.Print "Location", "Value"
For i = LBound(arrMarks) To UBound(arrMarks)
Debug.Print i, arrMarks(i)
Next i
End Sub
17 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
For Each mark In arrMarks
' Will not change the array value
mark = 5 * Rnd
Next mark
Dim mark As Variant
For Each mark In arrMarks
Debug.Print mark
Next mark
18 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub EraseStatic()
' Declare array
Dim arrMarks(0 To 3) As Long
' Fill the array with random numbers
Dim i As Long
For i = LBound(arrMarks) To UBound(arrMarks)
arrMarks(i) = 5 * Rnd
Next i
' ALL VALUES SET TO ZERO
Erase arrMarks
' Print out the values - there are all now zero
Debug.Print "Location", "Value"
For i = LBound(arrMarks) To UBound(arrMarks)
Debug.Print i, arrMarks(i)
Next i
End Sub
19 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub EraseDynamic()
' Declare array
Dim arrMarks() As Long
ReDim arrMarks(0 To 3)
' Fill the array with random numbers
Dim i As Long
For i = LBound(arrMarks) To UBound(arrMarks)
arrMarks(i) = 5 * Rnd
Next i
' arrMarks is now deallocated. No locations exist.
Erase arrMarks
End Sub
20 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub UsingRedim()
Dim arr() As String
' Set array to be slots 0 to 2
ReDim arr(0 To 2)
arr(0) = "Apple"
' Array with apple is now deleted
ReDim arr(0 To 3)
End Sub
21 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub UsingRedimPreserve()
Dim arr() As String
' Set array to be slots 0 to 1
ReDim arr(0 To 2)
arr(0) = "Apple"
arr(1) = "Orange"
arr(2) = "Pear"
' Resize and keep original contents
ReDim Preserve arr(0 To 5)
End Sub
22 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
23 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub QuickSort(arr As Variant, first As Long, last As Long)
Dim vCentreVal As Variant, vTemp As Variant
Dim lTempLow As Long
Dim lTempHi As Long
lTempLow = first
lTempHi = last
vCentreVal = arr((first + last) \ 2)
Do While lTempLow <= lTempHi
Do While arr(lTempLow) < vCentreVal And lTempLow < last
lTempLow = lTempLow + 1
Loop
Do While vCentreVal < arr(lTempHi) And lTempHi > first
lTempHi = lTempHi - 1
Loop
If lTempLow <= lTempHi Then
' Swap values
vTemp = arr(lTempLow)
arr(lTempLow) = arr(lTempHi)
arr(lTempHi) = vTemp
' Move to next positions
lTempLow = lTempLow + 1
lTempHi = lTempHi - 1
End If
Loop
If first < lTempHi Then QuickSort arr, first, lTempHi
If lTempLow < last Then QuickSort arr, lTempLow, last
24 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
End Sub
Sub TestSort()
' Create temp array
Dim arr() As Variant
arr = Array("Banana", "Melon", "Peach", "Plum", "Apple")
' Sort array
QuickSort arr, LBound(arr), UBound(arr)
' Print arr to Immediate Window(Ctrl + G)
Dim i As Long
For i = LBound(arr) To UBound(arr)
Debug.Print arr(i)
Next i
End Sub
25 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
' Passes array to a Function
Public Sub PassToProc()
Dim arr(0 To 5) As String
' Pass the array to function
UseArray arr
End Sub
Public Function UseArray(ByRef arr() As String)
' Use array
Debug.Print UBound(arr)
End Function
26 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub TestArray()
' Declare dynamic array - not allocated
Dim arr() As String
' Return new array
arr = GetArray
End Sub
Public Function GetArray() As String()
' Create and allocate new array
Dim arr(0 To 5) As String
' Return array
GetArray = arr
End Function
27 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim ArrayMarks(0 To 2,0 To 3) As Long
28 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub TwoDimArray()
' Declare a two dimensional array
Dim arrMarks(0 To 3, 0 To 2) As String
' Fill the array with text made up of i and j values
Dim i As Long, j As Long
For i = LBound(arrMarks) To UBound(arrMarks)
For j = LBound(arrMarks, 2) To UBound(arrMarks, 2)
arrMarks(i, j) = CStr(i) & ":" & CStr(j)
Next j
Next i
' Print the values in the array to the Immediate Window
Debug.Print "i", "j", "Value"
For i = LBound(arrMarks) To UBound(arrMarks)
For j = LBound(arrMarks, 2) To UBound(arrMarks, 2)
Debug.Print i, j, arrMarks(i, j)
Next j
Next i
End Sub
29 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
30 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
' Using For loop needs two loops
Debug.Print "i", "j", "Value"
For i = LBound(arrMarks) To UBound(arrMarks)
For j = LBound(arrMarks, 2) To UBound(arrMarks, 2)
Debug.Print i, j, arrMarks(i, j)
Next j
Next i
' Using For Each requires only one loop
Debug.Print "Value"
Dim mark As Variant
For Each mark In arrMarks
Debug.Print mark
Next mark
31 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub ReadToArray()
' Declare dynamic array
Dim StudentMarks As Variant
' Read values into array from first row
StudentMarks = Range("A1:Z1").Value
' Write the values back to the third row
Range("A3:Z3").Value = StudentMarks
End Sub
32 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub ReadAndDisplay()
' Get Range
Dim rg As Range
Set rg = ThisWorkbook.Worksheets("Sheet1").Range("C3:E6")
' Create dynamic array
Dim StudentMarks As Variant
' Read values into array from sheet1
StudentMarks = rg.Value
' Print the array values
Debug.Print "i", "j", "Value"
Dim i As Long, j As Long
For i = LBound(StudentMarks) To UBound(StudentMarks)
For j = LBound(StudentMarks, 2) To UBound(StudentMarks, 2)
Debug.Print i, j, StudentMarks(i, j)
Next j
Next i
End Sub
33 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
34 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Public Sub ReadToArray()
' Read values into array from first row
Dim StudentMarks As Variant
StudentMarks = Range("A1:Z20000").Value
Dim i As Long
For i = LBound(StudentMarks) To UBound(StudentMarks)
' Update marks here
StudentMarks(i, 1) = StudentMarks(i, 1) * 2
'...
Next i
' Write the new values back to the worksheet
Range("A1:Z20000").Value = StudentMarks
End Sub
35 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub UsingCellsToUpdate()
Dim c As Variant
For Each c In Range("A1:Z20000")
c.Value = ' Update values here
Next c
End Sub
' Assigning - this is faster
Range("A1:A10").Value = Range("B1:B10").Value
' Copy Paste - this is slower
Range("B1:B1").Copy Destination:=Range("A1:A10")
36 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Need Help Using Arrays? Click here to get your FREE Cheat Sheet
(https://excelmacromastery.leadpages.co/leadbox
/145f1cd73f72a2%3A106f25298346dc/5669544198668288/)
37 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
38 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
39 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub JaggedArray()
' Declare main array
Dim Class() As Variant
' Declare sub arrays
Dim Students1() As String
Dim Students2() As String
Dim Students3() As String
ReDim Class(0 To 2)
' Set the different sizes
ReDim Students1(0 To 15)
ReDim Students2(0 To 6)
ReDim Students3(0 To 12)
Class(0) = Students1
Class(1) = Students2
Class(2) = Students3
' Put row and column number into array
Dim i As Long, j As Long
For i = LBound(Class) To UBound(Class)
For j = LBound(Class(i)) To UBound(Class(i))
Class(i)(j) = CStr(i) & ":" & CStr(j)
Next j
Next i
' Print out to worksheet called "Sheet1"
For i = LBound(Class) To UBound(Class)
For j = LBound(Class(i)) To UBound(Class(i))
Sheet1.Cells(i + 1, j + 2) = Class(i)(j)
Next j
Next i
End Sub
40 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
41 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub Test()
' Call the Display function with a range argument
Display ActiveSheet.Range("A1:D1")
End Sub
Sub Display(rg As Range)
End Sub
42 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
43 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
44 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim Translate(1 To 2) As Variant
Translate(1) = Array("Dog", "Perro")
Translate(2) = Array("Cat", "Cato")
45 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
46 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
47 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim arr As Variant
' Range range values to array
arr = Sheet1.Range("A1:A10000")
Dim i As Long, j As Long
' Change values in array
For i = LBound(arr) To UBound(arr)
arr(i, 1) = Left(arr(i, 1), 10)
Next i
' Writte array values to range
Sheet1.Range("A1:A10000") = arr
48 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim numbers As Variant
numbers = Array(1, 2, 4, 5)
49 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
50 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim rg As Range
Set rg = Sheet2.Range("a1:f20")
With Sheet2
Debug.Print WorksheetFunction.SumIf(rg, "John"
End With
51 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
52 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
53 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
54 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
55 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
56 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim c As Variant
For Each c In Sheet1.Range("A1:A10")
' DOES NOT change the value
c = 6
' CHANGES the value
c.Value = 6
Next c
57 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
58 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
59 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
60 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub SortArray()
Dim arr As Variant, val As Variant
arr = Sheet1.Range("A1:A20").Value
Dim i As Long, j As Long
For i = LBound(arr, 1) To UBound(arr, 1) - 1
For j = i + 1 To UBound(arr, 1)
If arr(i, 1) > arr(j, 1) Then
val = arr(i, 1)
arr(i, 1) = arr(j, 1)
arr(j, 1) = val
End If
Next j
Next i
Sheet1.Range("D1:D20").Value = arr
End Sub
61 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
62 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim rg As Range
Set rg = Sheet1.Range("A1:E5")
Dim rgLine As Range
' Calculate columns
For Each rgLine In rg.Columns
Debug.Print WorksheetFunction.Sum(rgLine)
Next
' Calculate rows
For Each rgLine In rg.Rows
Debug.Print WorksheetFunction.Sum(rgLine)
Next
63 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
64 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
65 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
66 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
67 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
68 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub MakeBold()
Dim dict As Object
Set dict = CreateObject("Scripting.Dictionary"
dict("A") = 1
Dim sItem As String, i As Long
' Go through sheet
For i = 1 To 100
sItem = Sheet1.Range("A" & i)
' Check exists in a dictionary
If dict.Exists(sItem) Then
Sheet1.Range("A" & i).Font.Bold =
End If
Next
End Sub
69 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim arr As Variant
arr = Sheet1.Range("A1:F2")
Dim arr2 As Variant
arr2 = WorksheetFunction.Transpose(arr)
70 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
71 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
72 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
73 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
74 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
75 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
76 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim rg As Range
Set rg = Sheet1.Range("D5:e9").SpecialCells(xlCellTypeVi
Dim mainarr As Variant, arr As Variant
' Go through the range areas
For Each rgCur In rg.Areas
' Put current area in array
arr = rgCur.Value
' Merge array to new array
mainarr = MergeArrays(mainarr, arr)
Next
Function MargeArrays(mainarr As varaiant, arr
' create merge array code here
End Function
77 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
78 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
79 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
80 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
81 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
82 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
83 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
84 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
85 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
86 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
87 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
88 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
89 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim bBigger As Boolean
bBigger = True
Dim i As Long
For i = LBound(x) To UBound(x)
If x(i) >= y Then
bBigger = False
Exit For
End If
Next i
Debug.Print "Is y bigger? :" & bBigger
90 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
91 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
92 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
93 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
94 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
95 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
96 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Dim i As Long
For i = 1 To 5
Sheet1.Range("B" & i).Characters(Start:=3,
Next i
97 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
98 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub Compare()
' Get workbook
Dim wk1 As Workbook, wk2 As Workbook
Set wk1 = Workbooks.Open("c:\docs\book1.xlsx"
Set wk2 = Workbooks.Open("c:\docs\book2.xlsx"
' get worksheet
Dim sh1 As Worksheet, sh2 As Worksheet
Set sh1 = wk1.Worksheets("Sheet1")
Set sh2 = wk1.Worksheets("Sheet1")
Dim i As Long
For i = 1 To 100
' Compare cells
If sh1.Range("A" & i) = sh2.Range("A" & i)
' add code here to write value to details
End If
Next
End Sub
99 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
100 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
Sub CountNumbers()
' Create dictionary
Dim dict As Object
Set dict = CreateObject("Scripting.Dictionary"
' Read values to array - quicker to read through
Dim arr As Variant
arr = Sheet1.Range("A1:A30000")
' Read through the array
Dim i As Long
For i = LBound(arr) To UBound(arr)
' Add current number to dictionary
dict(arr(i, 1)) = dict(arr(i, 1)) + 1
Next i
' Print results to Immediate
PrintDictionary dict
End Sub
' Print the Dictionary to the Immediate Window
Sub PrintDictionary(dict As Object)
Dim key As Variant
For Each key In dict
Debug.Print key, dict(key)
Next
End Sub
101 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
102 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
103 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
104 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
105 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
106 of 107 6/12/17, 1:12 PM
The Complete Guide to Using Arrays in Excel VBA - Excel Macro Mastery https://excelmacromastery.com/excel-vba-array/
107 of 107 6/12/17, 1:12 PM