Store.GetRootFolder method (Outlook)

Returns a Folder object representing the root-level folder of the Store. Read-only.

Syntax

expression. GetRootFolder

expression A variable that represents a Store object.

Return value

A Folder object that represents the folder at the root of that Store.

Remarks

Use the GetRootFolder method to enumerate the subfolders of the root folder of the Store. Unlike NameSpace.Folders which contains all folders for all stores in the current profile, Store.GetRootFolder.Folders allows you to enumerate all folders for a given Store object in the current profile.

The Parent property of the root folder of a store returns the string "Mapi".

The root folder for the Exchange Public Folder store is the folder Public Folders. This folder is returned by the call to Application.Session.GetDefaultFolder(olPublicFoldersAllPublicFolders).

GetRootFolder returns an error if the service provider does not support root folders.

Example

The following code sample in Microsoft Visual Basic for Applications (VBA) starts at the root-level folder of each Store in a Stores collection for a session, and enumerates all folders on all stores for that session.

Sub EnumerateFoldersInStores() 
 
 Dim colStores As Outlook.Stores 
 
 Dim oStore As Outlook.Store 
 
 Dim oRoot As Outlook.Folder 
 
 
 
 On Error Resume Next 
 
 Set colStores = Application.Session.Stores 
 
 For Each oStore In colStores 
 
 Set oRoot = oStore.GetRootFolder 
 
 Debug.Print (oRoot.FolderPath) 
 
 EnumerateFolders oRoot 
 
 Next 
 
End Sub 
 
 
 
Private Sub EnumerateFolders(ByVal oFolder As Outlook.Folder) 
 
 Dim folders As Outlook.folders 
 
 Dim Folder As Outlook.Folder 
 
 Dim foldercount As Integer 
 
 
 
 On Error Resume Next 
 
 Set folders = oFolder.folders 
 
 foldercount = folders.Count 
 
 'Check if there are any folders below oFolder 
 
 If foldercount Then 
 
 For Each Folder In folders 
 
 Debug.Print (Folder.FolderPath) 
 
 EnumerateFolders Folder 
 
 Next 
 
 End If 
 
End Sub

See also

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