module Text.RSS (RSS(..), Item, ChannelElem(..), ItemElem(..),
Title,Link,Description,Width,Height,
Email,Domain,MIME_Type,InputName,
Weekday(..), Hour, Minutes,
CloudHost, CloudPort, CloudPath,
CloudProcedure, CloudProtocol(..),
rssToXML, showXML
) where
import Data.Ix (Ix)
import Network.URI (URI)
import Data.Time.Format (defaultTimeLocale,
rfc822DateFormat)
import Data.Time.Clock (UTCTime)
import Data.Time.Format (formatTime)
import Text.XML.HaXml.Combinators (CFilter, cdata, literal, mkElem,
mkElemAttr)
import Text.XML.HaXml.Escape (stdXmlEscaper, xmlEscape)
import Text.XML.HaXml.Types (Content (..), Element)
import Text.XML.HaXml.Verbatim (verbatim)
data = Title Link Description [ChannelElem] [Item]
deriving Int -> RSS -> ShowS
[RSS] -> ShowS
RSS -> String
(Int -> RSS -> ShowS)
-> (RSS -> String) -> ([RSS] -> ShowS) -> Show RSS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RSS -> ShowS
showsPrec :: Int -> RSS -> ShowS
$cshow :: RSS -> String
show :: RSS -> String
$cshowList :: [RSS] -> ShowS
showList :: [RSS] -> ShowS
Show
type Item = [ItemElem]
type Title = String
type Link = URI
type Description = String
type Width = Int
type Height = Int
type Email = String
type Domain = String
type MIME_Type = String
type InputName = String
type Hour = Int
type Minutes = Int
type CloudHost = String
type CloudPort = Int
type CloudPath = String
type CloudProcedure = String
data CloudProtocol = CloudProtocolXmlRpc | CloudProtocolSOAP
deriving Int -> CloudProtocol -> ShowS
[CloudProtocol] -> ShowS
CloudProtocol -> String
(Int -> CloudProtocol -> ShowS)
-> (CloudProtocol -> String)
-> ([CloudProtocol] -> ShowS)
-> Show CloudProtocol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CloudProtocol -> ShowS
showsPrec :: Int -> CloudProtocol -> ShowS
$cshow :: CloudProtocol -> String
show :: CloudProtocol -> String
$cshowList :: [CloudProtocol] -> ShowS
showList :: [CloudProtocol] -> ShowS
Show
data ChannelElem = Language String
| Copyright String
| ManagingEditor Email
| WebMaster Email
| ChannelPubDate UTCTime
| LastBuildDate UTCTime
| ChannelCategory (Maybe Domain) String
| Generator String
| Cloud CloudHost CloudPort CloudPath CloudProcedure CloudProtocol
| TTL Minutes
| Image URI Title Link (Maybe Width) (Maybe Height) (Maybe Description)
| Rating String
| TextInput Title Description InputName Link
| SkipHours [Hour]
| SkipDays [Weekday]
deriving Int -> ChannelElem -> ShowS
[ChannelElem] -> ShowS
ChannelElem -> String
(Int -> ChannelElem -> ShowS)
-> (ChannelElem -> String)
-> ([ChannelElem] -> ShowS)
-> Show ChannelElem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChannelElem -> ShowS
showsPrec :: Int -> ChannelElem -> ShowS
$cshow :: ChannelElem -> String
show :: ChannelElem -> String
$cshowList :: [ChannelElem] -> ShowS
showList :: [ChannelElem] -> ShowS
Show
data ItemElem = Title Title
| Link Link
| Description Description
| Author Email
| Category (Maybe Domain) String
| URI
| Enclosure URI Int MIME_Type
| Guid Bool String
| PubDate UTCTime
| Source URI Title
deriving (Int -> ItemElem -> ShowS
Item -> ShowS
ItemElem -> String
(Int -> ItemElem -> ShowS)
-> (ItemElem -> String) -> (Item -> ShowS) -> Show ItemElem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ItemElem -> ShowS
showsPrec :: Int -> ItemElem -> ShowS
$cshow :: ItemElem -> String
show :: ItemElem -> String
$cshowList :: Item -> ShowS
showList :: Item -> ShowS
Show)
data Weekday = Sunday | Monday | Tuesday | Wednesday
| Thursday | Friday | Saturday
deriving (Weekday -> Weekday -> Bool
(Weekday -> Weekday -> Bool)
-> (Weekday -> Weekday -> Bool) -> Eq Weekday
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Weekday -> Weekday -> Bool
== :: Weekday -> Weekday -> Bool
$c/= :: Weekday -> Weekday -> Bool
/= :: Weekday -> Weekday -> Bool
Eq, Eq Weekday
Eq Weekday =>
(Weekday -> Weekday -> Ordering)
-> (Weekday -> Weekday -> Bool)
-> (Weekday -> Weekday -> Bool)
-> (Weekday -> Weekday -> Bool)
-> (Weekday -> Weekday -> Bool)
-> (Weekday -> Weekday -> Weekday)
-> (Weekday -> Weekday -> Weekday)
-> Ord Weekday
Weekday -> Weekday -> Bool
Weekday -> Weekday -> Ordering
Weekday -> Weekday -> Weekday
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Weekday -> Weekday -> Ordering
compare :: Weekday -> Weekday -> Ordering
$c< :: Weekday -> Weekday -> Bool
< :: Weekday -> Weekday -> Bool
$c<= :: Weekday -> Weekday -> Bool
<= :: Weekday -> Weekday -> Bool
$c> :: Weekday -> Weekday -> Bool
> :: Weekday -> Weekday -> Bool
$c>= :: Weekday -> Weekday -> Bool
>= :: Weekday -> Weekday -> Bool
$cmax :: Weekday -> Weekday -> Weekday
max :: Weekday -> Weekday -> Weekday
$cmin :: Weekday -> Weekday -> Weekday
min :: Weekday -> Weekday -> Weekday
Ord, Int -> Weekday
Weekday -> Int
Weekday -> [Weekday]
Weekday -> Weekday
Weekday -> Weekday -> [Weekday]
Weekday -> Weekday -> Weekday -> [Weekday]
(Weekday -> Weekday)
-> (Weekday -> Weekday)
-> (Int -> Weekday)
-> (Weekday -> Int)
-> (Weekday -> [Weekday])
-> (Weekday -> Weekday -> [Weekday])
-> (Weekday -> Weekday -> [Weekday])
-> (Weekday -> Weekday -> Weekday -> [Weekday])
-> Enum Weekday
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Weekday -> Weekday
succ :: Weekday -> Weekday
$cpred :: Weekday -> Weekday
pred :: Weekday -> Weekday
$ctoEnum :: Int -> Weekday
toEnum :: Int -> Weekday
$cfromEnum :: Weekday -> Int
fromEnum :: Weekday -> Int
$cenumFrom :: Weekday -> [Weekday]
enumFrom :: Weekday -> [Weekday]
$cenumFromThen :: Weekday -> Weekday -> [Weekday]
enumFromThen :: Weekday -> Weekday -> [Weekday]
$cenumFromTo :: Weekday -> Weekday -> [Weekday]
enumFromTo :: Weekday -> Weekday -> [Weekday]
$cenumFromThenTo :: Weekday -> Weekday -> Weekday -> [Weekday]
enumFromThenTo :: Weekday -> Weekday -> Weekday -> [Weekday]
Enum, Weekday
Weekday -> Weekday -> Bounded Weekday
forall a. a -> a -> Bounded a
$cminBound :: Weekday
minBound :: Weekday
$cmaxBound :: Weekday
maxBound :: Weekday
Bounded, Ord Weekday
Ord Weekday =>
((Weekday, Weekday) -> [Weekday])
-> ((Weekday, Weekday) -> Weekday -> Int)
-> ((Weekday, Weekday) -> Weekday -> Int)
-> ((Weekday, Weekday) -> Weekday -> Bool)
-> ((Weekday, Weekday) -> Int)
-> ((Weekday, Weekday) -> Int)
-> Ix Weekday
(Weekday, Weekday) -> Int
(Weekday, Weekday) -> [Weekday]
(Weekday, Weekday) -> Weekday -> Bool
(Weekday, Weekday) -> Weekday -> Int
forall a.
Ord a =>
((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (Weekday, Weekday) -> [Weekday]
range :: (Weekday, Weekday) -> [Weekday]
$cindex :: (Weekday, Weekday) -> Weekday -> Int
index :: (Weekday, Weekday) -> Weekday -> Int
$cunsafeIndex :: (Weekday, Weekday) -> Weekday -> Int
unsafeIndex :: (Weekday, Weekday) -> Weekday -> Int
$cinRange :: (Weekday, Weekday) -> Weekday -> Bool
inRange :: (Weekday, Weekday) -> Weekday -> Bool
$crangeSize :: (Weekday, Weekday) -> Int
rangeSize :: (Weekday, Weekday) -> Int
$cunsafeRangeSize :: (Weekday, Weekday) -> Int
unsafeRangeSize :: (Weekday, Weekday) -> Int
Ix, ReadPrec [Weekday]
ReadPrec Weekday
Int -> ReadS Weekday
ReadS [Weekday]
(Int -> ReadS Weekday)
-> ReadS [Weekday]
-> ReadPrec Weekday
-> ReadPrec [Weekday]
-> Read Weekday
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Weekday
readsPrec :: Int -> ReadS Weekday
$creadList :: ReadS [Weekday]
readList :: ReadS [Weekday]
$creadPrec :: ReadPrec Weekday
readPrec :: ReadPrec Weekday
$creadListPrec :: ReadPrec [Weekday]
readListPrec :: ReadPrec [Weekday]
Read, Int -> Weekday -> ShowS
[Weekday] -> ShowS
Weekday -> String
(Int -> Weekday -> ShowS)
-> (Weekday -> String) -> ([Weekday] -> ShowS) -> Show Weekday
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Weekday -> ShowS
showsPrec :: Int -> Weekday -> ShowS
$cshow :: Weekday -> String
show :: Weekday -> String
$cshowList :: [Weekday] -> ShowS
showList :: [Weekday] -> ShowS
Show)
rssToXML :: RSS -> CFilter ()
(RSS String
title Link
link String
description [ChannelElem]
celems [Item]
items) =
String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"rss" [(String
"version",String -> CFilter ()
forall i. String -> CFilter i
literal String
"2.0")]
[String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"channel" ([String -> CFilter ()
mkTitle String
title,
Link -> CFilter ()
mkLink Link
link,
String -> CFilter ()
mkDescription String
description,
CFilter ()
mkDocs]
[CFilter ()] -> [CFilter ()] -> [CFilter ()]
forall a. [a] -> [a] -> [a]
++ (ChannelElem -> CFilter ()) -> [ChannelElem] -> [CFilter ()]
forall a b. (a -> b) -> [a] -> [b]
map ChannelElem -> CFilter ()
mkChannelElem [ChannelElem]
celems
[CFilter ()] -> [CFilter ()] -> [CFilter ()]
forall a. [a] -> [a] -> [a]
++ (Item -> CFilter ()) -> [Item] -> [CFilter ()]
forall a b. (a -> b) -> [a] -> [b]
map Item -> CFilter ()
mkItem [Item]
items)]
showXML :: CFilter () -> String
showXML :: CFilter () -> String
showXML = Element () -> String
forall a. Verbatim a => a -> String
verbatim (Element () -> String)
-> (CFilter () -> Element ()) -> CFilter () -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CFilter () -> Element ()
cfilterToElem
cfilterToElem :: CFilter () -> Element ()
cfilterToElem :: CFilter () -> Element ()
cfilterToElem CFilter ()
f = case CFilter ()
f (Bool -> String -> () -> Content ()
forall i. Bool -> String -> i -> Content i
CString Bool
False String
"" ()) of
[CElem Element ()
e ()
_] -> XmlEscaper -> Element () -> Element ()
forall i. XmlEscaper -> Element i -> Element i
xmlEscape XmlEscaper
stdXmlEscaper Element ()
e
[] -> String -> Element ()
forall a. HasCallStack => String -> a
error String
"RSS produced no output"
[Content ()]
_ -> String -> Element ()
forall a. HasCallStack => String -> a
error String
"RSS produced more than one output"
mkSimple :: String -> String -> CFilter ()
mkSimple :: String -> String -> CFilter ()
mkSimple String
t String
str = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
t [String -> CFilter ()
forall i. String -> CFilter i
literal String
str]
mkTitle :: Title -> CFilter ()
mkTitle :: String -> CFilter ()
mkTitle = String -> String -> CFilter ()
mkSimple String
"title"
mkLink :: Link -> CFilter ()
mkLink :: Link -> CFilter ()
mkLink = String -> String -> CFilter ()
mkSimple String
"link" (String -> CFilter ()) -> (Link -> String) -> Link -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> String
forall a. Show a => a -> String
show
mkDescription :: Description -> CFilter ()
mkDescription :: String -> CFilter ()
mkDescription String
str = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"description" [String -> CFilter ()
forall i. String -> CFilter i
cdata String
str]
mkDocs :: CFilter ()
mkDocs :: CFilter ()
mkDocs = String -> String -> CFilter ()
mkSimple String
"docs" String
"http://www.rssboard.org/rss-specification"
mkPubDate :: UTCTime -> CFilter ()
mkPubDate :: UTCTime -> CFilter ()
mkPubDate = String -> String -> CFilter ()
mkSimple String
"pubDate" (String -> CFilter ())
-> (UTCTime -> String) -> UTCTime -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> String
formatDate
formatDate :: UTCTime -> String
formatDate :: UTCTime -> String
formatDate = TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
rfc822DateFormat
mkCategory :: Maybe Domain -> String -> CFilter ()
mkCategory :: Maybe String -> String -> CFilter ()
mkCategory Maybe String
md String
s = String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"category" [(String, CFilter ())]
forall {i}. [(String, CFilter i)]
attrs [String -> CFilter ()
forall i. String -> CFilter i
literal String
s]
where attrs :: [(String, CFilter i)]
attrs = [(String, CFilter i)]
-> (String -> [(String, CFilter i)])
-> Maybe String
-> [(String, CFilter i)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\String
d -> [(String
"domain", String -> CFilter i
forall i. String -> CFilter i
literal String
d)]) Maybe String
md
maybeElem :: (a -> CFilter ()) -> Maybe a -> [CFilter ()]
maybeElem :: forall a. (a -> CFilter ()) -> Maybe a -> [CFilter ()]
maybeElem = [CFilter ()] -> (a -> [CFilter ()]) -> Maybe a -> [CFilter ()]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ((a -> [CFilter ()]) -> Maybe a -> [CFilter ()])
-> ((a -> CFilter ()) -> a -> [CFilter ()])
-> (a -> CFilter ())
-> Maybe a
-> [CFilter ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((CFilter () -> [CFilter ()] -> [CFilter ()]
forall a. a -> [a] -> [a]
:[]) (CFilter () -> [CFilter ()])
-> (a -> CFilter ()) -> a -> [CFilter ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)
mkChannelElem :: ChannelElem -> CFilter ()
mkChannelElem :: ChannelElem -> CFilter ()
mkChannelElem (Language String
str) = String -> String -> CFilter ()
mkSimple String
"language" String
str
mkChannelElem (Copyright String
str) = String -> String -> CFilter ()
mkSimple String
"copyright" String
str
mkChannelElem (ManagingEditor String
str) = String -> String -> CFilter ()
mkSimple String
"managingEditor" String
str
mkChannelElem (WebMaster String
str) = String -> String -> CFilter ()
mkSimple String
"webMaster" String
str
mkChannelElem (ChannelPubDate UTCTime
date) = UTCTime -> CFilter ()
mkPubDate UTCTime
date
mkChannelElem (LastBuildDate UTCTime
date) = String -> String -> CFilter ()
mkSimple String
"lastBuildDate" (String -> CFilter ()) -> String -> CFilter ()
forall a b. (a -> b) -> a -> b
$ UTCTime -> String
formatDate UTCTime
date
mkChannelElem (ChannelCategory Maybe String
md String
str) = Maybe String -> String -> CFilter ()
mkCategory Maybe String
md String
str
mkChannelElem (Generator String
str) = String -> String -> CFilter ()
mkSimple String
"generator" String
str
mkChannelElem (Cloud String
host Int
port String
path String
proc CloudProtocol
proto)
= String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"cloud" [(String
"domain", String -> CFilter ()
forall i. String -> CFilter i
literal String
host),
(String
"port", String -> CFilter ()
forall i. String -> CFilter i
literal (Int -> String
forall a. Show a => a -> String
show Int
port)),
(String
"path", String -> CFilter ()
forall i. String -> CFilter i
literal String
path),
(String
"registerProcedure", String -> CFilter ()
forall i. String -> CFilter i
literal String
proc),
(String
"protocol", String -> CFilter ()
forall i. String -> CFilter i
literal (CloudProtocol -> String
protocolName CloudProtocol
proto))] []
mkChannelElem (TTL Int
minutes) = String -> String -> CFilter ()
mkSimple String
"ttl" (String -> CFilter ()) -> String -> CFilter ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
minutes
mkChannelElem (Image Link
uri String
title Link
link Maybe Int
mw Maybe Int
mh Maybe String
mdesc)
= String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"image" ([String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"url" [String -> CFilter ()
forall i. String -> CFilter i
literal (Link -> String
forall a. Show a => a -> String
show Link
uri)],
String -> CFilter ()
mkTitle String
title, Link -> CFilter ()
mkLink Link
link]
[CFilter ()] -> [CFilter ()] -> [CFilter ()]
forall a. [a] -> [a] -> [a]
++ (Int -> CFilter ()) -> Maybe Int -> [CFilter ()]
forall a. (a -> CFilter ()) -> Maybe a -> [CFilter ()]
maybeElem (String -> String -> CFilter ()
mkSimple String
"width" (String -> CFilter ()) -> (Int -> String) -> Int -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
mw
[CFilter ()] -> [CFilter ()] -> [CFilter ()]
forall a. [a] -> [a] -> [a]
++ (Int -> CFilter ()) -> Maybe Int -> [CFilter ()]
forall a. (a -> CFilter ()) -> Maybe a -> [CFilter ()]
maybeElem (String -> String -> CFilter ()
mkSimple String
"height" (String -> CFilter ()) -> (Int -> String) -> Int -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
mh
[CFilter ()] -> [CFilter ()] -> [CFilter ()]
forall a. [a] -> [a] -> [a]
++ (String -> CFilter ()) -> Maybe String -> [CFilter ()]
forall a. (a -> CFilter ()) -> Maybe a -> [CFilter ()]
maybeElem String -> CFilter ()
mkDescription Maybe String
mdesc)
mkChannelElem (Rating String
str) = String -> String -> CFilter ()
mkSimple String
"rating" String
str
mkChannelElem (TextInput String
title String
desc String
name Link
link)
= String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"textInput" [String -> CFilter ()
mkTitle String
title, String -> CFilter ()
mkDescription String
desc,
String -> String -> CFilter ()
mkSimple String
"name" String
name, Link -> CFilter ()
mkLink Link
link]
mkChannelElem (SkipHours [Int]
hs) = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"skipHours" ((Int -> CFilter ()) -> [Int] -> [CFilter ()]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> CFilter ()
mkSimple String
"hour" (String -> CFilter ()) -> (Int -> String) -> Int -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) [Int]
hs)
mkChannelElem (SkipDays [Weekday]
ds) = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"skipDays" ((Weekday -> CFilter ()) -> [Weekday] -> [CFilter ()]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> CFilter ()
mkSimple String
"day" (String -> CFilter ())
-> (Weekday -> String) -> Weekday -> CFilter ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Weekday -> String
forall a. Show a => a -> String
show) [Weekday]
ds)
protocolName :: CloudProtocol -> String
protocolName :: CloudProtocol -> String
protocolName CloudProtocol
CloudProtocolXmlRpc = String
"xml-rpc"
protocolName CloudProtocol
CloudProtocolSOAP = String
"soap"
mkItem :: Item -> CFilter ()
mkItem :: Item -> CFilter ()
mkItem Item
itemElems = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"item" ((ItemElem -> CFilter ()) -> Item -> [CFilter ()]
forall a b. (a -> b) -> [a] -> [b]
map ItemElem -> CFilter ()
mkItemElem Item
itemElems)
mkItemElem :: ItemElem -> CFilter ()
mkItemElem :: ItemElem -> CFilter ()
mkItemElem (Title String
t) = String -> CFilter ()
mkTitle String
t
mkItemElem (Link Link
l) = Link -> CFilter ()
mkLink Link
l
mkItemElem (Description String
d) = String -> CFilter ()
mkDescription String
d
mkItemElem (Author String
e) = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"author" [String -> CFilter ()
forall i. String -> CFilter i
literal String
e]
mkItemElem (Category Maybe String
md String
str) = Maybe String -> String -> CFilter ()
mkCategory Maybe String
md String
str
mkItemElem (Comments Link
uri) = String -> String -> CFilter ()
mkSimple String
"comments" (String -> CFilter ()) -> String -> CFilter ()
forall a b. (a -> b) -> a -> b
$ Link -> String
forall a. Show a => a -> String
show Link
uri
mkItemElem (Enclosure Link
uri Int
len String
mtype) =
String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"enclosure" [(String
"url", String -> CFilter ()
forall i. String -> CFilter i
literal (Link -> String
forall a. Show a => a -> String
show Link
uri)),
(String
"length", String -> CFilter ()
forall i. String -> CFilter i
literal (Int -> String
forall a. Show a => a -> String
show Int
len)),
(String
"type", String -> CFilter ()
forall i. String -> CFilter i
literal (String
mtype))]
[]
mkItemElem (Guid Bool
perm String
s) = String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"guid" [(String, CFilter ())]
forall {i}. [(String, CFilter i)]
attrs [ String -> CFilter ()
forall i. String -> CFilter i
literal String
s ]
where attrs :: [(String, CFilter i)]
attrs = if Bool
perm then [(String
"isPermaLink", String -> CFilter i
forall i. String -> CFilter i
literal String
"true")] else []
mkItemElem (PubDate UTCTime
ct) = String -> [CFilter ()] -> CFilter ()
forall i. String -> [CFilter i] -> CFilter i
mkElem String
"pubDate" [ String -> CFilter ()
forall i. String -> CFilter i
literal (UTCTime -> String
formatDate UTCTime
ct) ]
mkItemElem (Source Link
uri String
t) =
String -> [(String, CFilter ())] -> [CFilter ()] -> CFilter ()
forall i.
String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
mkElemAttr String
"source" [(String
"url", String -> CFilter ()
forall i. String -> CFilter i
literal (Link -> String
forall a. Show a => a -> String
show Link
uri))] [ String -> CFilter ()
forall i. String -> CFilter i
literal String
t ]