Safe Haskell | Safe |
---|---|
Language | Haskell98 |
ICalendar types, based on RFC5545.
Synopsis
- data OtherProperty = OtherProperty {}
- data RequestStatus = RequestStatus {}
- data Sequence = Sequence {}
- data LastModified = LastModified {}
- data DTStamp = DTStamp {}
- data Created = Created {}
- data Trigger
- data AlarmTriggerRelationship
- data Repeat = Repeat {}
- data RRule = RRule {}
- data Recur = Recur {
- recurFreq :: Frequency
- recurUntilCount :: Maybe (Either (Either Date DateTime) Int)
- recurInterval :: Int
- recurBySecond :: [Int]
- recurByMinute :: [Int]
- recurByHour :: [Int]
- recurByDay :: [Either (Int, Weekday) Weekday]
- recurByMonthDay :: [Int]
- recurByYearDay :: [Int]
- recurByWeekNo :: [Int]
- recurByMonth :: [Int]
- recurBySetPos :: [Int]
- recurWkSt :: Weekday
- data Weekday
- data Frequency
- data RDate
- = RDateDates { }
- | RDateDateTimes { }
- | RDatePeriods { }
- data ExDate
- = ExDates {
- exDates :: Set Date
- exDateOther :: OtherParams
- | ExDateTimes { }
- = ExDates {
- data UID = UID {
- uidValue :: Text
- uidOther :: OtherParams
- data URL = URL {
- urlValue :: URI
- urlOther :: OtherParams
- data RelationshipType
- data RelatedTo = RelatedTo {}
- data Range
- data RecurrenceId
- data Organizer = Organizer {}
- data Contact = Contact {}
- data PartStat
- data Role
- data CUType
- data Attendee = Attendee {
- attendeeValue :: CalAddress
- attendeeCUType :: CUType
- attendeeMember :: Set CalAddress
- attendeeRole :: Role
- attendeePartStat :: PartStat
- attendeeRSVP :: Bool
- attendeeDelTo :: Set CalAddress
- attendeeDelFrom :: Set CalAddress
- attendeeSentBy :: Maybe CalAddress
- attendeeCN :: Maybe Text
- attendeeDir :: Maybe URI
- attendeeLanguage :: Maybe Language
- attendeeOther :: OtherParams
- data TZUrl = TZUrl {}
- data UTCOffset = UTCOffset {}
- data TZName = TZName {}
- data TZID = TZID {
- tzidValue :: Text
- tzidGlobal :: Bool
- tzidOther :: OtherParams
- data TimeTransparency
- = Opaque { }
- | Transparent { }
- data FBType
- = Free
- | Busy
- | BusyUnavailable
- | BusyTentative
- | FBTypeX (CI Text)
- data UTCPeriod
- data Period
- data FreeBusy = FreeBusy {}
- data DurationProp = DurationProp {}
- data Sign
- data Duration
- data DTStart
- = DTStartDateTime { }
- | DTStartDate { }
- data Due
- = DueDateTime { }
- | DueDate { }
- data DTEnd
- = DTEndDateTime { }
- | DTEndDate { }
- data DateTime
- = FloatingDateTime { }
- | UTCDateTime { }
- | ZonedDateTime { }
- data Date = Date {}
- data Summary = Summary {}
- data JournalStatus
- = DraftJournal { }
- | FinalJournal { }
- | CancelledJournal { }
- data TodoStatus
- = TodoNeedsAction { }
- | CompletedTodo { }
- | InProcessTodo { }
- | CancelledTodo { }
- data EventStatus
- = TentativeEvent { }
- | ConfirmedEvent { }
- | CancelledEvent { }
- data Resources = Resources {}
- data Priority = Priority {}
- data PercentComplete = PercentComplete {}
- data Location = Location {}
- data Geo = Geo {}
- data Description = Description {}
- data Comment = Comment {}
- data Completed = Completed {}
- data ClassValue
- = Public
- | Private
- | Confidential
- | ClassValueX (CI Text)
- data Class = Class {}
- data Categories = Categories {}
- data Attachment
- = UriAttachment { }
- | BinaryAttachment { }
- data VOther = VOther {}
- data VAlarm
- = VAlarmAudio { }
- | VAlarmDisplay { }
- | VAlarmEmail { }
- | VAlarmX { }
- data TZProp = TZProp {}
- data VTimeZone = VTimeZone {}
- data VFreeBusy = VFreeBusy {
- vfbDTStamp :: DTStamp
- vfbUID :: UID
- vfbContact :: Maybe Contact
- vfbDTStart :: Maybe DTStart
- vfbDTEnd :: Maybe DTEnd
- vfbOrganizer :: Maybe Organizer
- vfbUrl :: Maybe URL
- vfbAttendee :: Set Attendee
- vfbComment :: Set Comment
- vfbFreeBusy :: Set FreeBusy
- vfbRStatus :: Set RequestStatus
- vfbOther :: Set OtherProperty
- data VJournal = VJournal {
- vjDTStamp :: DTStamp
- vjUID :: UID
- vjClass :: Class
- vjCreated :: Maybe Created
- vjDTStart :: Maybe DTStart
- vjLastMod :: Maybe LastModified
- vjOrganizer :: Maybe Organizer
- vjRecurId :: Maybe RecurrenceId
- vjSeq :: Sequence
- vjStatus :: Maybe JournalStatus
- vjSummary :: Maybe Summary
- vjUrl :: Maybe URL
- vjRRule :: Set RRule
- vjAttach :: Set Attachment
- vjAttendee :: Set Attendee
- vjCategories :: Set Categories
- vjComment :: Set Comment
- vjContact :: Set Contact
- vjDescription :: Set Description
- vjExDate :: Set ExDate
- vjRelated :: Set RelatedTo
- vjRDate :: Set RDate
- vjRStatus :: Set RequestStatus
- vjOther :: Set OtherProperty
- data VTodo = VTodo {
- vtDTStamp :: DTStamp
- vtUID :: UID
- vtClass :: Class
- vtCompleted :: Maybe Completed
- vtCreated :: Maybe Created
- vtDescription :: Maybe Description
- vtDTStart :: Maybe DTStart
- vtGeo :: Maybe Geo
- vtLastMod :: Maybe LastModified
- vtLocation :: Maybe Location
- vtOrganizer :: Maybe Organizer
- vtPercent :: Maybe PercentComplete
- vtPriority :: Priority
- vtRecurId :: Maybe RecurrenceId
- vtSeq :: Sequence
- vtStatus :: Maybe TodoStatus
- vtSummary :: Maybe Summary
- vtUrl :: Maybe URL
- vtRRule :: Set RRule
- vtDueDuration :: Maybe (Either Due DurationProp)
- vtAttach :: Set Attachment
- vtAttendee :: Set Attendee
- vtCategories :: Set Categories
- vtComment :: Set Comment
- vtContact :: Set Contact
- vtExDate :: Set ExDate
- vtRStatus :: Set RequestStatus
- vtRelated :: Set RelatedTo
- vtResources :: Set Resources
- vtRDate :: Set RDate
- vtAlarms :: Set VAlarm
- vtOther :: Set OtherProperty
- data VEvent = VEvent {
- veDTStamp :: DTStamp
- veUID :: UID
- veClass :: Class
- veDTStart :: Maybe DTStart
- veCreated :: Maybe Created
- veDescription :: Maybe Description
- veGeo :: Maybe Geo
- veLastMod :: Maybe LastModified
- veLocation :: Maybe Location
- veOrganizer :: Maybe Organizer
- vePriority :: Priority
- veSeq :: Sequence
- veStatus :: Maybe EventStatus
- veSummary :: Maybe Summary
- veTransp :: TimeTransparency
- veUrl :: Maybe URL
- veRecurId :: Maybe RecurrenceId
- veRRule :: Set RRule
- veDTEndDuration :: Maybe (Either DTEnd DurationProp)
- veAttach :: Set Attachment
- veAttendee :: Set Attendee
- veCategories :: Set Categories
- veComment :: Set Comment
- veContact :: Set Contact
- veExDate :: Set ExDate
- veRStatus :: Set RequestStatus
- veRelated :: Set RelatedTo
- veResources :: Set Resources
- veRDate :: Set RDate
- veAlarms :: Set VAlarm
- veOther :: Set OtherProperty
- data Method = Method {}
- data Scale = Scale {}
- data ICalVersion
- = MaxICalVersion { }
- | MinMaxICalVersion { }
- data ProdId = ProdId {}
- data VCalendar = VCalendar {
- vcProdId :: ProdId
- vcVersion :: ICalVersion
- vcScale :: Scale
- vcMethod :: Maybe Method
- vcOther :: Set OtherProperty
- vcTimeZones :: Map Text VTimeZone
- vcEvents :: Map (Text, Maybe (Either Date DateTime)) VEvent
- vcTodos :: Map (Text, Maybe (Either Date DateTime)) VTodo
- vcJournals :: Map (Text, Maybe (Either Date DateTime)) VJournal
- vcFreeBusys :: Map Text VFreeBusy
- vcOtherComps :: Set VOther
- data OtherParams = OtherParams (Set OtherParam)
- data OtherParam = OtherParam (CI Text) [Text]
- type CalAddress = URI
- newtype Language = Language (CI Text)
Documentation
data OtherProperty Source #
Any other property.
Instances
Eq OtherProperty Source # | |
Defined in Text.ICalendar.Types (==) :: OtherProperty -> OtherProperty -> Bool # (/=) :: OtherProperty -> OtherProperty -> Bool # | |
Ord OtherProperty Source # | |
Defined in Text.ICalendar.Types compare :: OtherProperty -> OtherProperty -> Ordering # (<) :: OtherProperty -> OtherProperty -> Bool # (<=) :: OtherProperty -> OtherProperty -> Bool # (>) :: OtherProperty -> OtherProperty -> Bool # (>=) :: OtherProperty -> OtherProperty -> Bool # max :: OtherProperty -> OtherProperty -> OtherProperty # min :: OtherProperty -> OtherProperty -> OtherProperty # | |
Show OtherProperty Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> OtherProperty -> ShowS # show :: OtherProperty -> String # showList :: [OtherProperty] -> ShowS # |
data RequestStatus Source #
Request Status. 3.8.8.3.
Instances
Eq RequestStatus Source # | |
Defined in Text.ICalendar.Types (==) :: RequestStatus -> RequestStatus -> Bool # (/=) :: RequestStatus -> RequestStatus -> Bool # | |
Ord RequestStatus Source # | |
Defined in Text.ICalendar.Types compare :: RequestStatus -> RequestStatus -> Ordering # (<) :: RequestStatus -> RequestStatus -> Bool # (<=) :: RequestStatus -> RequestStatus -> Bool # (>) :: RequestStatus -> RequestStatus -> Bool # (>=) :: RequestStatus -> RequestStatus -> Bool # max :: RequestStatus -> RequestStatus -> RequestStatus # min :: RequestStatus -> RequestStatus -> RequestStatus # | |
Show RequestStatus Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> RequestStatus -> ShowS # show :: RequestStatus -> String # showList :: [RequestStatus] -> ShowS # |
Sequence number. 3.8.7.4.
data LastModified Source #
Last Modified. 3.8.7.3.
Instances
Eq LastModified Source # | |
Defined in Text.ICalendar.Types (==) :: LastModified -> LastModified -> Bool # (/=) :: LastModified -> LastModified -> Bool # | |
Ord LastModified Source # | |
Defined in Text.ICalendar.Types compare :: LastModified -> LastModified -> Ordering # (<) :: LastModified -> LastModified -> Bool # (<=) :: LastModified -> LastModified -> Bool # (>) :: LastModified -> LastModified -> Bool # (>=) :: LastModified -> LastModified -> Bool # max :: LastModified -> LastModified -> LastModified # min :: LastModified -> LastModified -> LastModified # | |
Show LastModified Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> LastModified -> ShowS # show :: LastModified -> String # showList :: [LastModified] -> ShowS # |
Trigger. 3.8.6.3.
data AlarmTriggerRelationship Source #
Alarm Trigger Relationship. 3.2.14.
Instances
Repeat count. 3.8.6.2.
Recur value. 3.3.10.
Recur | |
|
Weekday, in recurrences. 3.3.10.
Instances
Bounded Weekday Source # | |
Enum Weekday Source # | |
Eq Weekday Source # | |
Ord Weekday Source # | |
Show Weekday Source # | |
Frequency in recurrences. 3.3.10.
Recurrence Date-Times. 3.8.5.2.
Exception Date-Times. 3.8.5.1.
Unique Identifier. 3.8.4.7.
UID | |
|
Uniform Resource Locator. 3.8.4.6.
URL | |
|
data RelationshipType Source #
Relationship Type. 3.2.15.
Unrecognized RelationshipTypeX values MUST be treated as Parent.
Instances
Eq RelationshipType Source # | |
Defined in Text.ICalendar.Types (==) :: RelationshipType -> RelationshipType -> Bool # (/=) :: RelationshipType -> RelationshipType -> Bool # | |
Ord RelationshipType Source # | |
Defined in Text.ICalendar.Types compare :: RelationshipType -> RelationshipType -> Ordering # (<) :: RelationshipType -> RelationshipType -> Bool # (<=) :: RelationshipType -> RelationshipType -> Bool # (>) :: RelationshipType -> RelationshipType -> Bool # (>=) :: RelationshipType -> RelationshipType -> Bool # max :: RelationshipType -> RelationshipType -> RelationshipType # min :: RelationshipType -> RelationshipType -> RelationshipType # | |
Show RelationshipType Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> RelationshipType -> ShowS # show :: RelationshipType -> String # showList :: [RelationshipType] -> ShowS # | |
Default RelationshipType Source # | |
Defined in Text.ICalendar.Types def :: RelationshipType # |
Related To. 3.8.4.5.
Recurrence Identifier Range. 3.2.13
data RecurrenceId Source #
Recurrence ID. 3.8.4.4.
Instances
Eq RecurrenceId Source # | |
Defined in Text.ICalendar.Types (==) :: RecurrenceId -> RecurrenceId -> Bool # (/=) :: RecurrenceId -> RecurrenceId -> Bool # | |
Ord RecurrenceId Source # | |
Defined in Text.ICalendar.Types compare :: RecurrenceId -> RecurrenceId -> Ordering # (<) :: RecurrenceId -> RecurrenceId -> Bool # (<=) :: RecurrenceId -> RecurrenceId -> Bool # (>) :: RecurrenceId -> RecurrenceId -> Bool # (>=) :: RecurrenceId -> RecurrenceId -> Bool # max :: RecurrenceId -> RecurrenceId -> RecurrenceId # min :: RecurrenceId -> RecurrenceId -> RecurrenceId # | |
Show RecurrenceId Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> RecurrenceId -> ShowS # show :: RecurrenceId -> String # showList :: [RecurrenceId] -> ShowS # |
Organizer. 3.8.4.3.
TODO: CAL-ADDRESS-related properties.
Participation Status. 3.2.12.
PartStatNeedsAction | |
Accepted | |
Declined | |
Tentative | |
Delegated | |
PartStatCompleted | |
InProcess | |
PartStatX (CI Text) |
Role. 3.2.16.
Calendar User Type. 3.2.3.
Unrecognized CUTypeX MUST be treated as Unknown.
Attendee. 3.8.4.1.
Time Zone URL. 3.8.3.5.
TZUrl | |
|
UTC Offset. 3.3.14, 3.8.3.4, and 3.8.3.3. (unified-ish)
UTCOffset | |
|
Time Zone Identifier. 3.8.3.1.
TZID | |
|
data TimeTransparency Source #
Time Transparency. 3.8.2.7.
Instances
Eq TimeTransparency Source # | |
Defined in Text.ICalendar.Types (==) :: TimeTransparency -> TimeTransparency -> Bool # (/=) :: TimeTransparency -> TimeTransparency -> Bool # | |
Ord TimeTransparency Source # | |
Defined in Text.ICalendar.Types compare :: TimeTransparency -> TimeTransparency -> Ordering # (<) :: TimeTransparency -> TimeTransparency -> Bool # (<=) :: TimeTransparency -> TimeTransparency -> Bool # (>) :: TimeTransparency -> TimeTransparency -> Bool # (>=) :: TimeTransparency -> TimeTransparency -> Bool # max :: TimeTransparency -> TimeTransparency -> TimeTransparency # min :: TimeTransparency -> TimeTransparency -> TimeTransparency # | |
Show TimeTransparency Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> TimeTransparency -> ShowS # show :: TimeTransparency -> String # showList :: [TimeTransparency] -> ShowS # | |
Default TimeTransparency Source # | |
Defined in Text.ICalendar.Types def :: TimeTransparency # |
Free/Busy Time Type. 3.2.9.
Unrecognized FBTypeX MUST be treated as Busy.
Period of time which must be UTC, as in FreeBusy. 3.3.9.
data DurationProp Source #
Duration property. 3.8.2.5.
Instances
Eq DurationProp Source # | |
Defined in Text.ICalendar.Types (==) :: DurationProp -> DurationProp -> Bool # (/=) :: DurationProp -> DurationProp -> Bool # | |
Ord DurationProp Source # | |
Defined in Text.ICalendar.Types compare :: DurationProp -> DurationProp -> Ordering # (<) :: DurationProp -> DurationProp -> Bool # (<=) :: DurationProp -> DurationProp -> Bool # (>) :: DurationProp -> DurationProp -> Bool # (>=) :: DurationProp -> DurationProp -> Bool # max :: DurationProp -> DurationProp -> DurationProp # min :: DurationProp -> DurationProp -> DurationProp # | |
Show DurationProp Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> DurationProp -> ShowS # show :: DurationProp -> String # showList :: [DurationProp] -> ShowS # |
Sign.
Duration value. 3.3.6.
Date-Time Start. 3.8.2.4.
Date-Time Due. 3.8.2.3.
Date-Time End. 3.8.2.2.
Date-Time value. 3.3.5.
data JournalStatus Source #
Status, but only for Journals. 3.8.1.11.
Instances
Eq JournalStatus Source # | |
Defined in Text.ICalendar.Types (==) :: JournalStatus -> JournalStatus -> Bool # (/=) :: JournalStatus -> JournalStatus -> Bool # | |
Ord JournalStatus Source # | |
Defined in Text.ICalendar.Types compare :: JournalStatus -> JournalStatus -> Ordering # (<) :: JournalStatus -> JournalStatus -> Bool # (<=) :: JournalStatus -> JournalStatus -> Bool # (>) :: JournalStatus -> JournalStatus -> Bool # (>=) :: JournalStatus -> JournalStatus -> Bool # max :: JournalStatus -> JournalStatus -> JournalStatus # min :: JournalStatus -> JournalStatus -> JournalStatus # | |
Show JournalStatus Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> JournalStatus -> ShowS # show :: JournalStatus -> String # showList :: [JournalStatus] -> ShowS # |
data TodoStatus Source #
Status, but only for TODOs. 3.8.1.11.
Instances
Eq TodoStatus Source # | |
Defined in Text.ICalendar.Types (==) :: TodoStatus -> TodoStatus -> Bool # (/=) :: TodoStatus -> TodoStatus -> Bool # | |
Ord TodoStatus Source # | |
Defined in Text.ICalendar.Types compare :: TodoStatus -> TodoStatus -> Ordering # (<) :: TodoStatus -> TodoStatus -> Bool # (<=) :: TodoStatus -> TodoStatus -> Bool # (>) :: TodoStatus -> TodoStatus -> Bool # (>=) :: TodoStatus -> TodoStatus -> Bool # max :: TodoStatus -> TodoStatus -> TodoStatus # min :: TodoStatus -> TodoStatus -> TodoStatus # | |
Show TodoStatus Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> TodoStatus -> ShowS # show :: TodoStatus -> String # showList :: [TodoStatus] -> ShowS # |
data EventStatus Source #
Status, but only for Events. 3.8.1.11.
Instances
Eq EventStatus Source # | |
Defined in Text.ICalendar.Types (==) :: EventStatus -> EventStatus -> Bool # (/=) :: EventStatus -> EventStatus -> Bool # | |
Ord EventStatus Source # | |
Defined in Text.ICalendar.Types compare :: EventStatus -> EventStatus -> Ordering # (<) :: EventStatus -> EventStatus -> Bool # (<=) :: EventStatus -> EventStatus -> Bool # (>) :: EventStatus -> EventStatus -> Bool # (>=) :: EventStatus -> EventStatus -> Bool # max :: EventStatus -> EventStatus -> EventStatus # min :: EventStatus -> EventStatus -> EventStatus # | |
Show EventStatus Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> EventStatus -> ShowS # show :: EventStatus -> String # showList :: [EventStatus] -> ShowS # |
Resources. 3.8.1.10.
Priority. 3.8.1.9.
data PercentComplete Source #
Percent complete. 3.8.1.8.
Instances
Eq PercentComplete Source # | |
Defined in Text.ICalendar.Types (==) :: PercentComplete -> PercentComplete -> Bool # (/=) :: PercentComplete -> PercentComplete -> Bool # | |
Ord PercentComplete Source # | |
Defined in Text.ICalendar.Types compare :: PercentComplete -> PercentComplete -> Ordering # (<) :: PercentComplete -> PercentComplete -> Bool # (<=) :: PercentComplete -> PercentComplete -> Bool # (>) :: PercentComplete -> PercentComplete -> Bool # (>=) :: PercentComplete -> PercentComplete -> Bool # max :: PercentComplete -> PercentComplete -> PercentComplete # min :: PercentComplete -> PercentComplete -> PercentComplete # | |
Show PercentComplete Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> PercentComplete -> ShowS # show :: PercentComplete -> String # showList :: [PercentComplete] -> ShowS # |
Location. 3.8.1.7.
data Description Source #
Description. 3.8.1.5.
Instances
Eq Description Source # | |
Defined in Text.ICalendar.Types (==) :: Description -> Description -> Bool # (/=) :: Description -> Description -> Bool # | |
Ord Description Source # | |
Defined in Text.ICalendar.Types compare :: Description -> Description -> Ordering # (<) :: Description -> Description -> Bool # (<=) :: Description -> Description -> Bool # (>) :: Description -> Description -> Bool # (>=) :: Description -> Description -> Bool # max :: Description -> Description -> Description # min :: Description -> Description -> Description # | |
Show Description Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> Description -> ShowS # show :: Description -> String # showList :: [Description] -> ShowS # |
Date-Time Completed. 3.8.2.1.
data ClassValue Source #
Classification value. 3.8.1.3. Unrecognized ClassValueX MUST be treated as Private.
Instances
Eq ClassValue Source # | |
Defined in Text.ICalendar.Types (==) :: ClassValue -> ClassValue -> Bool # (/=) :: ClassValue -> ClassValue -> Bool # | |
Ord ClassValue Source # | |
Defined in Text.ICalendar.Types compare :: ClassValue -> ClassValue -> Ordering # (<) :: ClassValue -> ClassValue -> Bool # (<=) :: ClassValue -> ClassValue -> Bool # (>) :: ClassValue -> ClassValue -> Bool # (>=) :: ClassValue -> ClassValue -> Bool # max :: ClassValue -> ClassValue -> ClassValue # min :: ClassValue -> ClassValue -> ClassValue # | |
Show ClassValue Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> ClassValue -> ShowS # show :: ClassValue -> String # showList :: [ClassValue] -> ShowS # | |
Default ClassValue Source # | |
Defined in Text.ICalendar.Types def :: ClassValue # |
Classification. 3.8.1.3.
data Categories Source #
Categories. 3.8.1.2.
Instances
Eq Categories Source # | |
Defined in Text.ICalendar.Types (==) :: Categories -> Categories -> Bool # (/=) :: Categories -> Categories -> Bool # | |
Ord Categories Source # | |
Defined in Text.ICalendar.Types compare :: Categories -> Categories -> Ordering # (<) :: Categories -> Categories -> Bool # (<=) :: Categories -> Categories -> Bool # (>) :: Categories -> Categories -> Bool # (>=) :: Categories -> Categories -> Bool # max :: Categories -> Categories -> Categories # min :: Categories -> Categories -> Categories # | |
Show Categories Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> Categories -> ShowS # show :: Categories -> String # showList :: [Categories] -> ShowS # |
data Attachment Source #
Attachment. 3.8.1.1.
UriAttachment | |
| |
BinaryAttachment | |
Instances
Eq Attachment Source # | |
Defined in Text.ICalendar.Types (==) :: Attachment -> Attachment -> Bool # (/=) :: Attachment -> Attachment -> Bool # | |
Ord Attachment Source # | |
Defined in Text.ICalendar.Types compare :: Attachment -> Attachment -> Ordering # (<) :: Attachment -> Attachment -> Bool # (<=) :: Attachment -> Attachment -> Bool # (>) :: Attachment -> Attachment -> Bool # (>=) :: Attachment -> Attachment -> Bool # max :: Attachment -> Attachment -> Attachment # min :: Attachment -> Attachment -> Attachment # | |
Show Attachment Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> Attachment -> ShowS # show :: Attachment -> String # showList :: [Attachment] -> ShowS # |
Any other component not recognized.
VAlarm component. 3.6.6.
VAlarmAudio | |
| |
VAlarmDisplay | |
| |
VAlarmEmail | |
| |
VAlarmX | |
|
Time zone property, also 3.6.5.
TZProp | |
|
Time Zone Component. 3.6.5.
VTimeZone | |
|
Free/Busy Component. 3.6.4
VFreeBusy | |
|
Journal Component. 3.6.3
VJournal | |
|
To-Do Component. 3.6.2
VTodo | |
|
Event Component. 3.6.1.
VEvent | |
|
Calendar Scale. 3.7.1.
Scale | |
|
data ICalVersion Source #
Version. 3.7.4.
Instances
Eq ICalVersion Source # | |
Defined in Text.ICalendar.Types (==) :: ICalVersion -> ICalVersion -> Bool # (/=) :: ICalVersion -> ICalVersion -> Bool # | |
Ord ICalVersion Source # | |
Defined in Text.ICalendar.Types compare :: ICalVersion -> ICalVersion -> Ordering # (<) :: ICalVersion -> ICalVersion -> Bool # (<=) :: ICalVersion -> ICalVersion -> Bool # (>) :: ICalVersion -> ICalVersion -> Bool # (>=) :: ICalVersion -> ICalVersion -> Bool # max :: ICalVersion -> ICalVersion -> ICalVersion # min :: ICalVersion -> ICalVersion -> ICalVersion # | |
Show ICalVersion Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> ICalVersion -> ShowS # show :: ICalVersion -> String # showList :: [ICalVersion] -> ShowS # |
VCalendar component. 3.4.
VCalendar | |
|
Instances
Eq VCalendar Source # | |
Ord VCalendar Source # | |
Defined in Text.ICalendar.Types | |
Show VCalendar Source # | |
Semigroup VCalendar Source # |
Picks the left in most cases. On UIDRecurrenceIdTZID clash, picks the If the Sequence, DTStamp or LastModified is the same, picks the left. |
Monoid VCalendar Source # | |
Default VCalendar Source # | |
Defined in Text.ICalendar.Types |
data OtherParams Source #
Other parameters, either x-param or other iana-param.
Instances
Eq OtherParams Source # | |
Defined in Text.ICalendar.Types (==) :: OtherParams -> OtherParams -> Bool # (/=) :: OtherParams -> OtherParams -> Bool # | |
Ord OtherParams Source # | |
Defined in Text.ICalendar.Types compare :: OtherParams -> OtherParams -> Ordering # (<) :: OtherParams -> OtherParams -> Bool # (<=) :: OtherParams -> OtherParams -> Bool # (>) :: OtherParams -> OtherParams -> Bool # (>=) :: OtherParams -> OtherParams -> Bool # max :: OtherParams -> OtherParams -> OtherParams # min :: OtherParams -> OtherParams -> OtherParams # | |
Show OtherParams Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> OtherParams -> ShowS # show :: OtherParams -> String # showList :: [OtherParams] -> ShowS # | |
Default OtherParams Source # | |
Defined in Text.ICalendar.Types def :: OtherParams # |
data OtherParam Source #
One other parameter, either x-param or iana-param.
OtherParam (CI Text) [Text] |
Instances
Eq OtherParam Source # | |
Defined in Text.ICalendar.Types (==) :: OtherParam -> OtherParam -> Bool # (/=) :: OtherParam -> OtherParam -> Bool # | |
Ord OtherParam Source # | |
Defined in Text.ICalendar.Types compare :: OtherParam -> OtherParam -> Ordering # (<) :: OtherParam -> OtherParam -> Bool # (<=) :: OtherParam -> OtherParam -> Bool # (>) :: OtherParam -> OtherParam -> Bool # (>=) :: OtherParam -> OtherParam -> Bool # max :: OtherParam -> OtherParam -> OtherParam # min :: OtherParam -> OtherParam -> OtherParam # | |
Show OtherParam Source # | |
Defined in Text.ICalendar.Types showsPrec :: Int -> OtherParam -> ShowS # show :: OtherParam -> String # showList :: [OtherParam] -> ShowS # |
type CalAddress = URI Source #