2
votes

I'm trying to create a VBA macro that will look into the A column, find all unique email addresses, create a new outlook email for each and populate the body of that email with the rows where that email is present (also including the header).

Example data:

+----------------+---------------------+---------+
|     Email      |     Application     | Version |
+----------------+---------------------+---------+
| [email protected] | Microsoft_Office_13 | v2.0    |
| [email protected] | Putty               | v3.0    |
| [email protected] | Notepad             | v5.6    |
| [email protected] | Microsoft_Office_13 | v2.0    |
| [email protected] | Putty               | v3.0    |
| [email protected] | Adobe_Reader        | v6.4    |
| [email protected] | Microsoft_Office_13 | v3.6    |
| [email protected] | Paint               | v6.4    |
| [email protected] | Adobe_Reader        | v6.4    |
+----------------+---------------------+---------+

This is what I was able to find in my research, but it will create an email for every time the address is listed. It also doesn't really have any code which shows how to pull a range of cells into the body.

Sub Test1()
    Dim OutApp As Object
    Dim OutMail As Object
    Dim cell As Range

    Application.ScreenUpdating = False
    Set OutApp = CreateObject("Outlook.Application")

    On Error GoTo cleanup
    For Each cell In Columns("A").Cells.SpecialCells(xlCellTypeConstants)
        If cell.Value Like "?*@?*.?*" And _
           LCase(Cells(cell.Row, "C").Value) = "yes" Then

            Set OutMail = OutApp.CreateItem(0)
            On Error Resume Next
            With OutMail
                .To = cell.Value
                .Subject = "Reminder"
                .Body = "Hi, please find your account permissions below:"
                .Display
            End With
            On Error GoTo 0
            Set OutMail = Nothing
        End If
    Next cell

cleanup:
    Set OutApp = Nothing
    Application.ScreenUpdating = True
End Sub

The desired email output would be something like:

Hi, please find your account permissions below:

+----------------+---------------------+---------+
|     Email      |     Application     | Version |
+----------------+---------------------+---------+
| [email protected] | Microsoft_Office_13 | v2.0    |
| [email protected] | Putty               | v3.0    |
| [email protected] | Adobe_Reader        | v6.4    |
+----------------+---------------------+---------+
3
Maybe this is of helpStorax

3 Answers

0
votes

I used the code from my answer mentioned in the comment and modified it. Create a class and name it AppInfo. Here you find how to do that

Option Explicit

Public app As String
Public version As String

Then put the following code into a module. The asumption is that the data is in the active sheet starting in A1 with the header Email, Application and Version.

Option Explicit

Sub Consolidate()

#If Early Then
    Dim emailInformation As New Scripting.Dictionary
#Else
    Dim emailInformation As Object
    Set emailInformation = CreateObject("Scripting.Dictionary")
#End If

    GetEmailInformation emailInformation
    SendInfoEmail emailInformation
End Sub


Sub GetEmailInformation(emailInformation As Object)

Dim rg As Range
Dim sngRow As Range

Dim emailAddress As String
Dim myAppInfo As AppInfo
Dim AppInfos As Collection

Set rg = Range("A1").CurrentRegion    ' Assuming the list starts in A1 and DOES NOT contain empty row
Set rg = rg.Offset(1).Resize(rg.Rows.Count - 1)    ' Cut the headings

    For Each sngRow In rg.Rows

        emailAddress = sngRow.Cells(1, 1)

        Set myAppInfo = New AppInfo
        With myAppInfo
            .app = sngRow.Cells(1, 2)
            .version = sngRow.Cells(1, 3)
        End With

        If emailInformation.Exists(emailAddress) Then
            emailInformation.item(emailAddress).Add myAppInfo
        Else
            Set AppInfos = New Collection
            AppInfos.Add myAppInfo
            emailInformation.Add emailAddress, AppInfos
        End If

    Next

End Sub
Sub SendInfoEmail(emailInformation As Object)

