Anda di halaman 1dari 14

Getting ready to code

First you’ll need to open Excel Options from the main menu, go to Popular and enable
the Developer tab.
Once you’ve done that, click the Developer tab in the ribbon, and click the Visual Basic button on
the left to open the VBA editor. To make formulas that can be used by the whole workbook,
you’ll want to place your code in the Modules folder in the left-hand pane.
Excel specifics
Creating Normal and Array formulas
To create a formula which returns a single value, create a function thus:

Public Function MyFormula() As Variant


MyFormula = 123
End Function

The Variant specifier is the type of value to return. Variant essentially means any type; if you
want to limit the formula to return a specific type, you can change it, eg.:
Public Function MyFormula() As Currency

Public Function MyFormula() As String

VBA in Excel provides a raft of types such as Currency which are tailored to typical Excel usage
scenarios.
As you can see above, you set the result (return value) of the formula by assigning it to the
function name itself, ie.

MyFormula = 123

when the function is named MyFormula.


If you are making an array formula, you will need to return several values and they must be of
the Variant type:
Public Function MyArrayFormula() As Variant()

Dim Result(1 To 2) As Variant

Result(1) = 123
Result(2) = 456

MyArrayFormula = Result

End Function

Notice that the function declaration uses parentheses (Variant()) after the type specifier to
denote that we will be returning multiple values. By changing the value after To in
the Dimstatement, you can specify how many values to return, and of course, when you place
the array formula in the spreadsheet, you must ensure you select the same number of cells as
there are returned values otherwise an error will occur.
Placing the formula in the spreadsheet
Using the code above, you can enter text such as =MyFormula() into a cell to use the formula
you have created.
To place an array formula:

1. Select the cells you want to use for the results


2. Type in the formula
3. Press CTRL+SHIFT+ENTER
Passing values to a formula
The input value the formula accepts go in the function definition. For example, to pass a string:

Public Function MyFormula(ByVal someText As String) As Variant

To use multiple inputs, separate them with commas:

Public Function MyFormula(ByVal someText As String, ByVal somePrice As


Currency) As Variant

Notice that you can use cell references when you place the formula, eg. =MyFormula(A2, A3)and
they will be converted to a String and a Currency in the example above. If the cell values cannot
be converted, a type mismatch error will occur. If you don’t care what type of data is in the
cells, use Variant:
Public Function MyFormula(ByVal firstItem As Variant, ByVal secondItem As
Variant) As Variant

Passing cell references


Use the Range type to pass a reference to a single cell or a rectangular selection of cells
(including single rows and columns):
Public Function MyFormula(SomeCell as Range) As Variant

Note that you do not use ByVal here as we want the cell reference directly.
Getting the value of a cell reference
If your Range variable refers to a single cell, use the Value property to fetch its contents:
Public Function Add(firstCell As Range, secondCell As Range) As Variant
Add = firstCell.Value + secondCell.Value
End Function

Defining cell references in code


Define ranges as follows:

Dim myRange As Range


Set myRange = Range("A1:Z100")

Notice this will refer to the currently active worksheet (see below for how to access any
worksheet). Also note that we use the Set statement here as is required by VBA when setting
the value of an object rather than a simple type such as Integer.
Getting the values of all the cells in a range
You can iterate over all the cells in a range like this:

Dim singleCell as Range

For Each singleCell In MyRange


(do something with singleCell.Value)
Next singleCell

Referring to specific worksheets


Use the Sheets object to access a named worksheet:
Dim myRange As Range
Set myRange = Sheets("Some Worksheet").Range("A1:Z100")

You can also use the shortcut syntax:

Dim myRange As Range


Set myRange = Range("'Some Worksheet'!A1:Z100")

Referring to named ranges


This is very simple!

Dim myRange As Range


Set myRange = Sheets("My Worksheet").Range("SomeNamedRange")

Referring to tables and table columns


