PDA

View Full Version : Outlook Attachments



cosmarchy
02-05-2017, 02:13 PM
I'm trying to save the attachments in an email however I keep getting embedded pictures saved as if they are attachments.

I've found some information on the internet regarding hidden attachments and the code I have is supposed to look for these and filter them out leaving actual attachments.

The trouble is I get an error -2147221233 when I try to use the GetProperties method of PropertyAccessor.

It appears to be trouble with all the properties when I try and get them in this way.

Here is the code

'---------------------------------------------------------------------------------
' The sample scripts are not supported under any Microsoft standard support
' program or service. The sample scripts are provided AS IS without warranty
' of any kind. Microsoft further disclaims all implied warranties including,
' without limitation, any implied warranties of merchantability or of fitness for
' a particular purpose. The entire risk arising out of the use or performance of
' the sample scripts and documentation remains with you. In no event shall
' Microsoft, its authors, or anyone else involved in the creation, production, or
' delivery of the scripts be liable for any damages whatsoever (including,
' without limitation, damages for loss of business profits, business interruption,
' loss of business information, or other pecuniary loss) arising out of the use
' of or inability to use the sample scripts or documentation, even if Microsoft
' has been advised of the possibility of such damages.
'---------------------------------------------------------------------------------

Option Explicit

' *****************
' For Outlook 2010.
' *****************
#If VBA7 Then
' The window handle of Outlook.
Private lHwnd As LongPtr

' /* API declarations. */
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, _
ByVal lpWindowName As String) As LongPtr

' *****************************************
' For the previous version of Outlook 2010.
' *****************************************
#Else
' The window handle of Outlook.
Private lHwnd As Long

' /* API declarations. */
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, _
ByVal lpWindowName As String) As Long
#End If

' The class name of Outlook window.
Private Const olAppCLSN As String = "rctrl_renwnd32"
' Windows desktop - the virtual folder that is the root of the namespace.
Private Const CSIDL_DESKTOP = &H0
' Only return file system directories. If the user selects folders that are not part of the file system, the OK button is grayed.
Private Const BIF_RETURNONLYFSDIRS = &H1
' Do not include network folders below the domain level in the dialog box's tree view control.
Private Const BIF_DONTGOBELOWDOMAIN = &H2
' The maximum length for a path is 260 characters.
Private Const MAX_PATH = 260

' ######################################################
' Returns the number of attachements in the selection.
' ######################################################
Public Function SaveAttachmentsFromSelection() As Long
Dim objFSO As Object ' Computer's file system object.
Dim objShell As Object ' Windows Shell application object.
Dim objFolder As Object ' The selected folder object from Browse for Folder dialog box.
Dim objItem As Object ' A specific member of a Collection object either by position or by key.
Dim selItems As Selection ' A collection of Outlook item objects in a folder.
Dim atmt As Attachment ' A document or link to a document contained in an Outlook item.
Dim strAtmtPath As String ' The full saving path of the attachment.
Dim strAtmtFullName As String ' The full name of an attachment.
Dim strAtmtName(1) As String ' strAtmtName(0): to save the name; strAtmtName(1): to save the file extension. They are separated by dot of an attachment file name.
Dim strAtmtNameTemp As String ' To save a temporary attachment file name.
Dim intDotPosition As Integer ' The dot position in an attachment name.
Dim atmts As Attachments ' A set of Attachment objects that represent the attachments in an Outlook item.
Dim lCountEachItem As Long ' The number of attachments in each Outlook item.
Dim lCountAllItems As Long ' The number of attachments in all Outlook items.
Dim strFolderPath As String ' The selected folder path.
Dim blnIsEnd As Boolean ' End all code execution.
Dim blnIsSave As Boolean ' Consider if it is need to save.

blnIsEnd = False
blnIsSave = False
lCountAllItems = 0

On Error Resume Next

Set selItems = ActiveExplorer.Selection

If Err.Number = 0 Then

' Get the handle of Outlook window.
lHwnd = FindWindow(olAppCLSN, vbNullString)

If lHwnd <> 0 Then

