Handle Errors While Sending Outlook Emails [Excel VBA]

Note: This webpage is designed to accompany the Youtube video posted above. The video offers detailed explanation on all topics; while this webpage will serve as a repository for the code presented in the video.

    In this session,

  • We will quickly re-build the loop from the last video where we sent multiple emails with single attachments. So, even if you haven’t checked it out, this recap should get you up-to-speed. And if the code covered here feels slightly advanced, I will encourage you to go through the previous tutorial.
  • Next, we will look at error handling while sending emails. This involves data-integrity scenarios such as how to check if an email string is a valid email id. I can’t stress enough how important it is to check your data thoroughly through code before you begin your send email procedure. In the same code, we will also report back whether the email was sent successfully or not. This is especially handy if you have dozens of emails to send and want to check whether any failed to send or not.
  • In the last module, we will shift out the error handling part from the main sub-procedure to a separate sub. This will make our code neater.
  • In the same session, we will also take out all the hard-coding and set it as constants right at the top of our module. This will make it much easier to adjust in case the data columns ever change.

Type of Error Checks

We will conduct the error handling in 2 Stages.

Stage 1 checks for data-integrity errors in the dataset. If there is not even a single error, the macro will proceed to loop over the dataset again and send emails to each recipient. Stage 2 checks whether there is any error while sending the emails.

This can very well be done in the same procedure/ loop. The primary reason for breaking up the error handling into separate loops, is that we shouldn’t have to break the flow of sending emails just because a user has mis-typed some details in the data. If it were all done in one loop and if there was an error, you would need to correct the error and re-run the macro on the remaining recipients which can get messy.

Stage 1: Loop through data set and check for any user-related errors concerning data integrity.

  1. Whether the email address in column A is a valid string or not. So, we are not checking if the email address actually exists. Rather, we will check whether it follows the right format of a valid email address. i.e. if there is an @ sign. Whether, there is “.” after the @ sign etc. More details when we get to it.
  2. Next, we will check if there is a file name for us to attach in column C. If the cell is blank, we will return an error.
  3. Last, if there is a file name in Col C, we will check whether that file actually exists or not. If it doesn’t, we will return an error.


If even one error is detected in the entire dataset, no emails will be sent out. However, the main feature here is that the macro doesn’t stop on the first occurrence of any error. Rather, it will capture all the errors and list them out separately, in an error sheet for the user to review all at once. This will give the user the opportunity to correct all errors at one go, rather then correct one error, run the macro, only to find another error, correct that, run the macro again, find another error and so on. This would get quickly frustrating on a large dataset.

Stage 2: Run-time errors

Next, we will check if the actual sending of the email was successful or not. Here, if there is any error, only the email against that particular email will not be sent. Rest of the emails will get sent though. This is handy as well. If you want to have a large list of emails to send, and some failed, this macro would tell you specifically WHICH failed rather than having to sieve through the Outbox to check which ones weren’t sent.

We don’t expect to see any failures here anyways. We will already be checking for any data related errors in the previous stage of checks. And, if there is some issue with the code, then VBA will tell us before the code executes. So, the probability of an error during run-time is actually very low. Still, there is the possibility of connectivity. If you are at work, and there is network issue for a brief moment, we could get errors for example, when attaching the file at the time of sending the email.

Now for a disclaimer. The term Sent is being used here, synonymously with sending of emails. This is incorrect.

Technically, what I am referring to is that when we send the email via the macro, is that it is successfully transferred to our outbox.

And I am making the assumption, that the email was sent from here automatically. This will hold true for most cases. And we can go through the case, where it doesn’t hold true.

  1. Message is sent to Outbox, but doesn’t move to Sent Folder. In this case, the Message is not technically sent. For the scope of this macro, we would need to monitor that manually ourselves. Possible reasons are that the Send/ Receive option is not set to automatic or our internet is down or we just can’t connect to the Microsoft Exchange Server
  2. Message is sent from Outbox to Sent Folder; but isn’t delivered. This would technically qualify as Sent. But, you would have at some point seen an ugly email with the subject Undeliverable sent by Microsoft Outlook. This would most likely be because the email id of the recipient is not valid. Specifically, the email string may be valid, but the email address itself may not exists. An example would be that we had a typo in the email. This is an error that we would need to monitor ourselves as well.

So, just summing this up. These were two scenarios where the macro will classify the message as sent, but actually, it never reached the recipient.

Code 1: Error Handling

To send an email via Outlook and to access the various features of Outlook, we need to create a reference to the Outlook Object library.

