Forgot to set your Outlook Out of Office Automatic Reply before going on vacation? You can enable it remotely from your laptop or smartphone with a little VBA.

Just in time for the holidays, I’ll show you how in this tutorial.


Initial Setup
Starting Automatic Replies
Stopping Automatic Replies


Initial Setup

Background Information

Here’s a high-level overview of what we’re going to do here. It’s actually pretty cool, so stick with me.

Believe it or not, there’s no native way to enable “out of office” messages using VBA.

Instead, we’re going to create a macro that listens for incoming emails. When it detects an email from an email address you specify with a subject matching a string you specify, it will start automatically responding to all emails with a message simulating an out of office reply.

Note, this will only work if you don’t shut your computer off when you’re on vacation. This macro doesn’t interact with the server side, so outlook must be on. If you’re computer is locked, it will work fine. I know this isn’t ideal, but if you wanted an ideal solution, you should have remembered to set your Out of Office before you left! ;)

You used to be able to use Rules in Outlook to trigger a VBA script. Due to security concerns, Microsoft disabled this feature in most versions of Outlook, so we’re going to make a more powerful version of our own.


Outlook Out of Office VBA Tutorial

Adding the Macros

  1. Open Outlook
  2. Make sure you have Outlook Macros Enabled
  3. Open the VBA Editor (Alt+F11)
  4. Paste the following macros in the ThisOutlookSession section under Microsoft Outlook Objects
Private WithEvents Items As Outlook.Items
Public bOOO As Boolean
Public strBody As String
Private Sub Application_Startup()
  Dim olApp As Outlook.Application
  Dim objNS As Outlook.NameSpace
  Set olApp = Outlook.Application
  Set objNS = olApp.GetNamespace("MAPI")
  ' default local Inbox
  Set Items = objNS.GetDefaultFolder(olFolderInbox).Items
End Sub

Private Sub Items_ItemAdd(ByVal item As Object)
  'When you get an email, check to see if you've enabled automatic replies.
  'This will only work if your Outlook session is open. It does not interact with the server itself.
  'In other words, if you shut your computer off when you leave, it will not work.
  On Error GoTo ErrorHandler
  Dim Msg As Outlook.MailItem
  Dim strStart As String 'unique identifier that must appear in the subject to start automatic replies
  Dim strStop As String  'unique identifier that must appear in the subject to stop automatic replies
  Dim strEmail As String 'email address the email must be sent from
  
'-----------------------------------
  'DECLARE VARIABLES
  strEmail = "youremail@address.com"
  strStart = "START OOO"
  strStop = "STOP OOO"
'-----------------------------------
  If TypeName(item) = "MailItem" Then
    Set Msg = item
    If InStr(1, UCase(Msg.Subject), UCase(strStart)) <> 0 And _
       UCase(Msg.SenderEmailAddress) = UCase(strEmail) Then
        'The trigger conditions were met.
        'Enable your out of office.
        bOOO = True
        strBody = Msg.Body
        Call SendInstructions(Msg, strEmail, strStop)
    ElseIf InStr(1, UCase(Msg.Subject), UCase(strStop)) <> 0 And _
       UCase(Msg.SenderEmailAddress) = UCase(strEmail) Then
        'The trigger conditions were met.
        'Disable your out of office.
        bOOO = False
        strBody = ""
        Call StopMessages(Msg, strEmail, strStart)
    End If
   
    If bOOO = True Then
        If InStr(1, UCase(Msg.Subject), UCase(strStart)) <> 0 And _
           UCase(Msg.SenderEmailAddress) = UCase(strEmail) Then
           'don't send a message
        Else
            'send a message
            Call SendOutOfOffice(Msg)
        End If
    End If
    Set Msg = Nothing
  End If
ProgramExit:
  Exit Sub
ErrorHandler:
  Debug.Print Err.Number & ": " & Err.Description
  Err.Clear
  Resume ProgramExit
End Sub

