{-# LANGUAGE RecordWildCards, OverloadedStrings #-} {-# OPTIONS_GHC -F -pgmFhsx2hs #-} module Clckwrks.Page.Atom where import Control.Monad.Trans (liftIO) import Clckwrks.Monad (Clck, Content(..), query, withAbs) import Clckwrks.Page.Acid import Clckwrks.Page.Monad (PageM, markupToContent) import Clckwrks.Page.Types import Clckwrks.ProfileData.Acid import Clckwrks.Page.URL import qualified Data.ByteString.Lazy.UTF8 as UTF8 import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import Data.String (fromString) import qualified Data.Text as Text import Data.Text.Lazy (Text) import qualified Data.Text.Lazy.Encoding as TL import Data.Time import Data.Time.Clock.POSIX (posixSecondsToUTCTime) import Data.Time.Format (formatTime) import Data.UUID (toString) import Happstack.Server (Happstack, Response, ok, toResponseBS) import HSP.XMLGenerator import HSP.XML (XML, cdata, renderXML, fromStringLit) import System.Locale (defaultTimeLocale) import Web.Routes (showURL) atom :: FeedConfig -- ^ feed configuration -> [Page] -- ^ pages to publish in feed -> PageM XML atom FeedConfig{..} pages = do blogURL <- withAbs $ showURL Blog atomURL <- withAbs $ showURL AtomFeed unXMLGenT $ <% feedTitle %> <% feedAuthorName %> <% atomDate $ mostRecentUpdate pages %> <% "urn:uuid:" ++ toString feedUUID %> <% mapM entry pages %> mostRecentUpdate :: [Page] -- ^ pages to consider -> UTCTime -- ^ most recent updated time mostRecentUpdate [] = posixSecondsToUTCTime 0 mostRecentUpdate pages = maximum $ map pageUpdated pages entry :: Page -> PageM XML entry Page{..} = do viewPageSlug <- withAbs $ showURL (ViewPageSlug pageId (toSlug pageTitle pageSlug)) unXMLGenT $ <% pageTitle %> <% "urn:uuid:" ++ toString pageUUID %> <% author %> <% atomDate pageUpdated %> <% atomContent pageSrc %> where author :: XMLGenT PageM XML author = do mu <- query $ UsernameForId pageAuthor case mu of Nothing -> return $ cdata "" (Just n) | Text.null n -> return $ cdata "" | otherwise -> <% n %> atomDate :: UTCTime -> String atomDate time = formatTime defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ" time atomContent :: Markup -> PageM XML atomContent markup = do c <- markupToContent markup case c of (PlainText txt) -> unXMLGenT $ <% txt %> (TrustedHtml html) -> unXMLGenT $ <% html %> handleAtomFeed :: PageM Response handleAtomFeed = do ps <- query AllPosts feedConfig <- query GetFeedConfig xml <- atom feedConfig ps ok $ toResponseBS (fromString "application/atom+xml;charset=utf-8") ((UTF8.fromString $ "\n") <> (TL.encodeUtf8 $ renderXML xml))