The header row of a table defines the column names, so if you have a table called Productswith
a column called Price you can fetch all the prices (all the cells in the Price column of the table) as
follows:
Dim myRange As Range
Set myRange = Sheets("My Worksheet").Range("Products[Price]")

Note the use of square brackets to denote that the column is part of a table. To fetch the whole
table:

Dim myRange As Range


Set myRange = Sheets("My Worksheet").Range("Products")

Note: You can name a table in the Design tab of the ribbon when any cell in the table is
selected.
Working with row and column values
Oftentimes you will want to retrieve the actual row and column numbers of a cell or the start of
a range so that you can refer to adjacent cells. To kick off, if you have a row and column number
already and want to get the cell reference, use:

Dim someCell As Range


Set someCell = Cells(rowNumber, columnNumber)

If you just want the cell’s actual value, things are simpler:

cellValue = Cells(rowNumber, columnNumber).Value

Note that cells are numbered from (1,1) as the top-left corner of a worksheet. In fact, all
operations in Excel VBA are 1-indexed (meaning that iterating over a group of items starts at 1,
not 0 as is the case in many other languages).

To get the row and column numbers of the first item in a range (which could be a single cell, a
single row, a single column or a rectangular selection), use the Row and Column properties
of Range:
someColumn = Sheets("My Worksheet").Range("SomeNamedRange").Column
someRow = someOtherRange.Row

Note that when you retrieve these row and column numbers, they are relative to the top-left of
the entire worksheet, not the range. Fortunately, this is usually what you want.

Retrieving cell references from a position relative to another cell reference


Armed with this information, we can now look at the cells around a cell reference. Suppose we
have a formula where we pass a single cell reference from part of a table, perhaps a product
name, and we want to look up the price of the product. We can find out the row number of the
product, and – if we use a named range – the column number of the price column. Using these
two values together, we can find the price of the product:

My Function doSomethingWithPrice(ProductNameCell As Range) As Variant

ProductRow = ProductNameCell.Row
PriceColumn = Range("ProductTable[Price]").Column

Price = Cells(ProductRow, PriceColumn).Value


...
End Function

Notice that it’s essential to pass a cell reference and not the actual product name value here; if
we did so, there would be no way to find out which cell was passed to the formula.

Accessing built-in worksheet functions


Use the WorksheetFunction object:
someCount = WorksheetFunction.CountIf(Range("someRange"),
someCell.Value)

This is the equivalent of writing the following formula in a cell:

=CountIf(someRange, 123)
storing the result in someCount.
Any worksheet function can be used, but as you can see above, the arguments must be passed
in terms of VBA cell references and values.
Exiting a formula function early
Sometimes you will want to do a test before continuing with the formula, and exit with a
different value if the test succeeds or fails. You can use the Exit Function statement to achieve
this. For example:
Public Function yesOrNo(someCell As Range) As String

If someCell.Value <> 123 Then


yesOrNo = "No"

Exit Function
End If

... do something else ...

yesOrNo = "Yes"
End Function

This function exits early if the value of the passed cell is not 123, otherwise it continues
executing the formula.

Language elements and syntax


Comparisons in VBA for C++/C#/PHP/Java programmers
For equality comparisons, use = instead of ==.

For inequality comparisons, use <> instead of !=.

For compound comparisons, use And and Or instead of && and ||.
For boolean comparisons, use True and False instead of true, false and !.
If statements do not require outer brackets in VBA. Compound If statements take the form:
If someCondition = someOtherCondition And ... And ... Then
some code
ElseIf anotherCondition <> yetAnotherCondition Then
some code
Else
some code
End If

Ternary operator
There is no equivalent of the ternary operator in VBA, however you can easily replicate it by
using a function such as:

Public Function iff(condCheck As Boolean, ifTrue As Variant, ifFalse As


Variant) As Variant

If condCheck Then
iff = ifTrue
Else
iff = ifFalse
End If

