module Hakyll.Web.Feed
( FeedConfiguration (..)
, renderRss
, renderAtom
) where
import Control.Monad ((<=<))
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Item
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
import Paths_hakyll
data FeedConfiguration = FeedConfiguration
{
feedTitle :: String
,
feedDescription :: String
,
feedAuthorName :: String
,
feedAuthorEmail :: String
,
feedRoot :: String
} deriving (Show, Eq)
renderFeed :: FilePath
-> FilePath
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderFeed feedPath itemPath config itemContext items = do
feedTpl <- compilerUnsafeIO $ loadTemplate feedPath
itemTpl <- compilerUnsafeIO $ loadTemplate itemPath
body <- makeItem =<< applyTemplateList itemTpl itemContext' items
applyTemplate feedTpl feedContext body
where
loadTemplate = fmap readTemplate . readFile <=< getDataFileName
itemContext' = mconcat
[ itemContext
, constField "root" (feedRoot config)
, constField "authorName" (feedAuthorName config)
, constField "authorEmail" (feedAuthorEmail config)
]
feedContext = mconcat
[ bodyField "body"
, constField "title" (feedTitle config)
, constField "description" (feedDescription config)
, constField "authorName" (feedAuthorName config)
, constField "authorEmail" (feedAuthorEmail config)
, constField "root" (feedRoot config)
, urlField "url"
, updatedField
, missingField
]
updatedField = field "updated" $ \_ -> case items of
[] -> return "Unknown"
(x : _) -> unContext itemContext' "updated" [] x >>= \cf -> case cf of
ListField _ _ -> fail "Hakyll.Web.Feed.renderFeed: Internal error"
StringField s -> return s
renderRss :: FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderRss config context = renderFeed
"templates/rss.xml" "templates/rss-item.xml" config
(makeItemContext "%a, %d %b %Y %H:%M:%S UT" context)
renderAtom :: FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderAtom config context = renderFeed
"templates/atom.xml" "templates/atom-item.xml" config
(makeItemContext "%Y-%m-%dT%H:%M:%SZ" context)
makeItemContext :: String -> Context a -> Context a
makeItemContext fmt context = mconcat
[dateField "published" fmt, context, dateField "updated" fmt]