module Data.Time.RRule.Types
( defaultRRule
, RRule(..)
, Day(..)
, Frequency(..)
, ToRRule(toRRule)
)
where
import Prelude hiding (until)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Text (Text, intercalate, pack, unpack)
import Data.Time.Format (formatTime, defaultTimeLocale)
import Data.Time.Clock (UTCTime)
class Show a => ToRRule a where
toRRule :: a -> Text
toRRule = pack . show
instance ToRRule Int
instance ToRRule a => ToRRule (NonEmpty a) where
toRRule (x :| xs) = intercalate "," $ toRRule x : map toRRule xs
instance (Show a, Integral a, ToRRule b) => ToRRule (a, b) where
toRRule (a, b) = (if a == 0 then "" else pack $ show a) <> toRRule b
instance ToRRule UTCTime where
toRRule = pack . formatTime defaultTimeLocale "%Y%m%dT%H%M%SZ"
instance ToRRule a => ToRRule (Maybe a) where
toRRule Nothing = ""
toRRule (Just a) = toRRule a
data Frequency
= Secondly
| Minutely
| Hourly
| Daily
| Weekly
| Monthly
| Yearly
deriving (Eq, Show)
instance ToRRule Frequency where
toRRule = \case
Secondly -> "SECONDLY"
Minutely -> "MINUTELY"
Hourly -> "HOURLY"
Daily -> "DAILY"
Weekly -> "WEEKLY"
Monthly -> "MONTHLY"
Yearly -> "YEARLY"
data Day = Sunday | Monday | Tuesday | Wednesday | Thursday | Friday | Saturday
deriving (Eq, Show)
instance ToRRule Day where
toRRule = \case
Sunday -> "SU"
Monday -> "MO"
Tuesday -> "TU"
Wednesday -> "WE"
Thursday -> "TH"
Friday -> "FR"
Saturday -> "SA"
data RRule = RRule
{ prefix :: Bool
, weekStart :: Maybe Day
, frequency :: Maybe Frequency
, count :: Maybe Int
, until :: Maybe UTCTime
, interval :: Maybe Int
, bySecond :: Maybe (NonEmpty Int)
, byMinute :: Maybe (NonEmpty Int)
, byHour :: Maybe (NonEmpty Int)
, byDay :: Maybe (NonEmpty (Int, Day))
, byWeekNo :: Maybe (NonEmpty Int)
, byMonth :: Maybe (NonEmpty Int)
, byMonthDay :: Maybe (NonEmpty Int)
, byYearDay :: Maybe (NonEmpty Int)
, bySetPos :: Maybe (NonEmpty Int)
}
deriving (Eq, Show)
defaultRRule :: RRule
defaultRRule = RRule
{ prefix = False
, weekStart = Nothing
, frequency = Nothing
, count = Nothing
, until = Nothing
, interval = Nothing
, bySecond = Nothing
, byMinute = Nothing
, byHour = Nothing
, byDay = Nothing
, byWeekNo = Nothing
, byMonth = Nothing
, byMonthDay = Nothing
, byYearDay = Nothing
, bySetPos = Nothing
}