NameSpace.OpenSharedFolder method (Outlook)

Opens a shared folder referenced through a URL or file name.

Syntax

expression. OpenSharedFolder( _Path_ , _Name_ , _DownloadAttachments_ , _UseTTL_ )

expression An expression that returns a NameSpace object.

Parameters

Name Required/Optional Data type Description
Path Required String The URL or local file name of the shared folder to be opened.
Name Optional Variant The name of the Really Simple Syndication (RSS) feed or Webcal calendar. This parameter is ignored for other shared folder types.
DownloadAttachments Optional Variant Indicates whether to download enclosures (for RSS feeds) or attachments (for Webcal calendars.) This parameter is ignored for other shared folder types.
UseTTL Optional Variant Indicates whether the Time To Live (TTL) setting in an RSS feed or WebCal calendar should be used. This parameter is ignored for other shared folder types.

Return value

A Folder object that represents the shared folder.

Remarks

This method is used to access the following shared folder types:

  • Webcal calendars (webcal:// mysite / mycalendar )

  • RSS feeds (feed:// mysite / myfeed )

  • Microsoft SharePoint Foundation folders (stssync:// mysite / myfolder )

  • iCalendar calendar (.ics) files

  • vCard contact (.vcf) files

  • Outlook message (.msg) files

Note

This method does not support iCalendar appointment (.ics) files. To open iCalendar appointment files, you can use the OpenSharedItem method of the NameSpace object.

Use the GetSharedDefaultFolder method of the Namespace object to share default folders, such as the Inbox folder, in Exchange.

Example

The following Visual Basic for Applications (VBA) example opens and displays a Webcal calendar.

Public Sub OpenSharedHolidayCalendar() 
 
 
 
 Dim oNamespace As NameSpace 
 
 Dim oFolder As Folder 
 
 
 
 On Error GoTo ErrRoutine 
 
 
 
 Set oNamespace = Application.GetNamespace("MAPI") 
 
 Set oFolder = oNamespace.OpenSharedFolder( _ 
 
 "webcal://icalx.com/public/icalshare/US32Holidays.ics") 
 
 oFolder.Display 
 
 
 
EndRoutine: 
 
 On Error GoTo 0 
 
 Set oFolder = Nothing 
 
 Set oNamespace = Nothing 
 
Exit Sub 
 
 
 
ErrRoutine: 
 
 MsgBox Err.Description, vbOKOnly, Err.Number & " - " & Err.Source 
 
 GoTo EndRoutine 
 
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.