Dim sBody As String
Dim sBodyStart As String
Dim sBodyInfo As String
Dim sBodyEnd As String
Dim emailAdress As Variant
Dim colLines As Collection
Dim line As Variant

    sBodyStart = "Hi, please find your account permissions below:" & vbCrLf


    For Each emailAdress In emailInformation
        Set colLines = emailInformation(emailAdress)
        sBodyInfo = ""
        For Each line In colLines
            sBodyInfo = sBodyInfo & _
                         "Application: " & line.app & vbTab & "Version:" & line.version & vbCrLf
        Next
        sBodyEnd = "Best Regards" & vbCrLf & _
                   "Team"

        sBody = sBodyStart & sBodyInfo & sBodyEnd
        SendEmail emailAdress, "Permissions", sBody
    Next


End Sub

Sub SendEmail(ByVal sTo As String _
              , ByVal sSubject As String _
                , ByVal sBody As String _
                  , Optional ByRef coll As Collection)


    #If Early Then
        Dim ol As Outlook.Application
        Dim outMail As Outlook.MailItem
        Set ol = New Outlook.Application
    #Else
        Dim ol As Object
        Dim outMail As Object
        Set ol = CreateObject("Outlook.Application")
    #End If

    Set outMail = ol.CreateItem(0)

    With outMail
        .To = sTo
        .Subject = sSubject
        .Body = sBody
        If Not (coll Is Nothing) Then
            Dim item As Variant
            For Each item In coll
                .Attachments.Add item
            Next
        End If

        .Display
        '.Send
    End With

    Set outMail = Nothing

End Sub
0
votes

You can do this in different ways, but I am just giving you a quick answer that will solve your problem. I used a function developed by Ron de Bruin to convert the range to an html body.

  • I deleted one of the conditions to check the content of the cells in column A so make sure you put it back and test it with your own data

  • I used a dictionary to store the emails we generate the outlook instance so if in the other cells you have the same email you would not generate the email again

  • you need to use an html body instead of body in the outlook new item so that you have more options to quickly paste your content and format it (color, size, font etc)

    Option Explicit
    
    
    Sub Test1()
        Dim OutApp As Object
        Dim OutMail As Object
        Dim dict As Object 'keep the unique list of emails
        Dim cell As Range
        Dim cell2 As Range
        Dim rng As Range
        Dim i As Long
        Dim WS As Worksheet
    
        Application.ScreenUpdating = False
        Set OutApp = CreateObject("Outlook.Application")
        Set dict = CreateObject("scripting.dictionary")
        Set WS = ThisWorkbook.Sheets("Sheet1") 'change the name of the sheet accordingly
    
        On Error GoTo cleanup
        For Each cell In WS.Columns("A").Cells.SpecialCells(xlCellTypeConstants)
            If cell.Value Like "?*@?*.?*" Then
    
                'check if this email address has been used to generate an outlook email or not
                If dict.exists(cell.Value) = False Then
    
                    dict.Add cell.Value, "" 'add the new email address
                    Set OutMail = OutApp.CreateItem(0)
                    Set rng = WS.UsedRange.Rows(1)
    
                    'find all of the rows with the same email and add it to the range
                    For Each cell2 In WS.UsedRange.Columns(1).Cells
                        If cell2.Value = cell.Value Then
                            Set rng = Application.Union(rng, WS.UsedRange.Rows(cell2.Row))
                        End If
                    Next cell2
    
                    On Error Resume Next
                    With OutMail
                        .To = cell.Value
                        .Subject = "Reminder"
                        .HTMLBody = "Hi, please find your account permissions below:" & vbNewLine & vbNewLine & RangetoHTML(rng)
                        .Display
                    End With
    
                    On Error GoTo 0
                    Set OutMail = Nothing
                End If
            End If
        Next cell
    
    cleanup:
        Set OutApp = Nothing
        Application.ScreenUpdating = True
    End Sub
    
    Function RangetoHTML(rng As Range)
    ' coded by Ron de Bruin 28-Oct-2006
    ' Working in Office 2000-2016
        Dim fso As Object
        Dim ts As Object
        Dim TempFile As String
        Dim TempWB As Workbook
    
        TempFile = Environ$("temp") & "\" & Format(Now, "dd-mm-yy h-mm-ss") & ".htm"
    
        'Copy the range and create a new workbook to past the data in
        rng.Copy
        Set TempWB = Workbooks.Add(1)
        With TempWB.Sheets(1)
            .Cells(1).PasteSpecial Paste:=8
            .Cells(1).PasteSpecial xlPasteValues, , False, False
            .Cells(1).PasteSpecial xlPasteFormats, , False, False
            .Cells(1).Select
            Application.CutCopyMode = False
            On Error Resume Next
            .DrawingObjects.Visible = True
            .DrawingObjects.Delete
            On Error GoTo 0
        End With
    
        'Publish the sheet to a htm file
        With TempWB.PublishObjects.Add( _
             SourceType:=xlSourceRange, _
             Filename:=TempFile, _
             Sheet:=TempWB.Sheets(1).Name, _
             Source:=TempWB.Sheets(1).UsedRange.Address, _
             HtmlType:=xlHtmlStatic)
            .Publish (True)
        End With
    
        'Read all data from the htm file into RangetoHTML
        Set fso = CreateObject("Scripting.FileSystemObject")
        Set ts = fso.GetFile(TempFile).OpenAsTextStream(1, -2)
        RangetoHTML = ts.readall
        ts.Close
        RangetoHTML = Replace(RangetoHTML, "align=center x:publishsource=", _
                              "align=left x:publishsource=")
    
        'Close TempWB
        TempWB.Close savechanges:=False
    
        'Delete the htm file we used in this function
        Kill TempFile
    
        Set ts = Nothing
        Set fso = Nothing
        Set TempWB = Nothing
    End Function
    