' /* Create a Shell application object to pop-up BrowseForFolder dialog box. */
Set objShell = CreateObject("Shell.Application")
Set objFSO = CreateObject("Scripting.FileSystemObject")
Set objFolder = objShell.BrowseForFolder(lHwnd, "Select folder to save attachments:", _
BIF_RETURNONLYFSDIRS + BIF_DONTGOBELOWDOMAIN, CSIDL_DESKTOP)

' /* Failed to create the Shell application. */
If Err.Number <> 0 Then
MsgBox "Run-time error '" & CStr(Err.Number) & " (0x" & CStr(Hex(Err.Number)) & ")':" & vbNewLine & _
Err.Description & ".", vbCritical, "Error from Attachment Saver"
blnIsEnd = True
GoTo PROC_EXIT
End If

If objFolder Is Nothing Then
strFolderPath = ""
blnIsEnd = True
GoTo PROC_EXIT
Else
strFolderPath = CGPath(objFolder.Self.Path)

' /* Go through each item in the selection. */
For Each objItem In selItems
lCountEachItem = objItem.Attachments.Count

' /* If the current item contains attachments. */
If lCountEachItem > 0 Then
Set atmts = objItem.Attachments

Call DemoPropertyAccessorGetProperties(objItem)


' /* Go through each attachment in the current item. */
For Each atmt In atmts

' Get the full name of the current attachment.
strAtmtFullName = atmt.FileName

' Find the dot postion in atmtFullName.
intDotPosition = InStrRev(strAtmtFullName, ".")

' Get the name.
strAtmtName(0) = Left$(strAtmtFullName, intDotPosition - 1)
' Get the file extension.
strAtmtName(1) = Right$(strAtmtFullName, Len(strAtmtFullName) - intDotPosition)
' Get the full saving path of the current attachment.
strAtmtPath = strFolderPath & atmt.FileName

' /* If the length of the saving path is not larger than 260 characters.*/
If Len(strAtmtPath) <= MAX_PATH Then
' True: This attachment can be saved.
blnIsSave = True

' /* Loop until getting the file name which does not exist in the folder. */
Do While objFSO.FileExists(strAtmtPath)
strAtmtNameTemp = strAtmtName(0) & _
Format(Now, "_mmddhhmmss") & _
Format(Timer * 1000 Mod 1000, "000")
strAtmtPath = strFolderPath & strAtmtNameTemp & "." & strAtmtName(1)

' /* If the length of the saving path is over 260 characters.*/
If Len(strAtmtPath) > MAX_PATH Then
lCountEachItem = lCountEachItem - 1
' False: This attachment cannot be saved.
blnIsSave = False
Exit Do
End If
Loop

' /* Save the current attachment if it is a valid file name. */
If blnIsSave Then atmt.SaveAsFile strAtmtPath
Else
lCountEachItem = lCountEachItem - 1
End If
Next
End If

' Count the number of attachments in all Outlook items.
lCountAllItems = lCountAllItems + lCountEachItem
Next
End If
Else
MsgBox "Failed to get the handle of Outlook window!", vbCritical, "Error from Attachment Saver"
blnIsEnd = True
GoTo PROC_EXIT
End If

' /* For run-time error:
' The Explorer has been closed and cannot be used for further operations.
' Review your code and restart Outlook. */
Else
MsgBox "Please select an Outlook item at least.", vbExclamation, "Message from Attachment Saver"
blnIsEnd = True
End If

PROC_EXIT:
SaveAttachmentsFromSelection = lCountAllItems

' /* Release memory. */
If Not (objFSO Is Nothing) Then Set objFSO = Nothing
If Not (objItem Is Nothing) Then Set objItem = Nothing
If Not (selItems Is Nothing) Then Set selItems = Nothing
If Not (atmt Is Nothing) Then Set atmt = Nothing
If Not (atmts Is Nothing) Then Set atmts = Nothing

' /* End all code execution if the value of blnIsEnd is True. */
If blnIsEnd Then End
End Function

' #####################
' Convert general path.
' #####################
Public Function CGPath(ByVal Path As String) As String
If Right(Path, 1) <> "\" Then Path = Path & "\"
CGPath = Path
End Function

