Attachments.Remove method (Outlook)
Removes an object from the collection.
Syntax
expression.Remove (Index)
expression A variable that represents an Attachments object.
Parameters
Name | Required/Optional | Data type | Description |
---|---|---|---|
Index | Required | Long | The 1-based index value of the object within the collection. |
Example
This Visual Basic for Applications (VBA) example uses the Remove method to remove all attachments from a forwarded message before sending it on to Dan Wilson. Before running this example, replace 'Dan Wilson' with a valid recipient name.
Sub RemoveAttachmentBeforeForwarding()
Dim myinspector As Outlook.Inspector
Dim myItem As Outlook.MailItem
Dim myattachments As Outlook.Attachments
Set myinspector = Application.ActiveInspector
If Not TypeName(myinspector) = "Nothing" Then
Set myItem = myinspector.CurrentItem.Forward
Set myattachments = myItem.Attachments
While myattachments.Count > 0
myattachments.Remove 1
Wend
myItem.Display
myItem.Recipients.Add "Dan Wilson"
myItem.Send
Else
MsgBox "There is no active inspector."
End If
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.