NameSpace.SyncObjects property (Outlook)

Returns a SyncObjects collection containing all Send\Receive groups. Read-only.

Syntax

expression. SyncObjects

expression A variable that represents a NameSpace object.

Example

This Microsoft Visual Basic for Applications (VBA) example displays all the Send and Receive groups set up for the user and starts the synchronization based on the user's response.

Public Sub Sync() 
 
 Dim nsp As Outlook.NameSpace 
 
 Dim sycs As Outlook.SyncObjects 
 
 Dim syc As Outlook.SyncObject 
 
 Dim i As Integer 
 
 Dim strPrompt As Integer 
 
 Set nsp = Application.GetNamespace("MAPI") 
 
 Set sycs = nsp.SyncObjects 
 
 For i = 1 To sycs.Count 
 
 Set syc = sycs.Item(i) 
 
 strPrompt = MsgBox("Do you wish to synchronize " & syc.Name &"?", vbYesNo) 
 
 If strPrompt = vbYes Then 
 
 syc.Start 
 
 End If 
 
 Next 
 
End Sub

See also

NameSpace Object

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.