MailItem.Move method (Outlook)
Moves a Microsoft Outlook item to a new folder.
Syntax
expression. Move
( _DestFldr_
)
expression A variable that represents a MailItem object.
Parameters
Name | Required/Optional | Data type | Description |
---|---|---|---|
DestFldr | Required | Folder | An expression that returns a Folder object. The destination folder. |
Return value
An Object value that represents the item which has been moved to the designated folder.
Example
This Visual Basic for Applications (VBA) example uses GetDefaultFolder to return the Folder object that represents the default folder. It then uses the Find and FindNext methods to find all messages sent by Dan Wilson and uses the Move method to move all email messages sent by Dan Wilson from the default Inbox folder to the Personal Mail folder. To run this example without any errors, replace 'Dan Wilson' with a vaid sender name and make sure there's a folder under Inbox called 'Personal Mail'. Note that myItem
is declared as type Object so that it can represent all types of Outlook items including meeting request and task request items.
Sub MoveItems()
Dim myNameSpace As Outlook.NameSpace
Dim myInbox As Outlook.Folder
Dim myDestFolder As Outlook.Folder
Dim myItems As Outlook.Items
Dim myItem As Object
Set myNameSpace = Application.GetNamespace("MAPI")
Set myInbox = myNameSpace.GetDefaultFolder(olFolderInbox)
Set myItems = myInbox.Items
Set myDestFolder = myInbox.Folders("Personal Mail")
Set myItem = myItems.Find("[SenderName] = 'Dan Wilson'")
While TypeName(myItem) <> "Nothing"
myItem.Move myDestFolder
Set myItem = myItems.FindNext
Wend
End Sub
See also
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.