Private Sub SendOutOfOffice(Msg As Outlook.MailItem)
'Automatically reply to each email with a custom message
  On Error GoTo ErrorHandler
  Dim olOutMail As Outlook.MailItem
    With Msg
        Set olOutMail = Msg.Reply
        With olOutMail
            .Body = strBody
            .Send
        End With
        Set olOutMail = Nothing
    End With
    Exit Sub
ErrorHandler:
  Debug.Print Err.Number & ": " & Err.Description
  Err.Clear
End Sub
 
Private Sub SendInstructions(Msg As Outlook.MailItem, strEmail As String, strStop As String)
  On Error GoTo ErrorHandler
  Dim olOutMail As Outlook.MailItem
    With Msg
        Set olOutMail = Msg.Reply
        With olOutMail
            .Body = "You have enabled Automatic Replies. To disable automatic replies, send an email from " & _
                    strEmail & " with """ & strStop & """ in the subject line." & vbNewLine & vbNewLine & _
                    "Automatic replies will continue until you send this message!" & vbNewLine & vbNewLine & _
                    "Here's how your automatic reply will look:" & vbNewLine & Msg.Body
            .Send
        End With
        Set olOutMail = Nothing
    End With
    Exit Sub
ErrorHandler:
  Debug.Print Err.Number & ": " & Err.Description
  Err.Clear
End Sub
 
Private Sub StopMessages(Msg As Outlook.MailItem, strEmail As String, strStart As String)
  On Error GoTo ErrorHandler
  Dim olOutMail As Outlook.MailItem
    With Msg
        Set olOutMail = Msg.Reply
        With olOutMail
            .Body = "You have successfully disabled Automatic Replies. To enable automatic replies, send an email from " & _
                    strEmail & " with """ & strStart & """ in the subject line and your desired automatic reply in the body."
            .Send
        End With
        Set olOutMail = Nothing
    End With
    Exit Sub
ErrorHandler:
  Debug.Print Err.Number & ": " & Err.Description
  Err.Clear
End Sub

Make powerful macros with our free VBA Developer Kit

It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.

I'll take a free VBA Developer Kit

Configuring the Macro

I want you to find the macro titled Items_ItemAdd. You’ll see three variables in the section labeled DECLARE VARIABLES:

  1. strEmail
    • email address the email must be sent from
  2. strStart
    • unique identifier that must appear in the subject to start automatic replies
  3. strStop
    • unique identifier that must appear in the subject to stop automatic replies

Change the email address to an email address you’re able to send emails from while you’re on vacation. A personal email address you have access to from your laptop or smartphone is a good choice.

Once you’ve made it this far, click Save and restart Outlook. If you ever forget to set your out of office automatic reply, follow the steps in the next section to enable it remotely. VBA will save the day!


Starting Automatic Replies

To start your out of office message, email your work email address from the email address you defined in strEmail.

The subject must contain the string you specified in strStart. By default, the string is START OOO, but it’s not case sensitive.

Whatever you put in the body of your message is the message that will automatically be sent as a reply to all subsequent incoming emails.

If successful, you’ll get an email response back saying Automatic Replies were enabled and it will give you instructions on how to disable automatic replies. Like I said, any email you receive to your email after getting the “successfully enabled” email on your personal email account will automatically be replied to with your custom out of office text.

That’s pretty cool, isn’t it?


Stopping Automatic Replies

To turn off these automatic out of office replies, again you’ll need to email your work email address from the email address you defined in strEmail. This time, you’ll need the subject to contain the string you specified in the variable strStop. By default, this string is STOP OOO. Anything you put in the body of this email will be ignored so don’t bother wasting your time with it.

If successful, you’ll get an email response back saying you have successfully disabled automatic replies.

That’s all there is to it! Any email you receive after getting the “succesfully disabled” email will not receive your automatic out of office reply.

This isn’t exactly the same as a native out of office reply, but it’s the next best thing in a pinch when you’re out of other options. It’s saved my tail a number of times while I was on vacation. There’s something truly magical about being able to control how Outlook behaves with a simple email from your smartphone and a little VBA.

Just keep in mind that this will only work when you’re not logged out of your work computer.

That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.