User Tools

Site Tools


vba:outlookappointments

[VBA] Outlookkalendereinträge nach Datum gefiltert auslesen

Ein Beispiel um Kalendereinträge für einen Datumsbereich aus Outlook ausgelesen werden kann

dpOutlookAppointments.bas
'/**
' * Schreibt Termine eines Zeitabschnittes in das Direktfenster
' * @example    dpOutlookAppointments #4/1/2016 12:00#,  #4/5/2016#
' * @param  Date    StartDatum
' * @param  Date    EndDatum
' */
Public Sub dpOutlookAppointments(ByVal iFromDate As Date, ByVal iToDate As Date)
    Dim otl As New Outlook.application
    Dim app As Outlook.AppointmentItem
    Dim filter As String
 
    'Datum/Zeit Format für den Filter
    'Das Datum muss im PC/Länder speziefischen Format sein. Darum ddddd, Mit mm/dd/yyyy gehts auf deutschsprahegen PC nicht :(
    Const C_FILTER_DATE_FORMAT = "ddddd hh:nn am/pm"
 
    'Filter erstellen
    'Filter-Argumente: https://msdn.microsoft.com/en-us/library/office/ff869597.aspx
    filter = "[Start] >= '" & format(iFromDate, C_FILTER_DATE_FORMAT) & "' AND [Start] <= '" & format(iToDate, C_FILTER_DATE_FORMAT) & "'"
 
    'Appointments auslesen
    With otl.GetNamespace("MAPI").GetDefaultFolder(olFolderCalendar).itemS
 
        'Sicherstellen, dass bei Serien die einzelnen Einträge übernommen werden
        'https://msdn.microsoft.com/de-de/library/office/ff866969.aspx
        .Sort "Start"
        .IncludeRecurrences = True
 
        'Die Appointments filtern und ausgeben
        For Each app In .Restrict(filter)
            Debug.Print app.start, app.Subject
        Next app
    End With
 
    Set app = Nothing
    Set otl = Nothing
End Sub
vba/outlookappointments.txt · Last modified: 01.04.2016 10:31:57 by yaslaw