Filtering Items Using a Date-time Comparison

Filtrando itens recorrentes na pasta de calendário

To filter a collection of appointment items that include recurring appointments, you must use the Items collection. Use the Items.IncludeRecurrences property to specify that Items.Find or Items.Restrict should include recurring appointments. The Table object returns only one row representing the recurrent appointment item, instead of a row for each occurrence of the appointment.

Formato de data/hora das sequências de caracteres de comparação

Outlook evaluates date-time values according to the time format, short date format, and long date format settings in the Regional and Language Options applet in the Windows Control Panel. In particular, Outlook evaluates time according to that specified time format without seconds. If you specify seconds in the date-time comparison string, the filter will not operate as expected.

Although dates and times are typically stored with a date format, filters using the Jet and DAV Searching and Locating (DASL) syntax require that the date-time value to be converted to a string representation. In Jet syntax, the date-time comparison string should be enclosed in either double quotes or single quotes. In DASL syntax, the date-time comparison string should be enclosed in single quotes.

To make sure that the date-time comparison string is formatted as Microsoft Outlook expects, use the Visual Basic for Applications Format function (or its equivalent in your programming language). The following example creates a Jet filter to find all contacts that have been modified before June 12, 2005 at 3:30 P.M local time.

criteria = "[LastModificationTime] < '" _ 
         & Format$("6/12/2005 3:30PM","General Date") & "'"

Fusos horários usados na comparação

Quando uma propriedade interna explícita é referenciada em uma consulta Jet com seu nome de cadeia de caracteres explícito, a comparação avalia o valor da propriedade e a cadeia de comparação de data e hora como valores de hora local.

When a property is referenced in a DASL query by namespace, the comparison evaluates the property value and the date-time comparison string as Coordinated Universal Time (UTC) values. For example, the following DASL query finds all contacts that have been modified before June 12, 2005 at 3:30 pm, UTC.

criteria = "@SQL=" & Chr(34) & "DAV:getlastmodified" & Chr(34) _ 
         & " < '" & Format$("6/12/2005 3:30PM","General Date") & "'"

Conversão em UTC nas consultas DASL

Since DASL queries always perform date-time comparisons in UTC, if you use a date literal in a comparison string, you must use its UTC value for the comparison. Use a função auxiliar Row.LocalTimeToUTC ou macros de data e hora do Outlook para facilitar a conversão.

LocalTimeToUTC

One way to facilitate local time to UTC conversion is to use the helper function, LocalTimeToUTC, of the Row object. The following line of code uses this helper function to convert the value of the LastModificationTime property (which is a default column in all Table objects):

Row.LocalTimeToUTC("LastModificationTime")

Macros de data/hora do Outlook

As macros de data listadas a seguir retornam sequências de caracteres de filtro que comparam o valor de uma determinada propriedade de data/hora com uma data especificada em UTC; SchemaName é qualquer propriedade válida de data/hora referida por namespace.

Nota As macros de data e hora do Outlook só podem ser usadas em consultas DASL.

Macro Sintaxe Descrição
hoje %today(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual a hoje
tomorrow %tomorrow(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual a amanhã
ontem %yesterday(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual a ontem
next7days %next7days(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual aos próximos sete dias
last7days %last7days(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual aos últimos sete dias
nextweek %nextweek(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual à próxima semana
thisweek %thisweek(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual a esta semana
lastweek %lastweek(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual à semana passada
nextmonth %nextmonth(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual ao próximo mês
thismonth %thismonth(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual a este mês
lastmonth %lastmonth(" SchemaName")% Restringe os itens cujo valor da propriedade SchemaName é igual ao mês passado

Exemplo mostrando conversão em UTC

The following code example illustrates three filter strings that return all messages received today, and applies one of the filters to Items.Restrict and Application.AdvancedSearch. It first uses PropertyAccessor.LocalTimeToUTC to convert today's date to UTC date strings. The first filter uses the Outlook macro, today, to obtain a filter string that compares the ReceivedTime property with today's date in UTC. The second and third macros reference the ReceivedTime property by two different namespaces.

The code example finally applies the third filter to items in the Inbox twice, first using Items.Restrict and then using Application.AdvancedSearch. It prints the number of items in the Inbox, and the number of items returned from each application of the filter.

Public blnSearchComp As Boolean 
 
Sub TestDASLDateComparison() 
    Dim strFilter As String 
    Dim colItems As Outlook.Items 
    Dim colRestrict As Outlook.Items 
    Dim oSearch As Outlook.Search 
    Dim oResults As Outlook.Results 
    Dim datStartUTC As Date 
    Dim datEndUTC As Date 
    Dim oMail As MailItem 
    Dim oPA As PropertyAccessor 
    Const SchemaPropTag As String = _ 
    "https://schemas.microsoft.com/mapi/proptag/" 
 
    'Get items from Inbox 
    Set colItems = _ 
    Application.Session.GetDefaultFolder(olFolderInbox).Items 
     
    'This code is a workaround to get today's date 
    'as UTC for DASL date comparison 
    Set oMail = Application.CreateItem(olMailItem) 
    Set oPA = oMail.PropertyAccessor 
    datStartUTC = oPA.LocalTimeToUTC(Date) 
    datEndUTC = oPA.LocalTimeToUTC(DateAdd("d", 1, Date)) 
     
    'All three filters shown below will return the same results 
    'This filter uses DASL date macro for today 
    strFilter = "%today(" _ 
    & AddQuotes("urn:schemas:httpmail:datereceived") & ")%" 
     
    'This filter uses urn:schemas:httpmail namespace 
    strFilter = AddQuotes("urn:schemas:httpmail:datereceived") _ 
    & " > '" & datStartUTC & "' AND " _ 
    & AddQuotes("urn:schemas:httpmail:datereceived") _ 
    & " < '" & datEndUTC & "'" 
 
    'This filter uses https://schemas.microsoft.com/mapi/proptag 
    strFilter = AddQuotes(SchemaPropTag & "0x0E060040") _ 
    & " > '" & datStartUTC & "' AND " _ 
    & AddQuotes(SchemaPropTag & "0x0E060040") _ 
    & " < '" & datEndUTC & "'" 
 
    'Count of items in Inbox 
    Debug.Print (colItems.Count) 
 
    'This call succeeds with @SQL prefix 
    Set colRestrict = colItems.Restrict("@SQL=" & strFilter) 
    'Get count of restricted items 
    Debug.Print (colRestrict.Count) 
 
    Set oSearch = Application.AdvancedSearch("Inbox", strFilter, False) 
    While blnSearchComp = False 
        DoEvents 
    Wend      
 
    'Get count from Search object 
    Set oResults = oSearch.Results 
    Debug.Print (oResults.Count) 
End Sub 
 
Public Function AddQuotes(ByVal SchemaName As String) As String 
    On Error Resume Next 
    AddQuotes = Chr(34) & SchemaName & Chr(34) 
End Function 
 
 
Private Sub Application_AdvancedSearchComplete(ByVal SearchObject As Search) 
    MsgBox "The AdvancedSearchComplete Event fired" 
    blnSearchComp = True 
End Sub

Suporte e comentários

Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.