module Text.Feed.Util
( toFeedDateString
, toFeedDateStringUTC
) where
import Prelude ()
import Prelude.Compat
import Data.Time (UTCTime, formatTime)
import qualified Data.Time.Locale.Compat
import qualified System.Locale
import System.Time (ClockTime, formatCalendarTime, toUTCTime)
import Text.Feed.Types
toFeedDateString :: FeedKind -> ClockTime -> String
toFeedDateString fk ct = formatCalendarTime System.Locale.defaultTimeLocale fmt ut
where
fmt = feedKindTimeFormat fk
ut = toUTCTime ct
toFeedDateStringUTC :: FeedKind -> UTCTime -> String
toFeedDateStringUTC fk = formatTime Data.Time.Locale.Compat.defaultTimeLocale fmt
where
fmt = feedKindTimeFormat fk
feedKindTimeFormat :: FeedKind -> String
feedKindTimeFormat fk =
case fk of
AtomKind {} -> atomRdfTimeFormat
RSSKind {} -> "%a, %d %b %Y %H:%M:%S GMT"
RDFKind {} -> atomRdfTimeFormat
where
atomRdfTimeFormat = "%Y-%m-%dT%H:%M:%SZ"