In the VB Editor, go to Tools, then References:

You shouldn’t be able to see any reference to an Outlook library.

We need to search and select the Outlook library. Scroll down all the way till you see Microsoft, and then keep scrolling till you find Microsoft Outlook X.X Object Library. The version used in this tutorial is 16.0. Yours might be different. It shouldn’t matter. Select the library and Press OK.

Code as shown in the error handling section within the video is as below. Best way to proceed is to first build the loop without any error handling, test it and then, add in the error handling.

Full Code with Error Handling as Below.

Option Explicit

Const csFolderPath As String = "C:\Youtube\Outlook Tutorial 02\Multiple Email Loop\"

' Define Body
Const emBody As String = "Hi There,<br><br>" & _
            "Please find our latest statement attached.<br><br>" & _
            "Regards,<br>" & _
            "OSA Team"

' Define Subject
Const emSubject As String = "Statement of Overdue Invoices (Food Jar Co)"


Sub Send_Multiple_Emails_Single_Attach_w_Error()
Application.ScreenUpdating = False

Dim lrowEmRange As Long
lrowEmRange = wsToEmail.Range("A1").CurrentRegion.Rows.Count

wsToEmail.Columns("D:D").ClearContents
wsToEmail.Range("D1").Value = "Status"
wsError.Cells.Clear
wsError.Range("A1").Value = "Error"

If Dir(csFolderPath, vbDirectory) = "" Then
    MsgBox "Folder Path Incorrect." & vbNewLine & "Please check and correct.", vbExclamation, "Errors Found"
    Application.ScreenUpdating = True
    Exit Sub
End If

Dim emTo As String
Dim emAttach As String
Dim i As Long

Dim bUserDataError As Boolean
bUserDataError = False
Dim lrowError As Long

For i = 2 To lrowEmRange
    If Not wsToEmail.Range("A" & i).Value Like "?*@?*.?*" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "Invalid Email ID in Cell " & wsToEmail.Range("A" & i).Address
    End If

    If wsToEmail.Range("C" & i) = "" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "No Statement To Attach in Cell " & wsToEmail.Range("C" & i).Address
    End If

    emAttach = wsToEmail.Range("C" & i).Value
    emAttach = csFolderPath & emAttach

    If Not emAttach = "" And Dir(emAttach) = "" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "Invalid File Path for Statement in Cell " & wsToEmail.Range("C" & i).Address
    End If
Next i

If bUserDataError = True Then
    MsgBox "Email Id/Attachment error." & vbNewLine & "Please check and correct.", vbExclamation, "Errors Found"
    wsError.Activate
    Application.ScreenUpdating = True
    Exit Sub
End If

For i = 2 To lrowEmRange
    emTo = wsToEmail.Range("A" & i).Value
    emAttach = wsToEmail.Range("C" & i).Value
    emAttach = csFolderPath & emAttach
    If Not Send_Email(emTo, emAttach) Then
        wsToEmail.Range("D" & i).Value = "Error Occured"
        Else
        wsToEmail.Range("D" & i).Value = "Sent Ok"
    End If
Next i

Dim rngFindError As Range
Set rngFindError = wsToEmail.Range("D:D").Find(what:="Error Occured", LookIn:=xlValues, lookat:=xlWhole)

If rngFindError Is Nothing Then
    MsgBox "All emails were sent successfully"
    Else
    MsgBox "Atleast one email wasn't sent due to an error." & _
        vbNewLine & "Please review status in Col D.", vbExclamation, "Errors Found"
End If

Application.ScreenUpdating = True
End Sub

Function Send_Email(sfTo As String, sfAttach As String) As Boolean
On Error GoTo SystemErrorHandler

Dim oApp As Outlook.Application
Set oApp = New Outlook.Application
Dim oMail As Outlook.MailItem
Set oMail = oApp.CreateItem(olMailItem)

With oMail
    .To = sfTo
    .CC = ""
    .BCC = ""
    .Subject = emSubject
    .HTMLBody = emBody
    .Attachments.Add sfAttach
    .Display
    '.Send
End With
    Send_Email = True
    Exit Function
SystemErrorHandler:
    Send_Email = False
End Function

Code 2: Create Separate Function for Error Handling

In this section, the output will remain the same as previous. However, we will accomplish 2 things here.

  1. Take out the error handling part from the main sub and put it into it’s own function.
  2. Remove all the hard-coding and refer to the cells using constants. So, if/when the columns change positions, all you would need to do is change the constant’s value rather than go into the main sub and change every hard-coded reference to that cell.