' ######################################
' Run this macro for saving attachments.
' ######################################
Public Sub ExecuteSaving()
Dim lNum As Long

lNum = SaveAttachmentsFromSelection

If lNum > 0 Then
MsgBox CStr(lNum) & " attachment(s) was(were) saved successfully.", vbInformation, "Message from Attachment Saver"
Else
MsgBox "No attachment(s) in the selected Outlook items.", vbInformation, "Message from Attachment Saver"
End If
End Sub

Function DemoPropertyAccessorGetProperties(oMail)
Dim PropNames() As Variant
Dim myValues As Variant
Dim i As Integer
Dim j As Integer
''Dim oMail As Object
Dim oPA As Outlook.PropertyAccessor
Dim propArray

'Get first item in the inbox
''Set oMail = Application.Session.GetDefaultFolder(olFolderInbox).Items(1)

'PR_SUBJECT, PR_ATTR_HIDDEN, PR_ATTR_READONLY, PR_ATTR_SYSTEM
PropNames = Array("http://schemas.microsoft.com/mapi/proptag/0x0037001E", _
"http://schemas.microsoft.com/mapi/proptag/0x10F4000B", _
"http://schemas.microsoft.com/mapi/proptag/0x10F6000B", _
"http://schemas.microsoft.com/mapi/proptag/0x10F5000B")

'Obtain an instance of a PropertyAccessor object
Set oPA = oMail.PropertyAccessor

'Get myValues array with GetProperties call
myValues = oPA.GetProperties(PropNames)

For i = LBound(myValues) To UBound(myValues)
'Examine the type of the element
If IsError(myValues(i)) Then
'CVErr returns a variant of subtype error
Debug.Print (CVErr(myValues(i))) 'ERRORS HERE -2147221233
ElseIf IsArray(myValues(i)) Then
propArray = myValues(i)
For j = LBound(propArray) To UBound(propArray)
Debug.Print (propArray(j))
Next
ElseIf IsNull(myValues(i)) Then
Debug.Print ("Null value")
ElseIf IsEmpty(myValues(i)) Then
Debug.Print ("Empty value")
ElseIf IsDate(myValues(i)) Then
Debug.Print (oPA.UTCToLocalTime(myValues(i)))
'VB does not have IsBinary function
ElseIf VarType(myValues(i)) = vbByte Then
Debug.Print (oPA.BinaryToString(myValues(i)))
Else
Debug.Print (myValues(i))
End If
Next

End Function


Any assistance is appreciated.

Thanks

gmayor
02-05-2017, 09:43 PM
I am not even going to try and debug that -ask where you obtained the macro, however I find the following works. The main code will run from a rule. The Process Folder macro requires a userform progress indicator, which you can download from http://www.gmayor.com/Forum/frmProgress.zip . The macro will create the named folder if it doesn't exist and no similarly named attachments will be overwritten


Option Explicit

Sub ProcessAttachment()
'An Outlook macro by Graham Mayor
Dim olMsg As MailItem
On Error Resume Next
Set olMsg = ActiveExplorer.Selection.Item(1)
SaveAttachments olMsg
lbl_Exit:
Exit Sub
End Sub

Sub ProcessFolder()
'An Outlook macro by Graham Mayor
Dim olNS As Outlook.NameSpace
Dim olMailFolder As Outlook.MAPIFolder
Dim olItems As Outlook.Items
Dim olMailItem As Outlook.MailItem
Dim oFrm As New frmProgress
Dim PortionDone As Double
Dim i As Long

On Error GoTo err_handler
Set olNS = GetNamespace("MAPI")
Set olMailFolder = olNS.PickFolder
Set olItems = olMailFolder.Items
oFrm.Show vbModeless
i = 0
For Each olMailItem In olItems
i = i + 1
PortionDone = i / olItems.Count
oFrm.lblProgress.Width = oFrm.fmeProgress.Width * PortionDone
SaveAttachments olMailItem
DoEvents
Next olMailItem
err_handler:
Unload oFrm
Set oFrm = Nothing
Set olNS = Nothing
Set olMailFolder = Nothing
Set olItems = Nothing
Set olMailItem = Nothing
lbl_Exit:
Exit Sub
End Sub


