Results 1 to 7 of 7

Thread: Extract Email Details For All Incoming Mails Using VBA In Outlook

  1. #1
    Junior Member
    Join Date
    May 2013
    Posts
    4
    Rep Power
    0

    Extract Email Details For All Incoming Mails Using VBA In Outlook

    Hi,

    I need a macro, which need to pull the below mentioned details frwom Outlook (when receving new.ema) to Excel Sheet.

    Details Required:
    1. From Address
    2. Subject
    3. Received Date and Time
    4. Categories

    Could pls try it and send me the macro codings!

    Thanks
    G.vivek.

  2. #2
    Senior Member
    Join Date
    Jun 2012
    Posts
    337
    Rep Power
    13
    How much are you willing to pay for that code ?


    NB this forum isn't a software firm for free code !

  3. #3
    Administrator Excel Fox's Avatar
    Join Date
    Mar 2011
    Posts
    1,402
    Rep Power
    10
    In agreement with snb. We can help you with specific queries that you may come across in your projects, but we don't generally undertake entire projects as a whole. This is an online help community.

    EDIT: Sharing the code that I had with me in the next post.
    Last edited by Excel Fox; 05-24-2013 at 11:37 PM. Reason: Additional Info+Modification
    A dream is not something you see when you are asleep, but something you strive for when you are awake.

    It's usually a bad idea to say that something can't be done.

    The difference between dream and aim, is that one requires soundless sleep to see and the other requires sleepless efforts to achieve

    Join us at Facebook

  4. #4
    Administrator Excel Fox's Avatar
    Join Date
    Mar 2011
    Posts
    1,402
    Rep Power
    10
    For the sake of posterity, I'm editing my comment above, and pasting the modified version of a solution that I had shared with someone a few months before.

    Use this in the ThisOutlookSession module of the Outlook Application

    Code:
    Const strFilePath As String = "C:\Users\ExcelFox\Documents\Excel\OutlookMailItemsDB.xlsx"
    Const strSubjectLineStartWith As String = ""
     
    Private Sub Application_NewMailEx(ByVal EntryIDCollection As String)
         'Exit Sub
        Dim varArray As Variant
        Dim strSub As String
        Dim strBody As String
        Dim strArray() As String
        Dim lngLoop As Long
        Dim objItem As Object
        Dim lngMailCounter As Long
        Dim objMItem As MailItem
        strArray = Split(EntryIDCollection, ",")
        For lngMailCounter = LBound(strArray) To UBound(strArray)
            Set objItem = Session.GetItemFromID(strArray(lngMailCounter))
            If TypeName(objItem) = "MailItem" And InStr(1, objItem.Subject, strSubjectLineStartWith) And InStr(1, objItem.Body, "") Then
                Set objMItem = objItem
                With CreateObject("Excel.Application").workbooks.Open(strFilePath)
                    With .sheets(1)
                        With .cells(.rows.Count, 1).End(-4162)(2).resize(1, 5)
                            .Value = Array(objMItem.SenderEmailAddress, objMItem.Subject, objMItem.ReceivedTime, objMItem.Categories)
                        End With
                    End With
                    .Close 1
                End With
                Set objItem = Nothing
            End If
        Next lngMailCounter
        If Not IsEmpty(strArray) Then
            Erase strArray
        End If
         
    End Sub
    A dream is not something you see when you are asleep, but something you strive for when you are awake.

    It's usually a bad idea to say that something can't be done.

    The difference between dream and aim, is that one requires soundless sleep to see and the other requires sleepless efforts to achieve

    Join us at Facebook

  5. #5
    Senior Member
    Join Date
    Jun 2012
    Posts
    337
    Rep Power
    13
    My preference:

    Code:
    Sub email_ontvangen_lezen()
      With CreateObject("Outlook.Application").GetNamespace("MAPI").GetDefaultFolder(6)
        redim sn(.items.count,2)
     
       j=0
        for each it in .Items
          sn(j,0)=it.To 
          sn(j,1)=it.subject
          sn(j,2)=it.body
          j=j+1
        next
      End With
    
      thisworkbook.sheets(1).cells(1).resize(ubound(sn)+1,ubound(sn,2)+1)=sn
    End Sub
    Source:
    http://www.snb-vba.eu/VBA_Outlook_external_en.html#L153
    Last edited by snb; 05-25-2013 at 04:05 PM.

  6. #6
    Moderator
    Join Date
    Jul 2012
    Posts
    156
    Rep Power
    13
    To make it completely like OP has asked.
    Code:
    Sub Read_Mail()
      With CreateObject("Outlook.Application").GetNamespace("MAPI").GetDefaultFolder(6)
        ReDim sn(.Items.Count, 3)
        j = 0
        For Each It In .Items
          sn(j, 0) = It.SenderEmailAddress
          sn(j, 1) = It.Subject
          sn(j, 2) = WorksheetFunction.Text(It.ReceivedTime, "mm/dd/yy h:mm:ss AM/PM")
          sn(j, 3) = It.Categories
          j = j + 1
        Next
      End With
    
      With Sheets(1).Cells(1)
            .Resize(, 4) = Array("FROM", "SUBJECT", "DATE RECEIVED", "CATEGORIES")
            .Offset(1).Resize(UBound(sn) + 1, UBound(sn, 2) + 1) = sn
      End With
    End Sub

  7. #7
    Senior Member
    Join Date
    Jun 2012
    Posts
    337
    Rep Power
    13
    @bakerman

    Since we are working in VBA I'd prefer:

    Code:
          sn(j, 2) = format(It.ReceivedTime, "dd-mm-yyyy")

Similar Threads

  1. Replies: 26
    Last Post: 10-22-2019, 02:39 PM
  2. VBA To Extract Email Address From Text
    By dunndealpr in forum Excel Help
    Replies: 43
    Last Post: 06-05-2019, 03:56 PM
  3. Replies: 2
    Last Post: 05-23-2013, 08:08 AM
  4. Replies: 1
    Last Post: 05-22-2013, 01:50 PM
  5. How To Send Outlook Email Using VBA
    By mfaisalrazzak in forum Excel Help
    Replies: 7
    Last Post: 03-03-2013, 03:09 AM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •