NameSpace.GetSharedDefaultFolder method (Outlook)

Returns a Folder object that represents the specified default folder for the specified user.

Syntax

expression. GetSharedDefaultFolder( _Recipient_ , _FolderType_ )

expression A variable that represents a NameSpace object.

Parameters

Name Required/Optional Data type Description
Recipient Required Recipient The owner of the folder. Note that the Recipient object must be resolved.
FolderType Required OlDefaultFolders The type of folder.

Return value

A Folder object that represents the specified default folder for the specified user.

Remarks

This method is used in a delegation scenario, where one user has delegated access to another user for one or more of their default folders (for example, their shared Calendar folder).

FolderType can be one of the following OlDefaultFolders constants: olFolderCalendar, olFolderContacts, olFolderDrafts, olFolderInbox, olFolderJournal, olFolderNotes, or olFolderTasks. (The constants olFolderDeletedItems, olFolderOutbox, olFolderJunk, olFolderConflicts, olFolderLocalFailures, olFolderServerFailures, olFolderSyncIssues, olPublicFoldersAllPublicFolders, olFolderRssSubscriptions, olFolderToDo, olFolderManagedEmail, and olFolderSentMail cannot be specified for this argument.)

Example

This Visual Basic for Applications (VBA) example uses the GetSharedDefaultFolder method to resolve the Recipient object representing Dan Wilson, and then returns Dan's shared default Calendar folder.

Sub ResolveName() 
 
 Dim myNamespace As Outlook.NameSpace 
 
 Dim myRecipient As Outlook.Recipient 
 
 Dim CalendarFolder As Outlook.Folder 
 
 
 
 Set myNamespace = Application.GetNamespace("MAPI") 
 
 Set myRecipient = myNamespace.CreateRecipient("Dan Wilson") 
 
 myRecipient.Resolve 
 
 If myRecipient.Resolved Then 
 
 Call ShowCalendar(myNamespace, myRecipient) 
 
 End If 
 
End Sub 
 
 
 
Sub ShowCalendar(myNamespace, myRecipient) 
 
 Dim CalendarFolder As Outlook.Folder 
 
 
 
 Set CalendarFolder = _ 
 
 myNamespace.GetSharedDefaultFolder _ 
 
 (myRecipient, olFolderCalendar) 
 
 CalendarFolder.Display 
 
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.