Implementing Try-Catch-Finally in VBA

Maintained on

In general, it is common to perform error handling in each function and then throw to the calling code. However, implementing this in VBA is not straightforward.

If you create an error handler, it will suppress the error and if you try to raise the error again from there, it will result in an infinite loop within that function.

A specific example is:

  • When using the Open function to open a file, you may want to ensure that the Close operation still occurs even if an error occurs.
  • Additionally, you want to propagate the error to the calling code.
On Error GoTo 0
Call Err.Raise(Err.Number)

To resolve the issue, you can use the code provided above. Let me explain and show you some examples.

On Error GoTo 0

By using On Error GoTo 0, you can cancel the previously defined On Error statement.

Normally, if you write Err.Raise in the error handler, it will result in a loop like this:

  1. Catch the error.
  2. Go to the error handler.
  3. Raise the error.
  4. Go back to step 1.

However, by adding On Error GoTo 0, you can achieve the following:

  1. Catch the error.
  2. Go to the error handler.
  3. Cancel the error handler.
  4. Throw the error to the calling code.

This allows you to replicate Try-Catch-Finally, which includes throwing in the catch block, as seen in other programming languages.

Code Sample

Handling Errors and Throwing Only

Public sub Caller()
	On Error GoTo ERROR_HANDLER
	Call Called

ERROR_HANDLER:
	Debug.Print(Err.Number)
End Sub
Public sub Called()

	On Error GoTo ERROR_HANDLER
	Dim errNumber as Long

		' Write the code where an error may occur

	    Exit Sub

	ERROR_HANDLER:
		errNumber = Err.Number
		On Error GoTo 0

		' Write the code for handling the error here

		' Propagate the error to the caller
	Call Err.Raise(errNumber)

End Sub

Replicating Try-Catch-Finally

It requires quite a lengthy description.

Public sub Caller()

	On Error GoTo ERROR_HANDLER

	Call Called

ERROR_HANDLER:
	Debug.Print(Err.Number)
End Sub

Public sub Called()

	On Error GoTo ERROR_HANDLER
	Dim errNumber as Long

	' Write the code where an error may occur

FINALLY:

	If errNumber <> 0 then
		Err.Raise(errNumber)
	End if

	Exit Sub
ERROR_HANDLER:
	errNumber = Err.Number
	On Error GoTo 0

	' Write the code for handling the error here

 	Resume FINALLY
End Sub

Example Sample

When using Try-Catch only

'------------------------------------------------
'
' Function that calls another function
'
'------------------------------------------------
Public Sub Caller()
	On Error GoTo ERROR_HANDLER
	Call Called

ERROR_HANDLER:

	Debug.Print "Caller: Catch"

End Sub
'------------------------------------------------
'
' Function that is called (performs Throw)
'
'------------------------------------------------
Public Sub Called()

	On Error GoTo ERROR_HANDLER
	Dim errNumber as Long

	Dim n As Long: n = 1 / 0

	Exit Sub

ERROR_HANDLER:
	errNumber = Err.Number
	On Error GoTo 0

	Debug.Print "Called: Catch"

	' Propagate the error to the caller
	Call Err.Raise(errNumber)

End Sub

Execution Result

Called: Catch
Caller: Catch

When reproducing Try-Catch-Finally

'------------------------------------------------
'
' Function that calls another function
'
'------------------------------------------------
Public Sub Caller()

	On Error GoTo ERROR_HANDLER

	Call Called

ERROR_HANDLER:

	Debug.Print "Caller: Catch"

End Sub

'------------------------------------------------
'
' Function that is called (performs Throw)
'
'------------------------------------------------
Public Sub Called()

	On Error GoTo ERROR_HANDLER

	Dim errNumber as Long

	Dim n as Long: n = 1 / 0

FINALLY:

	Debug.Print "Called: Finally"

	If errNumber <> 0 then
		Err.Raise(errNumber)
	End if

	Exit Sub
ERROR_HANDLER:
	errNumber = Err.Number
	On Error GoTo 0

	Debug.Print "Called: Catch"

 	Resume FINALLY
End Sub

Execution Result

Called: Catch
Called: Finally
Caller: Catch
#Excel #VBA