{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Hakyll.Web.Feed
( FeedConfiguration (..)
, renderRss
, renderAtom
, renderRssWithTemplates
, renderAtomWithTemplates
) where
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Core.Util.String (replaceAll)
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
import Data.FileEmbed (makeRelativeToProject)
import System.FilePath ((</>))
rssTemplate :: Template
=
$(makeRelativeToProject ("data" </> "templates" </> "rss.xml")
>>= embedTemplate)
rssItemTemplate :: Template
=
$(makeRelativeToProject ("data" </> "templates" </> "rss-item.xml")
>>= embedTemplate)
atomTemplate :: Template
atomTemplate :: Template
atomTemplate =
$(makeRelativeToProject ("data" </> "templates" </> "atom.xml")
>>= embedTemplate)
atomItemTemplate :: Template
atomItemTemplate :: Template
atomItemTemplate =
$(makeRelativeToProject ("data" </> "templates" </> "atom-item.xml")
>>= embedTemplate)
data FeedConfiguration = FeedConfiguration
{
FeedConfiguration -> String
feedTitle :: String
,
FeedConfiguration -> String
feedDescription :: String
,
FeedConfiguration -> String
feedAuthorName :: String
,
FeedConfiguration -> String
feedAuthorEmail :: String
,
FeedConfiguration -> String
feedRoot :: String
} deriving (Int -> FeedConfiguration -> ShowS
[FeedConfiguration] -> ShowS
FeedConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FeedConfiguration] -> ShowS
$cshowList :: [FeedConfiguration] -> ShowS
show :: FeedConfiguration -> String
$cshow :: FeedConfiguration -> String
showsPrec :: Int -> FeedConfiguration -> ShowS
$cshowsPrec :: Int -> FeedConfiguration -> ShowS
Show, FeedConfiguration -> FeedConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeedConfiguration -> FeedConfiguration -> Bool
$c/= :: FeedConfiguration -> FeedConfiguration -> Bool
== :: FeedConfiguration -> FeedConfiguration -> Bool
$c== :: FeedConfiguration -> FeedConfiguration -> Bool
Eq)
renderFeed :: Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderFeed :: Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderFeed Template
feedTpl Template
itemTpl FeedConfiguration
config Context String
itemContext [Item String]
items = do
[Item String]
protectedItems <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) (f :: * -> *).
(Monad m, Functor f) =>
ShowS -> f String -> m (f String)
applyFilter ShowS
protectCDATA) [Item String]
items
Item String
body <- forall a. a -> Compiler (Item a)
makeItem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Template -> Context a -> [Item a] -> Compiler String
applyTemplateList Template
itemTpl Context String
itemContext' [Item String]
protectedItems
forall a. Template -> Context a -> Item a -> Compiler (Item String)
applyTemplate Template
feedTpl Context String
feedContext Item String
body
where
applyFilter :: (Monad m,Functor f) => (String -> String) -> f String -> m (f String)
applyFilter :: forall (m :: * -> *) (f :: * -> *).
(Monad m, Functor f) =>
ShowS -> f String -> m (f String)
applyFilter ShowS
tr f String
str = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShowS
tr f String
str
protectCDATA :: String -> String
protectCDATA :: ShowS
protectCDATA = String -> ShowS -> ShowS
replaceAll String
"]]>" (forall a b. a -> b -> a
const String
"]]>")
itemContext' :: Context String
itemContext' = forall a. Monoid a => [a] -> a
mconcat
[ Context String
itemContext
, forall a. String -> String -> Context a
constField String
"root" (FeedConfiguration -> String
feedRoot FeedConfiguration
config)
, forall a. String -> String -> Context a
constField String
"authorName" (FeedConfiguration -> String
feedAuthorName FeedConfiguration
config)
, forall {a}. Context a
emailField
]
feedContext :: Context String
feedContext = forall a. Monoid a => [a] -> a
mconcat
[ String -> Context String
bodyField String
"body"
, forall a. String -> String -> Context a
constField String
"title" (FeedConfiguration -> String
feedTitle FeedConfiguration
config)
, forall a. String -> String -> Context a
constField String
"description" (FeedConfiguration -> String
feedDescription FeedConfiguration
config)
, forall a. String -> String -> Context a
constField String
"authorName" (FeedConfiguration -> String
feedAuthorName FeedConfiguration
config)
, forall {a}. Context a
emailField
, forall a. String -> String -> Context a
constField String
"root" (FeedConfiguration -> String
feedRoot FeedConfiguration
config)
, forall a. String -> Context a
urlField String
"url"
, forall {a}. Context a
updatedField
, forall {a}. Context a
missingField
]
updatedField :: Context a
updatedField = forall a. String -> (Item a -> Compiler String) -> Context a
field String
"updated" forall a b. (a -> b) -> a -> b
$ \Item a
_ -> case [Item String]
items of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return String
"Unknown"
(Item String
x : [Item String]
_) -> forall a.
Context a -> String -> [String] -> Item a -> Compiler ContextField
unContext Context String
itemContext' String
"updated" [] Item String
x forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ContextField
cf -> case ContextField
cf of
StringField String
s -> forall (m :: * -> *) a. Monad m => a -> m a
return String
s
ContextField
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Hakyll.Web.Feed.renderFeed: Internal error"
emailField :: Context a
emailField = case FeedConfiguration -> String
feedAuthorEmail FeedConfiguration
config of
String
"" -> forall {a}. Context a
missingField
String
email -> forall a. String -> String -> Context a
constField String
"authorEmail" String
email
renderRssWithTemplates ::
Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
Template
feedTemplate Template
itemTemplate FeedConfiguration
config Context String
context = Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderFeed
Template
feedTemplate Template
itemTemplate FeedConfiguration
config
(forall a. String -> Context a -> Context a
makeItemContext String
"%a, %d %b %Y %H:%M:%S UT" Context String
context)
renderAtomWithTemplates ::
Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderAtomWithTemplates :: Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderAtomWithTemplates Template
feedTemplate Template
itemTemplate FeedConfiguration
config Context String
context = Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderFeed
Template
feedTemplate Template
itemTemplate FeedConfiguration
config
(forall a. String -> Context a -> Context a
makeItemContext String
"%Y-%m-%dT%H:%M:%SZ" Context String
context)
renderRss :: FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
= Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderRssWithTemplates Template
rssTemplate Template
rssItemTemplate
renderAtom :: FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderAtom :: FeedConfiguration
-> Context String -> [Item String] -> Compiler (Item String)
renderAtom = Template
-> Template
-> FeedConfiguration
-> Context String
-> [Item String]
-> Compiler (Item String)
renderAtomWithTemplates Template
atomTemplate Template
atomItemTemplate
makeItemContext :: String -> Context a -> Context a
makeItemContext :: forall a. String -> Context a -> Context a
makeItemContext String
fmt Context a
context = forall a. Monoid a => [a] -> a
mconcat
[Context a
context, forall a. String -> String -> Context a
dateField String
"published" String
fmt, forall a. String -> String -> Context a
dateField String
"updated" String
fmt]