Folder.FolderPath property (Outlook)

Returns a String that indicates the path of the current folder. Read-only.

Syntax

expression. FolderPath

expression A variable that represents a Folder object.

Example

The following example displays information about the default Contacts folder. The subroutine accepts a Folder object and displays the folder's name, path, and address book information.

Sub Folderpaths() 
 
 Dim nmsName As NameSpace 
 
 Dim fldFolder As Folder 
 
 
 
 'Create namespace reference 
 
 Set nmsName = Application.GetNamespace("MAPI") 
 
 'create folder instance 
 
 Set fldFolder = nmsName.GetDefaultFolder(olFolderContacts) 
 
 'call sub program 
 
 Call FolderInfo(fldFolder) 
 
End Sub 
 
 
 
Sub FolderInfo(ByVal fldFolder As Folder) 
 
 'Displays information about a given folder 
 
 MsgBox fldFolder.Name & "'s current path is " & _ 
 
 fldFolder.FolderPath & _ 
 
 ". The current address book name is " & fldFolder.AddressBookName & "." 
 
End Sub

See also

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