Best Practices

This is our definitive list of guidelines, suggestions, recommendations, etc
Thanks to Patrick O'Beirne, Jon Peltier, Jordan Goldmeier, Paul Kelly and Rory Archibald for their feedback.
Numbers 1 - 10 are aimed at Beginner Programmers.
Numbers 11 - 20 are aimed at Intermediate Programmers.
Numbers 21 - 30 are aimed at Advanced Programmers.


1) Always put Option Explicit at the top of all your modules (including userforms and classes).

Option Explicit 

This ensures that your code will only run, if all your variables have been explicitly declared.
Select (Tools > Options)(Editor tab, Require Variable Declaration) and make sure it is checked.
Selecting this check box will automatically add the statement Option Explicit to any new modules (not existing ones).


2) Try to declare your variables close to where they are being used, rather than at the top.

Public Function MyFunction() As String 
Dim iRowCounter As Integer

Some variables might belong at the top while others should be declared just before they are used. This makes refactoring the code easier.
Avoid using single letters for your variable names. Never use "i" and "j" in your loops.
Avoid using any reserved words or names that are similar to object properties or methods.


3) Avoid using the Variant data type unless there is a very good reason.

Dim vSomething As Variant 

The Variant is used to hold any data type, value or reference (except for fixed length strings).
This data type has the largest size at 16 bytes (128 bits) so not using it, will speed up your code.
The only time when you should use the Variant data type is:
*) When you really don't know the data type.
*) When you are writing a general helper routine that needs to work with a number of different data types.
*) When you want to pass an array of any data type into a subroutine or return an array from a function.


4) Try to declare related variables on the same line otherwise one variable per line.

Dim sPersonName As String, iPersonTotal As Integer 
Dim sMyString As String

If the variables have the same data type or they are related, then they should be on the same line. This will make refactoring the code easier.
When variables are declared on separate lines this improves readability and helps to reduce spelling mistakes.


5) Prefix your variables with a data type indicator followed by a descriptive name.

Dim sMyString As String 
Dim lMyNumber As Long

Type conversions can be implicit, so prefixing your variables to indicate their data type, will help reduce errors.
In most programming languages using Hungarian notation is not necessary, but for VBA a lot of developers find this useful.
For a list of all the prefixes, please refer to the Data Types page.


6) Always indent your code to make it more readable.

For iRowNo = 1 To 5 
'for example everything inside a loop should be indented
Next iRowNo

You can use spaces to indent your code, although tabs are recommended.
Indenting your code consistently makes the code easier to understand and the program flow more obvious.


7) Avoid using the On Error Resume Next error handling statement.

On Error Resume Next 

Adding some error handling into your subroutines and functions is recommended.
Instead of ignoring all your run-time errors you should use a Custom Error Handler.


8) Avoid using the GoTo statement to control your program flow.

GoTo LineLabel 
LineLabel:

Never use line labels to jump up or down, in your code.
Instead have a more structured approach to controlling program flow using conditional branching and loops.


9) Use With - End With when you are referencing the same object more than once.

With Selection.Font 
   .Size = 10
   .Bold = True
End With

This allows you to use a simplified syntax when you want to perform multiple operations on a single object.
The fewer the dots, the faster the code will run.


10) Use meaningful subroutine names, function names, variable names, etc.

Public Sub FormatAdditionalTextBoxes() 

Subroutines and functions should be given a name that describes the task they perform.
You should try and use a consistent naming convention.

Subroutine/Function Names - PascalCase or camelCase 
Variables (local level) - iHungarian
Variables (module level) - PascalCase
Constants - ALL CAPITALS

Intermediate Best Practices

The following two productivity tools are definitely worth considering at this point: rubberduckvba.com and mztools.com.
Numbers 11 - 20 are aimed at Intermediate Programmers.


11) Turn off Auto Syntax Check from your user options.

Public Sob Test 

As you type your code, it is automatically checked for syntax errors.
When any syntax errors are found you are alerted with a pop up message box which most people find very annoying.


12) Use the line continuation character to make your code more readable and to reduce the amount of horizontal scrolling.

Dim sMyLongString 
sMyLongString = "this is a very" & _
                "very long string"

This is an underscore character that must be prefixed by a space (" _").
Another way to reduce the number of characters on a single line is to use string concatenation


13) Avoid using global variables unless absolutely necessary.

Global g_sGlobalVariable As String         'use Public instead  
Dim m_sModuleLevelVariable As String 'use Private instead

Declaring a variable using Global at the top of a module is the same as using Public and is only included for backwards compatibility.
Declaring a variable using Dim at the top of a module is the same as using Private.
If you do need to use a global variable then always prefix it with a "g_" prefix.


14) Try and write subroutines and functions that are no more than 30 lines in length.

'always write short subroutines and functions

Having very long blocks of code makes debugging and readability a lot harder.
If you cannot see the start and end of a procedure without scrolling then its too long.


15) Use built-in constants and built-in enumerations to improve readability.

If MsgBox("Please confirm ?") = VBA.vbMsgBoxResult.vbYes Then 
objFileSearch.FileType = msoFileType.msoFileTypeExcelWorkbooks

