SyncObject.Stop method (Outlook)

Immediately ends synchronizing a user's folders using the specified Send/Receive group.

Syntax

expression. Stop

expression A variable that represents a SyncObject object.

Remarks

This method does not undo any synchronization that has already occurred.

Example

This Microsoft Visual Basic for Applications (VBA) example displays all the Send/Receive groups set up for the user and starts the synchronization based on the user's response. The subroutine following the one below immediately stops the synchronization. The syc variable is declared as a public variable so it can be referenced by both the subroutines.

Public syc As Outlook.SyncObject 
 
Public Sub Sync() 
 Dim nsp As Outlook.NameSpace 
 Dim sycs As Outlook.SyncObjects 
 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 
 
Private Sub StopSync() 
 MsgBox "Synchronization stopped by the user." 
 syc.Stop 
End Sub

See also

SyncObject 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.