module Text.RSS.Syntax
( RSS(..)
, URLString
, DateString
, RSSChannel(..)
, RSSItem(..)
, RSSSource(..)
, RSSEnclosure(..)
, RSSCategory(..)
, RSSGuid(..)
, RSSImage(..)
, RSSCloud(..)
, RSSTextInput(..)
, nullRSS
, nullChannel
, nullItem
, nullSource
, nullEnclosure
, newCategory
, nullGuid
, nullPermaGuid
, nullImage
, nullCloud
, nullTextInput
) where
import Prelude.Compat
import Data.Text (Text)
import Data.XML.Compat
import Data.XML.Types as XML
data =
{ :: Text
, :: [Attr]
, :: RSSChannel
, :: [XML.Element]
}
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
showList :: [RSS] -> ShowS
$cshowList :: [RSS] -> ShowS
show :: RSS -> String
$cshow :: RSS -> String
showsPrec :: Int -> RSS -> ShowS
$cshowsPrec :: Int -> RSS -> ShowS
Show)
type URLString = Text
type DateString = Text
data =
{ :: Text
, :: URLString
, :: Text
, :: [RSSItem]
, :: Maybe Text
, :: Maybe Text
, :: Maybe Text
, :: Maybe Text
, :: Maybe DateString
, :: Maybe DateString
, :: [RSSCategory]
, :: Maybe Text
, :: Maybe URLString
, :: Maybe RSSCloud
, :: Maybe Integer
, :: Maybe RSSImage
, :: Maybe Text
, :: Maybe RSSTextInput
, :: Maybe [Integer]
, :: Maybe [Text]
, :: [XML.Element]
}
deriving (Int -> RSSChannel -> ShowS
[RSSChannel] -> ShowS
RSSChannel -> String
(Int -> RSSChannel -> ShowS)
-> (RSSChannel -> String)
-> ([RSSChannel] -> ShowS)
-> Show RSSChannel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSChannel] -> ShowS
$cshowList :: [RSSChannel] -> ShowS
show :: RSSChannel -> String
$cshow :: RSSChannel -> String
showsPrec :: Int -> RSSChannel -> ShowS
$cshowsPrec :: Int -> RSSChannel -> ShowS
Show)
data =
{ :: Maybe Text
, :: Maybe URLString
, :: Maybe Text
, :: Maybe Text
, :: [RSSCategory]
, :: Maybe URLString
, :: Maybe Text
, :: Maybe RSSEnclosure
, :: Maybe RSSGuid
, :: Maybe DateString
, :: Maybe RSSSource
, :: [Attr]
, :: [XML.Element]
}
deriving (Int -> RSSItem -> ShowS
[RSSItem] -> ShowS
RSSItem -> String
(Int -> RSSItem -> ShowS)
-> (RSSItem -> String) -> ([RSSItem] -> ShowS) -> Show RSSItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSItem] -> ShowS
$cshowList :: [RSSItem] -> ShowS
show :: RSSItem -> String
$cshow :: RSSItem -> String
showsPrec :: Int -> RSSItem -> ShowS
$cshowsPrec :: Int -> RSSItem -> ShowS
Show)
data =
{ :: URLString
, :: [Attr]
, :: Text
}
deriving (Int -> RSSSource -> ShowS
[RSSSource] -> ShowS
RSSSource -> String
(Int -> RSSSource -> ShowS)
-> (RSSSource -> String)
-> ([RSSSource] -> ShowS)
-> Show RSSSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSSource] -> ShowS
$cshowList :: [RSSSource] -> ShowS
show :: RSSSource -> String
$cshow :: RSSSource -> String
showsPrec :: Int -> RSSSource -> ShowS
$cshowsPrec :: Int -> RSSSource -> ShowS
Show)
data =
{ :: URLString
, :: Maybe Integer
, :: Text
, :: [Attr]
}
deriving (Int -> RSSEnclosure -> ShowS
[RSSEnclosure] -> ShowS
RSSEnclosure -> String
(Int -> RSSEnclosure -> ShowS)
-> (RSSEnclosure -> String)
-> ([RSSEnclosure] -> ShowS)
-> Show RSSEnclosure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSEnclosure] -> ShowS
$cshowList :: [RSSEnclosure] -> ShowS
show :: RSSEnclosure -> String
$cshow :: RSSEnclosure -> String
showsPrec :: Int -> RSSEnclosure -> ShowS
$cshowsPrec :: Int -> RSSEnclosure -> ShowS
Show)
data =
{ RSSCategory -> Maybe Text
rssCategoryDomain :: Maybe Text
, :: [Attr]
, :: Text
}
deriving (Int -> RSSCategory -> ShowS
[RSSCategory] -> ShowS
RSSCategory -> String
(Int -> RSSCategory -> ShowS)
-> (RSSCategory -> String)
-> ([RSSCategory] -> ShowS)
-> Show RSSCategory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSCategory] -> ShowS
$cshowList :: [RSSCategory] -> ShowS
show :: RSSCategory -> String
$cshow :: RSSCategory -> String
showsPrec :: Int -> RSSCategory -> ShowS
$cshowsPrec :: Int -> RSSCategory -> ShowS
Show)
data =
{ :: Maybe Bool
, :: [Attr]
, :: Text
}
deriving (Int -> RSSGuid -> ShowS
[RSSGuid] -> ShowS
RSSGuid -> String
(Int -> RSSGuid -> ShowS)
-> (RSSGuid -> String) -> ([RSSGuid] -> ShowS) -> Show RSSGuid
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSGuid] -> ShowS
$cshowList :: [RSSGuid] -> ShowS
show :: RSSGuid -> String
$cshow :: RSSGuid -> String
showsPrec :: Int -> RSSGuid -> ShowS
$cshowsPrec :: Int -> RSSGuid -> ShowS
Show)
data =
{ :: URLString
, :: Text
, :: URLString
, :: Maybe Integer
, :: Maybe Integer
, :: Maybe Text
, :: [XML.Element]
}
deriving (Int -> RSSImage -> ShowS
[RSSImage] -> ShowS
RSSImage -> String
(Int -> RSSImage -> ShowS)
-> (RSSImage -> String) -> ([RSSImage] -> ShowS) -> Show RSSImage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSImage] -> ShowS
$cshowList :: [RSSImage] -> ShowS
show :: RSSImage -> String
$cshow :: RSSImage -> String
showsPrec :: Int -> RSSImage -> ShowS
$cshowsPrec :: Int -> RSSImage -> ShowS
Show)
data =
{ RSSCloud -> Maybe Text
rssCloudDomain :: Maybe Text
, :: Maybe Text
, :: Maybe Text
, :: Maybe Text
, :: Maybe Text
, :: [Attr]
}
deriving (Int -> RSSCloud -> ShowS
[RSSCloud] -> ShowS
RSSCloud -> String
(Int -> RSSCloud -> ShowS)
-> (RSSCloud -> String) -> ([RSSCloud] -> ShowS) -> Show RSSCloud
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSCloud] -> ShowS
$cshowList :: [RSSCloud] -> ShowS
show :: RSSCloud -> String
$cshow :: RSSCloud -> String
showsPrec :: Int -> RSSCloud -> ShowS
$cshowsPrec :: Int -> RSSCloud -> ShowS
Show)
data =
{ :: Text
, :: Text
, :: Text
, :: URLString
, :: [Attr]
, :: [XML.Element]
}
deriving (Int -> RSSTextInput -> ShowS
[RSSTextInput] -> ShowS
RSSTextInput -> String
(Int -> RSSTextInput -> ShowS)
-> (RSSTextInput -> String)
-> ([RSSTextInput] -> ShowS)
-> Show RSSTextInput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RSSTextInput] -> ShowS
$cshowList :: [RSSTextInput] -> ShowS
show :: RSSTextInput -> String
$cshow :: RSSTextInput -> String
showsPrec :: Int -> RSSTextInput -> ShowS
$cshowsPrec :: Int -> RSSTextInput -> ShowS
Show)
nullRSS ::
Text
-> URLString
-> RSS
Text
title Text
link =
RSS :: Text -> [Attr] -> RSSChannel -> [Element] -> RSS
RSS {rssVersion :: Text
rssVersion = Text
"2.0", rssAttrs :: [Attr]
rssAttrs = [], rssChannel :: RSSChannel
rssChannel = Text -> Text -> RSSChannel
nullChannel Text
title Text
link, rssOther :: [Element]
rssOther = []}
nullChannel ::
Text
-> URLString
-> RSSChannel
nullChannel :: Text -> Text -> RSSChannel
nullChannel Text
title Text
link =
RSSChannel :: Text
-> Text
-> Text
-> [RSSItem]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> [RSSCategory]
-> Maybe Text
-> Maybe Text
-> Maybe RSSCloud
-> Maybe Integer
-> Maybe RSSImage
-> Maybe Text
-> Maybe RSSTextInput
-> Maybe [Integer]
-> Maybe [Text]
-> [Element]
-> RSSChannel
RSSChannel
{ rssTitle :: Text
rssTitle = Text
title
, rssLink :: Text
rssLink = Text
link
, rssDescription :: Text
rssDescription = Text
title
, rssItems :: [RSSItem]
rssItems = []
, rssLanguage :: Maybe Text
rssLanguage = Maybe Text
forall a. Maybe a
Nothing
, rssCopyright :: Maybe Text
rssCopyright = Maybe Text
forall a. Maybe a
Nothing
, rssEditor :: Maybe Text
rssEditor = Maybe Text
forall a. Maybe a
Nothing
, rssWebMaster :: Maybe Text
rssWebMaster = Maybe Text
forall a. Maybe a
Nothing
, rssPubDate :: Maybe Text
rssPubDate = Maybe Text
forall a. Maybe a
Nothing
, rssLastUpdate :: Maybe Text
rssLastUpdate = Maybe Text
forall a. Maybe a
Nothing
, rssCategories :: [RSSCategory]
rssCategories = []
, rssGenerator :: Maybe Text
rssGenerator = Maybe Text
forall a. Maybe a
Nothing
, rssDocs :: Maybe Text
rssDocs = Maybe Text
forall a. Maybe a
Nothing
, rssCloud :: Maybe RSSCloud
rssCloud = Maybe RSSCloud
forall a. Maybe a
Nothing
, rssTTL :: Maybe Integer
rssTTL = Maybe Integer
forall a. Maybe a
Nothing
, rssImage :: Maybe RSSImage
rssImage = Maybe RSSImage
forall a. Maybe a
Nothing
, rssRating :: Maybe Text
rssRating = Maybe Text
forall a. Maybe a
Nothing
, rssTextInput :: Maybe RSSTextInput
rssTextInput = Maybe RSSTextInput
forall a. Maybe a
Nothing
, rssSkipHours :: Maybe [Integer]
rssSkipHours = Maybe [Integer]
forall a. Maybe a
Nothing
, rssSkipDays :: Maybe [Text]
rssSkipDays = Maybe [Text]
forall a. Maybe a
Nothing
, rssChannelOther :: [Element]
rssChannelOther = []
}
nullItem ::
Text
-> RSSItem
nullItem :: Text -> RSSItem
nullItem Text
title =
RSSItem :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> [RSSCategory]
-> Maybe Text
-> Maybe Text
-> Maybe RSSEnclosure
-> Maybe RSSGuid
-> Maybe Text
-> Maybe RSSSource
-> [Attr]
-> [Element]
-> RSSItem
RSSItem
{ rssItemTitle :: Maybe Text
rssItemTitle = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
title
, rssItemLink :: Maybe Text
rssItemLink = Maybe Text
forall a. Maybe a
Nothing
, rssItemDescription :: Maybe Text
rssItemDescription = Maybe Text
forall a. Maybe a
Nothing
, rssItemAuthor :: Maybe Text
rssItemAuthor = Maybe Text
forall a. Maybe a
Nothing
, rssItemCategories :: [RSSCategory]
rssItemCategories = []
, rssItemComments :: Maybe Text
rssItemComments = Maybe Text
forall a. Maybe a
Nothing
, rssItemContent :: Maybe Text
rssItemContent = Maybe Text
forall a. Maybe a
Nothing
, rssItemEnclosure :: Maybe RSSEnclosure
rssItemEnclosure = Maybe RSSEnclosure
forall a. Maybe a
Nothing
, rssItemGuid :: Maybe RSSGuid
rssItemGuid = Maybe RSSGuid
forall a. Maybe a
Nothing
, rssItemPubDate :: Maybe Text
rssItemPubDate = Maybe Text
forall a. Maybe a
Nothing
, rssItemSource :: Maybe RSSSource
rssItemSource = Maybe RSSSource
forall a. Maybe a
Nothing
, rssItemAttrs :: [Attr]
rssItemAttrs = []
, rssItemOther :: [Element]
rssItemOther = []
}
nullSource ::
URLString
-> Text
-> RSSSource
nullSource :: Text -> Text -> RSSSource
nullSource Text
url Text
title = RSSSource :: Text -> [Attr] -> Text -> RSSSource
RSSSource {rssSourceURL :: Text
rssSourceURL = Text
url, rssSourceAttrs :: [Attr]
rssSourceAttrs = [], rssSourceTitle :: Text
rssSourceTitle = Text
title}
nullEnclosure ::
URLString
-> Maybe Integer
-> Text
-> RSSEnclosure
nullEnclosure :: Text -> Maybe Integer -> Text -> RSSEnclosure
nullEnclosure Text
url Maybe Integer
mb_len Text
ty =
RSSEnclosure :: Text -> Maybe Integer -> Text -> [Attr] -> RSSEnclosure
RSSEnclosure
{ rssEnclosureURL :: Text
rssEnclosureURL = Text
url
, rssEnclosureLength :: Maybe Integer
rssEnclosureLength = Maybe Integer
mb_len
, rssEnclosureType :: Text
rssEnclosureType = Text
ty
, rssEnclosureAttrs :: [Attr]
rssEnclosureAttrs = []
}
newCategory ::
Text
-> RSSCategory
newCategory :: Text -> RSSCategory
newCategory Text
nm =
RSSCategory :: Maybe Text -> [Attr] -> Text -> RSSCategory
RSSCategory {rssCategoryDomain :: Maybe Text
rssCategoryDomain = Maybe Text
forall a. Maybe a
Nothing, rssCategoryAttrs :: [Attr]
rssCategoryAttrs = [], rssCategoryValue :: Text
rssCategoryValue = Text
nm}
nullGuid ::
Text
-> RSSGuid
nullGuid :: Text -> RSSGuid
nullGuid Text
v = RSSGuid :: Maybe Bool -> [Attr] -> Text -> RSSGuid
RSSGuid {rssGuidPermanentURL :: Maybe Bool
rssGuidPermanentURL = Maybe Bool
forall a. Maybe a
Nothing, rssGuidAttrs :: [Attr]
rssGuidAttrs = [], rssGuidValue :: Text
rssGuidValue = Text
v}
nullPermaGuid ::
Text
-> RSSGuid
nullPermaGuid :: Text -> RSSGuid
nullPermaGuid Text
v = (Text -> RSSGuid
nullGuid Text
v) {rssGuidPermanentURL :: Maybe Bool
rssGuidPermanentURL = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True}
nullImage ::
URLString
-> Text
-> URLString
-> RSSImage
nullImage :: Text -> Text -> Text -> RSSImage
nullImage Text
url Text
title Text
link =
RSSImage :: Text
-> Text
-> Text
-> Maybe Integer
-> Maybe Integer
-> Maybe Text
-> [Element]
-> RSSImage
RSSImage
{ rssImageURL :: Text
rssImageURL = Text
url
, rssImageTitle :: Text
rssImageTitle = Text
title
, rssImageLink :: Text
rssImageLink = Text
link
, rssImageWidth :: Maybe Integer
rssImageWidth = Maybe Integer
forall a. Maybe a
Nothing
, rssImageHeight :: Maybe Integer
rssImageHeight = Maybe Integer
forall a. Maybe a
Nothing
, rssImageDesc :: Maybe Text
rssImageDesc = Maybe Text
forall a. Maybe a
Nothing
, rssImageOther :: [Element]
rssImageOther = []
}
nullCloud :: RSSCloud
nullCloud :: RSSCloud
nullCloud =
RSSCloud :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> [Attr]
-> RSSCloud
RSSCloud
{ rssCloudDomain :: Maybe Text
rssCloudDomain = Maybe Text
forall a. Maybe a
Nothing
, rssCloudPort :: Maybe Text
rssCloudPort = Maybe Text
forall a. Maybe a
Nothing
, rssCloudPath :: Maybe Text
rssCloudPath = Maybe Text
forall a. Maybe a
Nothing
, rssCloudRegisterProcedure :: Maybe Text
rssCloudRegisterProcedure = Maybe Text
forall a. Maybe a
Nothing
, rssCloudProtocol :: Maybe Text
rssCloudProtocol = Maybe Text
forall a. Maybe a
Nothing
, rssCloudAttrs :: [Attr]
rssCloudAttrs = []
}
nullTextInput ::
Text
-> Text
-> URLString
-> RSSTextInput
nullTextInput :: Text -> Text -> Text -> RSSTextInput
nullTextInput Text
title Text
nm Text
link =
RSSTextInput :: Text -> Text -> Text -> Text -> [Attr] -> [Element] -> RSSTextInput
RSSTextInput
{ rssTextInputTitle :: Text
rssTextInputTitle = Text
title
, rssTextInputDesc :: Text
rssTextInputDesc = Text
title
, rssTextInputName :: Text
rssTextInputName = Text
nm
, rssTextInputLink :: Text
rssTextInputLink = Text
link
, rssTextInputAttrs :: [Attr]
rssTextInputAttrs = []
, rssTextInputOther :: [Element]
rssTextInputOther = []
}