0
votes

Simplest way, in my opinion, would be to format your table as a table in Excel (which will enable search and sort). Then you could do something like e.g.

email = "[email protected]"
Set ws = ThisWorkbook.Worksheets("Sheet1")
Set tbl = ws.ListObjects("Table1")
tbl.Range.AutoFilter Field:=1, Criteria1:=email
Set data = tbl.DataBodyRange
If (data.Rows.Count = 0) Then Exit Sub

If execution makes it past the check (data.Rows.Count > 0) then you can send a mailer using HTML:

Set app = CreateObject("Outlook.Application")
Set mail = OutApp.CreateItem(0)
bodyText = "<BODY style=font-size:11pt;font-family:Calibri>" & _
            " Hi, please find your account permissions below: <br> </BODY> "
With mail
    .To = email
    .Subject = "Email title here."
    .HTMLBody = bodyText & "<p>" & RangeToHTML(data)
    .Importance = 1 ' normal
    .Display
End With

which requires the following helper function:

Function RangeToHTML(rng As Range) As String

Dim fso As Object
Dim ts As Object
Dim tempFile As String
Dim tempWB As Workbook

    tempFile = Environ$("temp") & "/" & Format(Now, "dd-mm-yy h-mm-ss") & ".htm"

    'Copy the range and create a new workbook to past the data in
    rng.Copy
    Set tempWB = Workbooks.Add(1)
    With tempWB.Sheets(1)
        .Cells(1).PasteSpecial Paste:=8
        .Cells(1).PasteSpecial xlPasteValues, , False, False
        .Cells(1).PasteSpecial xlPasteFormats, , False, False
        .Cells(1).Select
        Application.CutCopyMode = False
        On Error Resume Next
        .DrawingObjects.Visible = True
        .DrawingObjects.Delete
        On Error GoTo 0
    End With

    'Publish the sheet to a htm file
    With tempWB.PublishObjects.Add( _
         SourceType:=xlSourceRange, _
         Filename:=tempFile, _
         Sheet:=tempWB.Sheets(1).name, _
         Source:=tempWB.Sheets(1).UsedRange.Offset(1).Address, _
         HtmlType:=xlHtmlStatic)
        .Publish (True)
    End With

    'Read all data from the htm file into RangetoHTML
    Set fso = CreateObject("Scripting.FileSystemObject")
    Set ts = fso.GetFile(tempFile).OpenAsTextStream(1, -2)
    RangeToHTML = ts.ReadAll
    ts.Close
    RangeToHTML = Replace(RangeToHTML, _
                    "align=center x:publishsource=", "align=left x:publishsource=")

    tempWB.Close savechanges:=False
    Kill tempFile

    Set ts = Nothing
    Set fso = Nothing
    Set tempWB = Nothing

End Function

You can modify as needed.