{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NamedFieldPuns #-} module Bamboo.Theme.MiniHTML5.Widget.RSS where import Bamboo.Model.Post hiding (title) import Bamboo.Type.State import Bamboo.Theme.MiniHTML5.Env hiding (render_rss, link, config, title, title') import Text.RSS hiding (RSS) import qualified Bamboo.Model.Post as Post import qualified Text.RSS as RSS import Network.URI import MPS (empty) data RSS = RSS { title :: RSS.Title , link :: RSS.Link , description :: RSS.Description , channel_elems :: [RSS.ChannelElem] , items :: [RSS.Item] } to_rss :: RSS -> RSS.RSS to_rss x = RSS.RSS (x.title) (x.link) (x.description) (x.channel_elems) (x.items) rss :: State -> String -> String -> String rss s categary title' = RSS { title , link , description = title' , channel_elems = [ RSS.Language "en-us" ] , items } .to_rss.rssToXML.showXML where full_uri x = nullURI { uriScheme = "http://", uriPath = host_link x } host_link x = s.config.host_name ++ (s.env.slashed_script_name / x) link = full_uri (categary / title) items = s.posts.map item_rss_template title = if title'.empty then s.config.blog_title else s.config.blog_title ++ " / " ++ title' item_rss_template x = [ Title $ x.Post.title , Description $ x.render_rss , Author $ s.config.author_email , Link $ full_uri (x.uri) , PubDate $ x.date ] render_rss x | s.config.summary_for_rss.is True = x.markup_summary.show | otherwise = x.markup.show