共用方式為


從資料夾路徑取得 Folder 物件

本主題顯示接受資料夾路徑並傳回 Folder 物件的函式,該物件對應至指定的資料夾。 例如,如果您提供資料夾路徑 「Mailbox - Dan Wilson\Inbox\Customers」,如果 [客戶] 資料夾存在於 [收件匣] 底下,程式中的 TestGetFolder 程式碼會顯示與 Dan Wilson 的 [收件匣] 下 [Customers] 資料夾對應的 Folder 物件。 如果 Customers 資料夾不存在, GetFolder 則 會傳回 Nothing

Function GetFolder(ByVal FolderPath As String) As Outlook.Folder 
    Dim TestFolder As Outlook.Folder 
    Dim FoldersArray As Variant 
    Dim i As Integer 
 
    On Error GoTo GetFolder_Error 
    If Left(FolderPath, 2) = "\\" Then 
        FolderPath = Right(FolderPath, Len(FolderPath) - 2) 
    End If 
    
    'Convert folderpath to array 
    FoldersArray = Split(FolderPath, "\") 
    Set TestFolder = Application.Session.Folders.item(FoldersArray(0)) 
    If Not TestFolder Is Nothing Then 
        For i = 1 To UBound(FoldersArray, 1) 
            Dim SubFolders As Outlook.Folders 
            Set SubFolders = TestFolder.Folders 
            Set TestFolder = SubFolders.item(FoldersArray(i)) 
            If TestFolder Is Nothing Then 
                Set GetFolder = Nothing 
            End If 
        Next 
    End If 
     
   'Return the TestFolder 
    Set GetFolder = TestFolder 
    Exit Function 
 
GetFolder_Error: 
    Set GetFolder = Nothing 
    Exit Function 
End Function 
 
Sub TestGetFolder() 
    Dim folder As Outlook.Folder 
    Set folder = GetFolder ("\\Mailbox - Dan Wilson\Inbox\Customers") 
    If Not(folder Is Nothing) Then 
        folder.Display 
    End If 
End Sub

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應