End Function

Use like this:

ternaryResult = iff(1+1 = 2, "1+1 does equal 2", "1+1 does not equal
2")

Note that by using Variant in the function definition, this ternary operator workaround will
automatically work with any types.
Switch statements
VBA provides Select Case as the equivalent of switch. The syntax is as follows:
Select Case someValue
Case 1
do something

Case 2 To 5
do something else

Case Else
same as default in other languages (if no case matches)

End Select

Note that no break statement is required, there is no case fall-through in VBA like there is in
C++ etc.
Comments
Use the apostrophe symbol to add comments to your code:

' this line will be ignored

Code that spans more than one line


Use the underscore character to split code onto more than one line:
If 1+1 = 2 _
And 2+2 = 4 Then
some code
End If

String functions
Here are a few useful string functions:

string1 & string2 ' concatenates two strings together

Len(stringValue) ' gets the length in characters of a string

Left$(stringValue, qty) ' get the left-hand most qty characters of a string

Mid$(stringValue, mid, qty) ' get a sub-string starting at character mid and qty characters long (
indexed in VBA)

Right$(stringValue, qty) ' get the right-hand most qty characters of a string

Trim(stringVal) ' trims the leading and trailing whitespace from a string

Replace(stringVal, src, dst) ' returns stringVal with all occurrences of src replaced with dst. Th
same length

LCase(stringVal) ' returns stringVal converted to lowercase

UCase(stringVal) ' returns stringVal converted to uppercase

Join(stringArray) ' takes an array of strings and combines them in order into a single string (like

And a couple of more esoteric examples:

Asc(charValue) ' get the ASCII code of a character

Hex(num) ' get a string representation of the hexadecimal value of a number

There are of course, many others.


Error handling
Error handling is surprisingly important when dealing with Excel formulas. If you have a formula
that is called frequently and keeps failing, you can end up with memory leaks, crashed
spreadsheets and ultimately your whole computer grinding to a halt.

There are several error handling statements and they can be placed anywhere in a function to
change the currently active error handling scheme. Here is a common use case:

Public Function myFormula() As Variant

' do something at the start of the function

On Error GoTo SomethingWentWrong:


' try to do something that might cause an error

On Error GoTo 0
' rest of function

myFormula = 123
Exit Function

SomethingWentWrong:

' exit function gracefully

myFormula = 0

End Function

