RecurrencePattern.RecurrenceType property (Outlook)

Returns or sets an OlRecurrenceType constant specifying the frequency of occurrences for the recurrence pattern. Read/write.

Syntax

expression. RecurrenceType

expression A variable that represents a RecurrencePattern object.

Remarks

You must set the RecurrenceType property before you set other properties for a RecurrencePattern object. The RecurrencePattern properties that you can set subsequently depends on the value of RecurrenceType, as shown in the following table:

OlRecurrenceType Valid RecurrencePattern Properties
olRecursWeekly DayOfWeekMask, Duration, EndTime, Interval, NoEndDate, Occurrences, PatternStartDate, PatternEndDate, StartTime
olRecursMonthly DayOfMonth, Duration, EndTime, Interval, NoEndDate, Occurrences, PatternStartDate, PatternEndDate, StartTime
olRecursMonthNth DayOfWeekMask, Duration, EndTime, Interval, Instance, NoEndDate, Occurrences, PatternStartDate, PatternEndDate, StartTime
olRecursYearly DayOfMonth, Duration, EndTime, Interval, MonthOfYear, NoEndDate, Occurrences, PatternStartDate, PatternEndDate, StartTime
olRecursYearNth DayOfWeekMask, Duration, EndTime, Interval, Instance, NoEndDate, Occurrences, PatternStartDate, PatternEndDate, StartTime

Example

This Visual Basic for Applications example uses GetRecurrencePattern to obtain the RecurrencePattern object for the newly-created AppointmentItem. The properties, RecurrenceType, DayOfWeekMask, MonthOfYear, Instance, Occurrences, StartTime, EndTime, and Subject are set, the appointment is saved and then displayed with the pattern: "Occurs the first Monday of June effective 6/1/2007 until 6/6/2016 from 2:00 PM to 5:00 PM."

Sub RecurringYearNth() 
 
 Dim oAppt As AppointmentItem 
 
 Dim oPattern As RecurrencePattern 
 
 Set oAppt = Application.CreateItem(olAppointmentItem) 
 
 Set oPattern = oAppt.GetRecurrencePattern 
 
 With oPattern 
 
 .RecurrenceType = olRecursYearNth 
 
 .DayOfWeekMask = olMonday 
 
 .MonthOfYear = 6 
 
 .Instance = 1 
 
 .Occurrences = 10 
 
 .Duration = 180 
 
 .PatternStartDate = #6/1/2007# 
 
 .StartTime = #2:00:00 PM# 
 
 .EndTime = #5:00:00 PM# 
 
 End With 
 
 oAppt.Subject = "Recurring YearNth Appointment" 
 
 oAppt.Save 
 
 oAppt.Display 
 
End Sub

See also

RecurrencePattern Object

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.