Application.NewMail event (Outlook)
Occurs when one or more new email messages are received in the Inbox.
Syntax
expression. NewMail
expression A variable that represents an Application object.
Remarks
This event is not available in Microsoft Visual Basic Scripting Edition (VBScript).
The NewMail event fires when new messages arrive in the Inbox and before client rule processing occurs. If you want to process items that arrive in the Inbox, consider using the ItemAdd event on the collection of items in the Inbox. The ItemAdd event passes a reference to each item that is added to a folder.
The NewMail event does not fire when the user is in offline mode.
Example
This Microsoft Visual Basic for Applications (VBA) example displays the Inbox folder when a new email message arrives. The sample code must be placed in a class module, and the Initialize_handler
routine must be called before the event procedure can be called by Microsoft Outlook.
Public WithEvents myOlApp As Outlook.Application
Sub Initialize_handler()
Set myOlApp = Outlook.Application
End Sub
Private Sub myOlApp_NewMail()
Dim myExplorers As Outlook.Explorers
Dim myFolder As Outlook.Folder
Dim x As Integer
Set myExplorers = myOlApp.Explorers
Set myFolder = myOlApp.GetNamespace("MAPI").GetDefaultFolder(olFolderInbox)
If myExplorers.Count <> 0 Then
For x = 1 To myExplorers.Count
On Error GoTo skipif
If myExplorers.Item(x).CurrentFolder.Name = "Inbox" Then
myExplorers.Item(x).Display
myExplorers.Item(x).Activate
Exit Sub
End If
skipif:
Next x
End If
On Error GoTo 0
myFolder.Display
End Sub
See also
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.