The statement On Error GoTo SomethingWentWrong: indicates to VBA that if an error occurs in
the code that follows, execution should jump to the specified label (SomethingWentWrong). Note
the use of the colon at the end of this statement.
Once the potentially problematic code is executed, the line On Error GoTo 0 returns Excel to its
default error handling, which essentially returns a formula error (#VALUE) if something goes
awry in your function.
After calculating the formula result, we add in Exit Function to prevent the error handling code
from being executed if everything went well. Finally, at the end of the function, we define
the SomethingWentWrong label and set the formula result to some reasonable value if there was
a problem.
This tactic will prevent you from getting #VALUE errors where a formula cannot be calculated,
which prevents column sub-totalling and PivotTables etc. from working properly.
Useful patterns
Finding the number of occurrences of a single value in a range of cells
If myRange is your range and testValue is the value you want to look for:
Qty = 0

Dim singleCell As Range


For Each singleCell In myRange

If singleCell.Value = testValue Then


Qty = Qty + 1
End If

Next singleCell

Qty now contains the number of items in myRange which have the value testValue.
You could just use WorksheetFunction.CountIf(myRange, testValue) to do the same thing, but
what if you want to get the row numbers of each occurrence of testValue? Instead, you can do
this:
Dim matchingRows(1 To 100) As Integer

Qty = 0

Dim singleCell As Range


For Each singleCell In myRange

If singleCell.Value = testValue Then


Qty = Qty + 1
matchingRows(Qty) = singleCell.Row
End If

Next singleCell

matchingRows now contains the row numbers of each occurrence of testValue in myRange. This
cannot be done with a standard worksheet function.
Finding all the unique values in a range
We can use the Scripting.Dictionary Visual Basic object to make things easier here:
Set UniqueValues = CreateObject("Scripting.Dictionary")
UniqueCount = 0
Dim singleCell As Range
For Each singleCell In myRange

If Not UniqueValues.Exists(singleCell.Value) Then


UniqueCount = UniqueCount + 1
UniqueValues.Add singleCell.Value, UniqueCount
End If

Next singleCell

Working with a disparate collection of cells


If the cells you want to test aren’t in a contiguous range, you will need to store the row and
column numbers of each cell to test. You can either use two one-dimensional arrays: one for the
rows and one for the column, or you can use an array of ranges containing a single cell each.

Let us suppose we want to test a number of disparate cells in a single column, whose column
number is stored in TestColumn. We have an array of the row numbers of each cell to test in this
column, stored in TestRows. You can iterate over all the cell values as follows:
Dim rowNumber As Integer
For Each rowNumber In TestRows
itemValue = Cells(rowNumber, TestColumn).Value
' do something with itemValue

Next rowNumber

Merging two or more ranges


You can merge various ranges together. Let us suppose you have an array of ranges
in rangeArray and you want to merge them into a single range. You can do this as follows:
Dim combinedRange As Range

For Each singleRange In rangeArray


If combinedRange Is Not Nothing Then
Set combinedRange = Application.Union(combinedRange, singleRange)
Else
Set combinedRange = singleRange
End If
Next singleRange

WARNING: Combined ranges may not always work as you expect. If the ranges are contiguous,
everything will be fine. However, you cannot merge a group of randomly placed cells this way
and then iterate over the range correctly. This is because when you reference a range, it is
always from the top-left cell. Consider the range B4:B6. This is a range with a starting row of 4,
starting column of 2, and a size (count) of 3. When you iterate over the 3 items, you correctly
get references to cells B4, B5 and B6 respectively. Now consider the case where you have
used Union to merge 3 disparate cells: C5, D8 and H4. The range has a starting row of 5,
starting column of 3 (column C) and a count of 3. It is only these starting values that the range
actually references, so if you iterate over it, you will retrieve cells C5, C6 and C7! Be wary of this
and use the techniques further above of storing the row and column numbers directly in an array
if you need to iterate over non-contiguous arbitrary groups of cells.
Fetching a web page
It’s very handy to be able to download web pages in a macro, usually for the purpose of parsing
them to insert data based on the values input to the formula. For example you might use the
input value to execute a web search to fetch the price of a product.

The business of just fetching a page is fairly straightforward. You create an invisible instance of
Internet Explorer (one that doesn’t appear on the screen), request a page, wait for the download
to complete, fetch the document from the browser then close it down:

Public Function FetchWebPage() As Boolean

Set IE = CreateObject("InternetExplorer.Application")
IE.Visible = False

FetchURL = "http://www.somewebsite.com/somepage"

IE.Navigate2 FetchURL
Do While IE.ReadyState <> 4 Or IE.Busy
DoEvents
Loop

On Error GoTo PageLoadFailed:


Set pageContents = IE.Document

On Error GoTo 0

' do something with pageContents

FetchWebPage = True

IE.Quit
Exit Function
PageLoadFailed:
FetchWebPage = False

IE.Quit
End Function

The Do While loop polls Internet Explorer repeatedly to see if the page has loaded yet or not,
relinquishing control to Windows periodically to do other tasks while waiting with
the DoEventscall.
The error handling is extremely important here. You must ensure that IE is closed down
regardless of the success or failure of your function to execute without error, otherwise you will
end up with loads of invisible copies of IE (use Task Manager to close them if necessary) which
will grind your machine to a halt as it consumes all of the available memory. It can also make
Excel stall or become extremely unresponsive. Always call IE.Quit on all execution paths of your
function.
Passing a search query to a web page
Things get a little more tricky if you need to pass a string as a GET query, because the string
must be processed such that any characters that would normally be invalid in a URL are properly
encoded. This is called, quite simply, URL encoding. Here is a function I pilfered from somewhere
on the internet which does the job:

Public Function URLEncode( _


StringVal As String, _
Optional SpaceAsPlus As Boolean = False _
) As String

Dim StringLen As Long: StringLen = Len(StringVal)

If StringLen > 0 Then


ReDim Result(StringLen) As String
Dim i As Long, CharCode As Integer
Dim Char As String, Space As String

If SpaceAsPlus Then Space = "+" Else Space = "%20"

For i = 1 To StringLen
Char = Mid$(StringVal, i, 1)
CharCode = Asc(Char)
Select Case CharCode
Case 97 To 122, 65 To 90, 48 To 57, 45, 46, 95, 126
Result(i) = Char
Case 32
Result(i) = Space
Case 0 To 15
Result(i) = "%0" & Hex(CharCode)
Case Else
Result(i) = "%" & Hex(CharCode)
End Select
Next i
URLEncode = Join(Result, "")
End If
End Function

If you have a product name you wish to search for, for example, you can change the
way FetchURL is defined in the previous example as follows:
FetchURL = "http://www.somewebsite.com/search?product=" &
URLEncode(productName)

If you need to send multiple variables, use URLEncode on each of them like this:
FetchURL = "http://www.somewebsite.com/search?product=" & URLEncode(productName) & "&lang
URLEncode(pageLanguage)

Parsing a web page


In simple cases you can use the Get External Data From Web feature in the Data tab of the
ribbon to automatically do web page parsing for you and avoiding using VBA altogether. In other
cases you may be able to access the data as XML rather than an HTML web page; this solution is
preferred and in these cases you should use the XML map tool to import your data.
In the cases where you want to parse an HTML page programmatically in a formula, or the
rudimentary parsing provided by Excel isn’t sufficient and no XML feed is available, you can as
with other languages use the DOM object model to parse the page. It is beyond the scope of this
article to explain the DOM but for those who are familiar with it or don’t mind diving into the
deep end, here are a few quick and dirty examples.

To get an element by its ID:

Set myElement = IE.Document.GetElementById("id-to-find")

To get a list of elements by class name:

Set myElements = IE.Document.GetElementsByClassName("class-name-to-


find")

To get a list of elements by tag name:


Set tableRowItems = someTableRowElement.GetElementsByTagName("td")

To iterate over a list of elements and get their text values:

For Each tableItem In tableRowItems


tableItemValue = tableItem.innerText
Next tableItem

To access a specific element in a list of elements (for example a list of elements found by tag or
class name) without using For Each, you can use the Item collection. Consider an unordered list
(<ul>) with a class name of list-class. Several lists in the document may have the list-
class class, but you just want to find the 2nd occurrence in the document and fetch all the list
items (<li>) from it. You can do so as follows:
Set listItems = IE.Document.GetElementsByClassName("list-
class").Item(1).GetElementsByTagName("li")

Note here that the elements are 0-indexed, so the first list-class element can be found
in Item(0) etc.
To access the child elements (excluding whitespace) of an element, use
the Childrencollection. For example if you have an element myTableRow which points to
a <tr> and you want to get the third <td> element text from the row:
tableItemValue = myTableRow.Children(2).innerText

Note here that the elements are 0-indexed, so the first </td> can be found in Children(0) etc.
Conclusion
I failed to find a web page which summarized the key facts on how to get simple tasks done in
Excel VBA without having to Google almost every line of code I wrote, so I thought it would be
nice to pull it all together in one place. I hope you found it useful!

Got questions about Excel VBA? Post them below and I’ll expand this resource with solutions.

Anda mungkin juga menyukai