The built-in constants should be written with their full VBA. syntax.
The built-in enumerations all start with a mso prefix.
Grouping constants that are related into enumerations makes them easier to find.


16) Do not use the Call keyword when calling procedures (and functions)

Call MySubroutine() 
Call MySubroutine(sArg1, sArg2, sArg3)

This syntax actually comes from the days of BASIC when every line had to start with a keyword.
When you use the Call statement all your arguments need to be in parentheses.


17) Try and add a custom Error Handler to all your procedures and functions.

On Error GoTo ErrorHandler 
ErrorHandler:

In most cases the routine that "finds" the error should be the routine that "handles" the error.
When it makes sense to pass the error back to the calling routine, an error handler should not be included.


18) Use dedicated functions to run any code that might result in a run-time error.

Public Function Folder_Create(ByVal sFullPath As String) As Boolean 
On Error GoTo ErrorHandler
   VBA.MkDir(sFullPath)
   Folder_Create = True
   Exit Function
ErrorHandler:
   Folder_Create = False

These functions should return True or False indicating success or failure.
These functions can have their own dedicated and independent error handling statements.


19) Use vbNullString for an empty string and the LEN function to check for an empty string.

Dim sMyString As String 
sMyString = VBA.Constants.vbNullString
If VBA.Len(sMyString) = 0 Then

Always assign your string to vbNullString when you need to empty the contents.
Avoid comparing with an empty string ("") as this requires more memory.


20) Put your user messages into a dedicated "modMessages" code module to avoid spelling mistakes.

modMessages.Message_DownloadComplete() 

Use a consistent naming convention and format, for all your messages and questions
Always explicitly reference the modMessages module when calling any of these subroutines or functions.


Advanced Best Practices

Numbers 21 - 30 are aimed at Advanced Programmers.


21) Use Tabs to indent your code, never use Spaces.

. . . four spaces 
  ⇢ is equal to one tab

You can change the number of characters that are represented by a tab using the Editor Tab
You can even use (Shift + Tab) to "unindent" your lines of code.


22) Log your errors to a local text file saved on the C drive.

C:\Temp\SolutionName\LogFile.txt 

This will make debugging and troubleshooting much easier.
You should create/upgrade your Error_Handle subroutine to do this.


23) Prefix your MsgBox titles with a consistent prefix, so they can be easily recognised in a screen shot.

Call MsgBox("MsgBox Prompt", _ 
            VBA.vbMsgBoxStyle.vbInformation, _
            "BET: MsgBox Title")

It is also worth adding other useful information in the title prefix, for example a version number.


24) Use the FileSystemObject to perform any file and folder operations.

Dim objFSOFileSystemObject As Scripting.FileSystemObject 
Set objFSOFileSystemObject = CreateObject("Scripting.FileSystemObject")

The Microsoft.Scripting.Runtime library offers clear, object-orientated access to all the common file and directory functions.
GetAttr, Dir, Kill, MkDir, FileLen, FileDateTime, FileCopy cannot handle Unicode pathnames.


25) Use Class Modules when it makes the most sense.

Dim objEmployee As CEmployee 
Set objEmployee = New CEmployee

Use a Class Module when you need to create your own customised objects.
You can define the methods and properties for them and even write event handlers.


26) Use Arrays to manipulate your data.

Dim arValues As Variant 
arValues = Array(1, 2, 3, 4)

Arrays are fast, quick to troubleshoot and helper functions only need to be written once.
Never have a ReDim Preserve inside a loop.
For best results, oversize the array at the beginning, and then use the ReDim statement once, at the end.


27) Avoid using Collections unless you need to insert and remove a lot of items.

Dim colEmployees As New Collection 
Set MyCollection = New VBA.Collection

You should try and use Arrays instead of collections for maximum flexibility and control.
Collections are slow at reading and writing data.
You can only add one item at a time to a collection.
You cannot change an item in a collection, you must remove and add a new item.
The Watch window will only display the first 256 items in a collection.


28) Avoid using Dictionaries unless you need unique keys.

Dim objFSODictionary As New Scripting.Dictionary 
Set objFSODictionary = New Scripting.Dictionary

You should try and use Arrays or Collections instead of the Scripting Dictionary.
Storing data in key/value pairs is not a logical fit for a lot of data sets.
Use a dictionary if you need to retrieve (or change) the keys as well as the items.


29) Avoid using Option Base or Option Compare statements.

Option Base 1 
Option Compare Text

The default starting position for arrays is 0, never change this to 1.
The default string comparison (using > and <) is case sensitive, never change this to not being case sensitive.


30) Let us know what you think should be added here.
Never assume the selection. Do not use ActiveWorkbook, Activesheet or ActiveCell.


Instead of calling Chr() or Chr$() on the following numeric values, use the predefined string constants. They are faster.
For example: vbNullChar (0), vbBack (8), vbTab (9), vbLf (10), vbVerticalTab (11), vbFormFeed (12), vbCr (13), vbCrLf (13 & 10), vbNewline (13 & 10)
vbNewline is a little bit faster than vbCrLf


Calling Asc("A") does not make sense because this returns a constant. Use the value 65 or just define a constant:

Const ascA = 65 


© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext