Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Measure response time between receipt of Outlook email and the reply by date 5

Status
Not open for further replies.

Skyshadow5

Technical User
Mar 27, 2002
53
0
0
GB
Desperately looking for a VBA solution to a tedious manual task.

I have a requirement to count the number of emails received in a shared mailbox folder, note the date and time it was received, and then note the date and time of the reply so I can get a measure of the time taken to reply to an email. This needs to be done in 7 differently named folders of a shared mailbox.
Ideally I'd like to export the data into an Excel s/sheet with column headers:

These three fields from the senders email:
From
Subject
Date / time (sent/received)

These four fields from the reply:
From [always the same set email address]
To
Subject
Replied (date / time)

In the eighth column will be a calculation to evaluate the time between receipt of email and response to email allowing me to find out quickest, slowest and average response times.

Big ask I know, hopefully someone already does something like this and has a ready made solution, thanks.

Clive
 
From what I can tell, there is no easy way to do this. One thing is that some of these properties are not exposed by the Outlook object model, so you need to use the extended MAPI properties. I think the general approach is one of the following:

1. Read PR_CONVERSATION_INDEX property and find an e-mail in the Sent Items
folder with the same value of PR_CONVERSATION_INDEX plus 5 bytes (see MSDN
for how PR_CONVERSATION_INDEX is created)
2. Read PR_MESSAGE_DELIVERY_TIME and PR_LAST_VERB_EXECUTION_TIME
(0x10820040). PR_LAST_VERB_EXECUTION_TIME is what Outlook uses when it
displays "You replied on..." or "You forwarded this message on ...".



However, you may want to look at an add-in that does this. This one is 29.95
Probably worth it assuming it will take you several hours to research and code, plus once you figure this out your boss will want more metrics.
 
Thanks for the reply MajP, I guessed this was going to be a tough nut to crack based on the lack of responses.
 
If I get a chance I will look at coding a solution. I do a lot of VBA, but do not work with Outlook much. I will see if I can do it with my personal email, then would have to modify it for a shared folder. I would probably do an Access/VBA solution because you can link and import data pretty easily into Access.
 
OPkey dokey. Should be possible, then, without those extended properties. Not at a VB/VBA machine currenlty, so no chance right now to knock together a proof of concept. Mya get a chance tomorrow.
 
Here is some code that gets me pretty close. It runs through a folder and for each replied to message, then it logs the information. Once logged into an access table it is trivial to get the metrics. In Outlook when you reply to a message there is data associated to the original message, and you will see a little purple arrow icon. So you run this not on the Sent folder, but the original folder from where you hit reply.

The other approach would be very complicated. If you went to the Sent folder there is no way AFAIK to tell that the sent message is a reply. So you would then have to get the Conversation ID and check in the recieved folder for a matching conversation.

So this worked for me sort of. I created a test folder and moved a bunch of replied messages (ones with a purple arrow icon) into the folder. Also added some non replied messages. It read them all. When I tried on my in box it stopped and only looped a couple of messages without throwing an error. I think it has to do with returning a non email message such as a task or appointment.

Code:
Public Sub TestItems()
   Const Last_Verb_Reply_All = 103
   Const Last_Verb_Reply_Sender = 102
   Const Last_Verb_Reply_Forward = 104
   Dim olApp As Outlook.Application
   Dim olSession As Outlook.NameSpace
   Dim olStartFolder As Outlook.MAPIFolder
   Dim mailitems As Outlook.Items
   Dim mailItem As Object
   Dim propertyAccessor As Outlook.propertyAccessor
   Dim LastVerbExecuted As Long
   Dim strRepliedTime As String
   
   Dim Subject As String
   Dim OriginalAuthor As String
   Dim Replier As String
   Dim RepliedTime As Date
   Dim RecievedTime As Date
   Dim strSql As String
   Set olApp = New Outlook.Application
   Set olSession = olApp.GetNamespace("MAPI")
   Set olStartFolder = olSession.PickFolder
   Set mailitems = olStartFolder.Items
   Dim count As Integer
   On Error Resume Next
   For Each mailItem In mailitems
     If mailItem.Class <> olMail Then Exit For
     Set propertyAccessor = mailItem.propertyAccessor
     LastVerbExecuted = CheckBlankFields("PR_LAST_VERB_EXECUTED", propertyAccessor.GetProperty("[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x10810003"))[/URL]
     Select Case LastVerbExecuted
       Case Last_Verb_Reply_All, Last_Verb_Reply_Sender, Last_Verb_Reply_Forward
          Subject = mailItem.Subject
          'This appears to be local time
          RecievedTime = mailItem.ReceivedTime
          'This appears to be GMT
          strRepliedTime = CheckBlankFields("PR_LAST_VERB_EXECUTION_TIME", propertyAccessor.GetProperty("[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x10820040"))[/URL]
          OriginalAuthor = mailItem.Sender
          'Replier = ...
          If strRepliedTime <> "" Then
            RepliedTime = CDate(strRepliedTime)
            RepliedTime = GetLocalTimeFromGMT(RepliedTime)
          End If
          LogData Subject, OriginalAuthor, Replier, RecievedTime, RepliedTime
       Case Else
         'in case you want to do something here
     End Select
   Next mailItem
End Sub
 
Private Function CheckBlankFields(FieldName As String, FieldValue As Variant) As String
  CheckBlankFields = ""
  If (FieldValue <> "") Then
    CheckBlankFields = FieldValue
  End If
End Function

Private Sub LogData(Subject As String, OriginalAuthor As String, Replier As String, RecievedTime As Date, RepliedTime As Date)
  'I saved it in Access but this could be any procedure to save the data
  Debug.Print Subject
  Debug.Print OriginalAuthor
  'Debug.Print Replier
  Debug.Print RecievedTime
  Debug.Print RepliedTime
  Debug.Print
  Dim strSql As String
  strSql = "Insert into TblOutput(OriginalAuthor, Subject, RecievedTime, RepliedTime)"
  strSql = strSql & " Values('" & OriginalAuthor & "', '" & Subject & "', #" & RecievedTime & "#, #" & RepliedTime & "#)"
  CurrentDb.Execute strSql
  Debug.Print strSql
End Sub

The time information comes back in local for Recieved Time and in GMT for replied time. So you have to convert. This Code taken from Pearson on the Web just for converting between GMT and Local. May be easier way.
Code:
Private Type SYSTEMTIME
        wYear As Integer
        wMonth As Integer
        wDayOfWeek As Integer
        wDay As Integer
        wHour As Integer
        wMinute As Integer
        wSecond As Integer
        wMilliseconds As Integer
End Type
    
    
    ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    ' NOTE: If you are using the Windows WinAPI Viewer Add-In to get
    ' function declarations, not that there is an error in the
    ' TIME_ZONE_INFORMATION structure. It defines StandardName and
    ' DaylightName As 32. This is fine if you have an Option Base
    ' directive to set the lower bound of arrays to 1. However, if
    ' your Option Base directive is set to 0 or you have no
    ' Option Base diretive, the code won't work. Instead,
    ' change the (32) to (0 To 31).
    ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    
    Private Type TIME_ZONE_INFORMATION
        Bias As Long
        StandardName(0 To 31) As Integer
        StandardDate As SYSTEMTIME
        StandardBias As Long
        DaylightName(0 To 31) As Integer
        DaylightDate As SYSTEMTIME
        DaylightBias As Long
    End Type
    
    
    ''''''''''''''''''''''''''''''''''''''''''''''
    ' These give symbolic names to the time zone
    ' values returned by GetTimeZoneInformation .
    ''''''''''''''''''''''''''''''''''''''''''''''
    
    Private Enum TIME_ZONE
        TIME_ZONE_ID_INVALID = 0        ' Cannot determine DST
        TIME_ZONE_STANDARD = 1          ' Standard Time, not Daylight
        TIME_ZONE_DAYLIGHT = 2          ' Daylight Time, not Standard
    End Enum
    

    Private Declare Function GetTimeZoneInformation Lib "kernel32" _
        (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long
    
    Private Declare Sub GetSystemTime Lib "kernel32" _
        (lpSystemTime As SYSTEMTIME)
 Public Function GetLocalTimeFromGMT(Optional GMTTime As Date) As Date
    '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    ' GetLocalTimeFromGMT
    ' This returns the Local Time from a GMT time. If GMTTime is present and
    ' greater than 0, it is assumed to be the GMT from which we will calculate
    ' Local Time. If GMTTime is 0 or omitted, it is assumed to be the GMT
    ' time.
    '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    Dim GMT As Date
    Dim TZI As TIME_ZONE_INFORMATION
    Dim DST As TIME_ZONE
    Dim LocalTime As Date
    
    If GMTTime <= 0 Then
        GMT = Now
    Else
        GMT = GMTTime
    End If
    DST = GetTimeZoneInformation(TZI)
    LocalTime = GMT - TimeSerial(0, TZI.Bias, 0) + IIf(DST = TIME_ZONE_DAYLIGHT, TimeSerial(1, 0, 0), 0)
    GetLocalTimeFromGMT = LocalTime
    
  End Function

 Function ConvertLocalToGMT(Optional LocalTime As Date) As Date
    '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    ' ConvertLocalToGMT
    ' This function returns the GMT based on LocalTime, if provided.
    ' If LocalTime is not equal to 0, the GMT corresponding to LocalTime
    ' is returned. If LocalTime is 0, the GMT corresponding to the local
    ' time is returned. Since GMT isn't affected by DST, we need to
    ' subtract 1 hour if we are presently in GMT.
    '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
    Dim T As Date
    Dim TZI As TIME_ZONE_INFORMATION
    Dim DST As TIME_ZONE
    Dim GMT As Date
    
    If LocalTime <= 0 Then
        T = Now
    Else
        T = LocalTime
    End If
    DST = GetTimeZoneInformation(TZI)
    GMT = T + TimeSerial(0, TZI.Bias, 0) - IIf(DST = TIME_ZONE_DAYLIGHT, TimeSerial(1, 0, 0), 0)
    ConvertLocalToGMT = GMT
    
    End Function
The time issue is actually a little more involved, that I did not account for. For one of my test messages, I replied when I was traveling in another time zone. So when I normalized it to GMT, I needed to get that time zone not where I am currently. Something to think about.

The code needs a lot of bells and whistles and error checking.
 
>The code needs a lot of bells and whistles and error checking.

Also seems to need the recipients of the reply, if the specs in the OP are to be followed.

> So you would then have to get the Conversation ID and check in the received folder for a matching conversation.

No, don't think so. Think you can retrieve all the messages for a conversation, no matter the folder each one is in, with a single call (which also has the side effect that the retrieved times are all in local time, so we don't have to worry about the GMT conversion)

>propertyAccessor

Given that Skyshadow5 has confirmed that they are using Outlook 2010 I think we can avoid PropertyAccessor
 
Also seems to need the recipients of the reply
I am guessing that would be the ReplyRecipients collection? Would be easy if that is it. I will give that a try.
I will standby for the rest, because I still cannot figure out how to get the reply time from the conversation. Thanks.



 
>I am guessing that would be the ReplyRecipients collection?

Since you are only looking at the original message the ReplyRecipients collection only contains a list of possible recipients, not the actual recipients the reply may have been sent to. In addition the reply may have a different Subject to the original mail (not just limited to sticking the default RE: in front of it).

In other words, to meet the requirements set out in the OP we need to find the actual reply and query its properties (which would have the handy knock-on effect of eliminating the GMT conversion)
 
In other words, to meet the requirements set out in the OP we need to find the actual reply and query its properties (which would have the handy knock-on effect of eliminating the GMT conversion)
How do you determine if a sent message is a reply? Is there a property on the sent message? I can only find that on the message replied to. The replied to message has a last verb executed (102,103,104), but the sent does not. I could not find a property in the mailitem model.
 
Yep, that is indeed the main problem - and is proving somewhat more intransigent than I expected ...
 
Many thanks guys for your efforts resolving this, much appreciated.
 
So by just looking at the original "replied to" message in your received folder you can get
From
Subject
Sent date/time
recieved date/time
and the Reply Date/time
so you can get your metrics for the reply time.

But from the replied to message I do not think you can get:
Reply From (who replied)
Reply To (who was replied to)
-Although you can kind of do this because you can determine if the replier hit reply or reply all. And you can then get the original TO names. Except if you are like me I hit reply all then remove some people from the list.
Reply Subject (If they edited the subject line)

I am still convinced from what I have read if you need that information. You need to pull the conversation topic and conversation index from the original "replied to" message. Then search the sent items for a message with the same conversation topic and the conversation index (incremented by 5 bytes). Then once you find the corresponding sent message you can get all the additional information. This starts to get a little more complex.

I will see if I can test that.
 
This was intriguing enough for me to try a full proof of concept. You just need to copy and paste this code into an Excel VBA module, and add a reference to the Outlook library.

Code:
[blue]Option Explicit

Public ns As Outlook.Namespace

Private Const EXCHIVERB_REPLYTOSENDER = 102
Private Const EXCHIVERB_REPLYTOALL = 103
Private Const EXCHIVERB_FORWARD = 104

Private Const PR_LAST_VERB_EXECUTED = "[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x10810003"[/URL]
Private Const PR_LAST_VERB_EXECUTION_TIME = "[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x10820040"[/URL]
Private Const PR_SMTP_ADDRESS = "[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x39FE001E"[/URL]
Private Const PR_RECEIVED_BY_ENTRYID As String = "[URL unfurl="true"]http://schemas.microsoft.com/mapi/proptag/0x003F0102"[/URL]

' Locates best matching reply in related conversation to the given mail message passed in as oMailItem
Private Function GetReply(oMailItem As MailItem) As MailItem
    Dim conItem As Outlook.Conversation
    Dim ConTable As Outlook.Table
    Dim ConArray() As Variant
    Dim MsgItem As MailItem
    Dim lp As Long
    Dim LastVerb As Long
    Dim VerbTime As Date
    Dim Clockdrift As Long
    Dim OriginatorID As String
    
    Set conItem = oMailItem.GetConversation ' Let Outlook and Exchange do the hard lifting to get entire converstion for email being checked.
    OriginatorID = oMailItem.PropertyAccessor.BinaryToString(oMailItem.PropertyAccessor.GetProperty(PR_RECEIVED_BY_ENTRYID))
    
    If Not conItem Is Nothing Then ' we have a conversation in which we should be able to match the reply
        Set ConTable = conItem.GetTable
        ConArray = ConTable.GetArray(ConTable.GetRowCount)
        LastVerb = oMailItem.PropertyAccessor.GetProperty(PR_LAST_VERB_EXECUTED)
        Select Case LastVerb
            Case EXCHIVERB_REPLYTOSENDER, EXCHIVERB_REPLYTOALL ', EXCHIVERB_FORWARD ' not interested in forwarded messages
                VerbTime = oMailItem.PropertyAccessor.GetProperty(PR_LAST_VERB_EXECUTION_TIME)
                VerbTime = oMailItem.PropertyAccessor.UTCToLocalTime(VerbTime) ' convert to local time
                ' Debug.Print "Reply to " & oMailItem.Subject & " sent on (local time): " & VerbTime
                For lp = 0 To UBound(ConArray)
                    If ConArray(lp, 4) = "IPM.Note" Then ' it is a mailitem
                        Set MsgItem = ns.GetItemFromID(ConArray(lp, 0)) 'mail item to check against
                        If Not MsgItem.Sender Is Nothing Then
                            If OriginatorID = MsgItem.Sender.ID Then
                                Clockdrift = DateDiff("s", VerbTime, MsgItem.SentOn)
                                If Clockdrift >= 0 And Clockdrift < 300 Then ' Allow for a clock drift of up to 300 seconds. This may be overgenerous
                                    Set GetReply = MsgItem
                                    Exit For ' only interested in first matching reply
                                End If
                            End If
                        End If
                    End If
                Next
            Case Else
        End Select
    End If
    ' as we exit function GetMsg is either Nothing or the reply we are interested in
End Function

Public Sub ListIt()
    Dim myOlApp As New Outlook.Application
    Dim myItem As Object ' item may not necessarily be a mailitem
    Dim myReplyItem As Outlook.MailItem
    Dim myFolder As Folder
    Dim xlRow As Long
      
    Set ns = myOlApp.GetNamespace("MAPI") ' Initialise Outlook access
    Set myFolder = ns.PickFolder() ' for the sake of this example we just pick a folder.
    
    InitSheet ActiveSheet ' initialise the spreadsheet
    
    xlRow = 3
    For Each myItem In myFolder.Items
        If myItem.Class = olMail Then
            Set myReplyItem = GetReply(myItem) ' this example only deals with mailitems
            If Not myReplyItem Is Nothing Then ' we found a reply
                PopulateSheet ActiveSheet, myItem, myReplyItem, xlRow
                xlRow = xlRow + 1
            End If
        End If
        DoEvents ' cheap and nasty way to allow other things to happen
    Next
  
    MsgBox "Done"
    
End Sub

Private Sub InitSheet(mySheet As Worksheet)
    With mySheet
        .Cells.Clear
        .Cells(1, 1).FormulaR1C1 = "Received"
        .Cells(2, 1).FormulaR1C1 = "From"
        .Cells(2, 2).FormulaR1C1 = "Subject"
        .Cells(2, 3).FormulaR1C1 = "Date/Time"
        .Cells(1, 4).FormulaR1C1 = "Replied"
        .Cells(2, 4).FormulaR1C1 = "From"
        .Cells(2, 5).FormulaR1C1 = "To"
        .Cells(2, 6).FormulaR1C1 = "Subject"
        .Cells(2, 7).FormulaR1C1 = "Date/Time"
        .Cells(2, 8).FormulaR1C1 = "Response Time"
    End With
End Sub

Private Sub PopulateSheet(mySheet As Worksheet, myItem As MailItem, myReplyItem As MailItem, xlRow As Long)
    Dim recips() As String
    Dim myRecipient As Outlook.Recipient
    Dim lp As Long
    
    With mySheet
        .Cells(xlRow, 1).FormulaR1C1 = myItem.SenderEmailAddress
        .Cells(xlRow, 2).FormulaR1C1 = myItem.Subject
        .Cells(xlRow, 3).FormulaR1C1 = myItem.ReceivedTime
        '.Cells(xlRow, 4).FormulaR1C1 = myReplyItem.SenderEmailAddress
        .Cells(xlRow, 4).FormulaR1C1 = myReplyItem.Sender.PropertyAccessor.GetProperty(PR_SMTP_ADDRESS) ' I prefer to see the SMTP address
        For lp = 0 To myReplyItem.Recipients.Count - 1
            ReDim Preserve recips(lp) As String
            recips(lp) = myReplyItem.Recipients(lp + 1).Address
        Next
        .Cells(xlRow, 5).FormulaR1C1 = Join(recips, vbCrLf)
        .Cells(xlRow, 6).FormulaR1C1 = myReplyItem.Subject
        .Cells(xlRow, 7).FormulaR1C1 = myReplyItem.SentOn
        .Cells(xlRow, 8).FormulaR1C1 = "=RC[-1]-RC[-5]"
        .Cells(xlRow, 8).NumberFormat = "[h]:mm:ss"
    End With
End Sub
[/blue]

it can then be invoked by calling the Macro called ListIt
 
Can you explain a few things.
As you loop the conversation and get the associated messages you check two things.

If Not MsgItem.Sender Is Nothing Then
If OriginatorID = MsgItem.Sender.ID Then

When would the Sender be nothing that you need to check this?
If I send a reply, the sender ID for the reply is my id? Who is the OriginatorID for a message?
Could you also just check if the reciever ID is ""? From testing it seemed that only sent messages had a reciever = "".
Could you explain the clock drift logic.

Thanks.
 
Clockdrift: it would appear that the time recorded for when you replied to a message (as retrieved by PR_LAST_VERB_EXECUTION_TIME) differes from the timestamp on the actual reply itself. I'd guess that tis is due to the delay in actually storing the reply and is probably somewhat dependent on how busy the information store might be. So it isn't really a real clock drift, just allows for that possible time difference

>When would the Sender be nothing

Didn't have the time to investigate why this might be, just that a few mails in the 'conversations' I was parsing suffered from this. Normally I'd only expect it to not be set if the mail has not actually been sent yet.

>Could you also just check if the reciever ID is ""?

I could - but the point is that I'm actually not interested in Sender, or whether the message has been sent (the fact that it is in the conversation ensures that. What I am interested in is Sender.ID, but I can't just put a check in for that because - as I stated above - Sender is sometime Nothing, in which case we get an error. And, since VBA does not do short-circuit evaluation, I can't put the condition all on one line.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top