Option Explicit

Const csFolderPath As String = "C:YoutubeOutlook Tutorial 02Multiple Email Loop"

' Define Body
Const emBody As String = "Hi There,<br><br>" & _
            "Please find our latest statement attached.<br><br>" & _
            "Regards,<br>" & _
            "OSA Team"

' Define Subject
Const emSubject As String = "Statement of Overdue Invoices (Food Jar Co)"

Const lEmailCol As Long = 1
Const lAttachCol As Long = 3
Const lStatusCol As Long = 4

Sub Send_Multiple_Emails_Single_Attach_w_Error()
Application.ScreenUpdating = False


wsToEmail.Columns(lStatusCol).ClearContents
wsToEmail.Cells(1, lStatusCol).Value = "Status"

Dim rngEmail As Range
Set rngEmail = wsToEmail.Range("A1").CurrentRegion
Set rngEmail = rngEmail.Offset(1, 0).Resize(rngEmail.Rows.Count - 1, rngEmail.Columns.Count)

wsError.Cells.Clear
wsError.Range("A1").Value = "Error"

If Dir(csFolderPath, vbDirectory) = "" Then
    MsgBox "Folder Path Incorrect." & vbNewLine & "Please check and correct.", vbExclamation, "Errors Found"
    Application.ScreenUpdating = True
    Exit Sub
End If

Dim emTo As String
Dim emAttach As String
Dim i As Long

If IsDataCorrect(rngEmail, lEmailCol, lAttachCol) Then
    MsgBox "Email Id/Attachment error." & vbNewLine & "Please check and correct.", vbExclamation, "Errors Found"
    wsError.Activate
    Application.ScreenUpdating = True
    Exit Sub
End If

For i = 2 To rngEmail.Rows.Count + 1
    emTo = wsToEmail.Cells(i, lEmailCol).Value
    emAttach = wsToEmail.Cells(i, lAttachCol).Value
    emAttach = csFolderPath & emAttach
    If Not Send_Email(emTo, emAttach) Then
        wsToEmail.Cells(i, lStatusCol).Value = "Error Occured"
        Else
        wsToEmail.Cells(i, lStatusCol).Value = "Sent Ok"
    End If
Next i

Dim rngFindError As Range
Set rngFindError = wsToEmail.Columns(lStatusCol).Find(what:="Error Occured", LookIn:=xlValues, lookat:=xlWhole)

If rngFindError Is Nothing Then
    MsgBox "All emails were sent successfully"
    Else
    MsgBox "Atleast one email wasn't sent due to an error." & _
        vbNewLine & "Please review status in Col " & lStatusCol, vbExclamation, "Errors Found"
End If

Application.ScreenUpdating = True
End Sub

Function Send_Email(sfTo As String, sfAttach As String) As Boolean
On Error GoTo SystemErrorHandler

Dim oApp As Outlook.Application
Set oApp = New Outlook.Application
Dim oMail As Outlook.MailItem
Set oMail = oApp.CreateItem(olMailItem)

With oMail
    .To = sfTo
    .CC = ""
    .BCC = ""
    .Subject = emSubject
    .HTMLBody = emBody
    .Attachments.Add sfAttach
    .Display
    '.Send
End With
    Send_Email = True
    Exit Function
SystemErrorHandler:
    Send_Email = False
End Function

Function IsDataCorrect(frngEmail As Range, flEmailCol As Long, flAttachCol As Long) As Boolean
Dim emAttach As String
Dim i As Long

Dim bUserDataError As Boolean
bUserDataError = False
Dim lrowError As Long

For i = 2 To frngEmail.Rows.Count + 1
    If Not wsToEmail.Cells(i, lEmailCol).Value Like "?*@?*.?*" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "Invalid Email ID in Cell " & wsToEmail.Cells(i, lEmailCol).Address
    End If

    If wsToEmail.Cells(i, lAttachCol).Value = "" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "No Statement To Attach in Cell " & wsToEmail.Cells(i, lAttachCol).Address
    End If

    emAttach = wsToEmail.Cells(i, lAttachCol).Value
    emAttach = csFolderPath & emAttach

    If Not emAttach = "" And Dir(emAttach) = "" Then
        bUserDataError = True
        lrowError = wsError.Cells(wsError.Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        wsError.Cells(lrowError, 1).Value = "Invalid File Path for Statement in Cell " & wsToEmail.Cells(i, lAttachCol).Address
    End If
Next i

IsDataCorrect = bUserDataError
End Function