Private Sub SaveAttachments(olItem As MailItem)
'An Outlook macro by Graham Mayor
Dim olAttach As Attachment
Dim strFname As String
Dim strExt As String
Dim j As Long
Const strSaveFldr As String = "C:\Outlook\Attachments\"

CreateFolders strSaveFldr
On Error GoTo CleanUp
If olItem.Attachments.Count > 0 Then
For j = olItem.Attachments.Count To 1 Step -1
Set olAttach = olItem.Attachments(j)
If Not olAttach.fileName Like "image*.*" Then
strFname = olAttach.fileName
strExt = Right(strFname, Len(strFname) - InStrRev(strFname, Chr(46)))
strFname = FileNameUnique(strSaveFldr, strFname, strExt)
olAttach.SaveAsFile strSaveFldr & strFname
'olAttach.Delete 'delete the attachment
End If
Next j
olItem.Save
End If
CleanUp:
Set olAttach = Nothing
Set olItem = Nothing
lbl_Exit:
Exit Sub
End Sub

Private Function FileNameUnique(strPath As String, _
strFileName As String, _
strExtension As String) As String
'An Outlook macro by Graham Mayor
Dim lngF As Long
Dim lngName As Long
lngF = 1
lngName = Len(strFileName) - (Len(strExtension) + 1)
strFileName = Left(strFileName, lngName)
Do While FileExists(strPath & strFileName & Chr(46) & strExtension) = True
strFileName = Left(strFileName, lngName) & "(" & lngF & ")"
lngF = lngF + 1
Loop
FileNameUnique = strFileName & Chr(46) & strExtension
lbl_Exit:
Exit Function
End Function

Private Function FileExists(filespec) As Boolean
'An Outlook macro by Graham Mayor
Dim fso As Object
Set fso = CreateObject("Scripting.FileSystemObject")
If fso.FileExists(filespec) Then
FileExists = True
Else
FileExists = False
End If
lbl_Exit:
Exit Function
End Function

Private Function FolderExists(fldr) As Boolean
'An Outlook macro by Graham Mayor
Dim fso As Object
Set fso = CreateObject("Scripting.FileSystemObject")
If (fso.FolderExists(fldr)) Then
FolderExists = True
Else
FolderExists = False
End If
lbl_Exit:
Exit Function
End Function

Private Function CreateFolders(strPath As String)
'An Outlook macro by Graham Mayor
Dim strTempPath As String
Dim lngPath As Long
Dim vPath As Variant
vPath = Split(strPath, "\")
strPath = vPath(0) & "\"
For lngPath = 1 To UBound(vPath)
strPath = strPath & vPath(lngPath) & "\"
If Not FolderExists(strPath) Then MkDir strPath
Next lngPath
lbl_Exit:
Exit Function
End Function

skatonni
02-06-2017, 07:28 AM
With


If Not olAttach.fileName Like "image*.*" Then

the user has to first determine all the possible names.

There is a PR_ATTACHMENT_HIDDEN property that could be used, but it brings its own problems.


Private Sub AttachmentsHidden()

' Remove the and
Const PR_ATTACHMENT_HIDDEN = "http://schemas.microsoft.com/mapi/proptag/0x7FFE000B"

Dim olkMsg As mailItem
Dim olkPA As propertyAccessor
Dim att As attachment

Dim attFileName As String

Set olkMsg = ActiveInspector.currentItem
Debug.Print "Subject: " & olkMsg.Subject

For Each att In olkMsg.Attachments

Set olkPA = att.propertyAccessor

attFileName = "File without a name"
On Error Resume Next
' Behaviour sometimes seen in my mail.
' Image in signature, no FileName, not hidden file
attFileName = att.FileName
On Error GoTo 0

If olkPA.GetProperty(PR_ATTACHMENT_HIDDEN) = False Then

' Save when not hidden and
' attFileName is not "File without a name"
Debug.Print " " & attFileName & ": Not hidden"

Else

Debug.Print " " & attFileName & ": Hidden"

End If

Next

ExitRoutine:
Set olkMsg = Nothing
Set olkPA = Nothing
Set att = Nothing

Debug.Print "Done."
End Sub