module Text.Atom.Feed
( URI
, NCName
, Date
, MediaType
, Attr
, Feed(..)
, Entry(..)
, EntryContent(..)
, Category(..)
, Generator(..)
, Link(..)
, TextContent(..)
, txtToString
, Source(..)
, Person(..)
, InReplyTo(..)
, InReplyTotal(..)
, newCategory
, nullFeed
, nullEntry
, nullGenerator
, nullLink
, nullSource
, nullPerson
) where
import Prelude.Compat
import Data.Text (Text, unpack)
import Data.XML.Compat
import Data.XML.Types as XML
type URI = Text
type NCName = Text
type Date = Text
type MediaType = Text
data Feed =
Feed
{ Feed -> URI
feedId :: URI
, Feed -> TextContent
feedTitle :: TextContent
, Feed -> URI
feedUpdated :: Date
, Feed -> [Person]
feedAuthors :: [Person]
, Feed -> [Category]
feedCategories :: [Category]
, Feed -> [Person]
feedContributors :: [Person]
, Feed -> Maybe Generator
feedGenerator :: Maybe Generator
, Feed -> Maybe URI
feedIcon :: Maybe URI
, Feed -> [Link]
feedLinks :: [Link]
, Feed -> Maybe URI
feedLogo :: Maybe URI
, Feed -> Maybe TextContent
feedRights :: Maybe TextContent
, Feed -> Maybe TextContent
feedSubtitle :: Maybe TextContent
, Feed -> [Entry]
feedEntries :: [Entry]
, Feed -> [Attr]
feedAttrs :: [Attr]
, Feed -> [Element]
feedOther :: [XML.Element]
}
deriving (Int -> Feed -> ShowS
[Feed] -> ShowS
Feed -> String
(Int -> Feed -> ShowS)
-> (Feed -> String) -> ([Feed] -> ShowS) -> Show Feed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Feed] -> ShowS
$cshowList :: [Feed] -> ShowS
show :: Feed -> String
$cshow :: Feed -> String
showsPrec :: Int -> Feed -> ShowS
$cshowsPrec :: Int -> Feed -> ShowS
Show)
data Entry =
Entry
{ Entry -> URI
entryId :: URI
, Entry -> TextContent
entryTitle :: TextContent
, Entry -> URI
entryUpdated :: Date
, Entry -> [Person]
entryAuthors :: [Person]
, Entry -> [Category]
entryCategories :: [Category]
, Entry -> Maybe EntryContent
entryContent :: Maybe EntryContent
, Entry -> [Person]
entryContributor :: [Person]
, Entry -> [Link]
entryLinks :: [Link]
, Entry -> Maybe URI
entryPublished :: Maybe Date
, Entry -> Maybe TextContent
entryRights :: Maybe TextContent
, Entry -> Maybe Source
entrySource :: Maybe Source
, Entry -> Maybe TextContent
entrySummary :: Maybe TextContent
, Entry -> Maybe InReplyTo
entryInReplyTo :: Maybe InReplyTo
, Entry -> Maybe InReplyTotal
entryInReplyTotal :: Maybe InReplyTotal
, Entry -> [Attr]
entryAttrs :: [Attr]
, Entry -> [Element]
entryOther :: [XML.Element]
}
deriving (Int -> Entry -> ShowS
[Entry] -> ShowS
Entry -> String
(Int -> Entry -> ShowS)
-> (Entry -> String) -> ([Entry] -> ShowS) -> Show Entry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Entry] -> ShowS
$cshowList :: [Entry] -> ShowS
show :: Entry -> String
$cshow :: Entry -> String
showsPrec :: Int -> Entry -> ShowS
$cshowsPrec :: Int -> Entry -> ShowS
Show)
data EntryContent
= TextContent Text
| HTMLContent Text
| XHTMLContent XML.Element
| MixedContent (Maybe Text) [XML.Node]
| ExternalContent (Maybe MediaType) URI
deriving (Int -> EntryContent -> ShowS
[EntryContent] -> ShowS
EntryContent -> String
(Int -> EntryContent -> ShowS)
-> (EntryContent -> String)
-> ([EntryContent] -> ShowS)
-> Show EntryContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EntryContent] -> ShowS
$cshowList :: [EntryContent] -> ShowS
show :: EntryContent -> String
$cshow :: EntryContent -> String
showsPrec :: Int -> EntryContent -> ShowS
$cshowsPrec :: Int -> EntryContent -> ShowS
Show)
data Category =
Category
{ Category -> URI
catTerm :: Text
, Category -> Maybe URI
catScheme :: Maybe URI
, Category -> Maybe URI
catLabel :: Maybe Text
, Category -> [Element]
catOther :: [XML.Element]
}
deriving (Int -> Category -> ShowS
[Category] -> ShowS
Category -> String
(Int -> Category -> ShowS)
-> (Category -> String) -> ([Category] -> ShowS) -> Show Category
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Category] -> ShowS
$cshowList :: [Category] -> ShowS
show :: Category -> String
$cshow :: Category -> String
showsPrec :: Int -> Category -> ShowS
$cshowsPrec :: Int -> Category -> ShowS
Show)
data Generator =
Generator
{ Generator -> Maybe URI
genURI :: Maybe URI
, Generator -> Maybe URI
genVersion :: Maybe Text
, Generator -> URI
genText :: Text
}
deriving (Generator -> Generator -> Bool
(Generator -> Generator -> Bool)
-> (Generator -> Generator -> Bool) -> Eq Generator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Generator -> Generator -> Bool
$c/= :: Generator -> Generator -> Bool
== :: Generator -> Generator -> Bool
$c== :: Generator -> Generator -> Bool
Eq, Int -> Generator -> ShowS
[Generator] -> ShowS
Generator -> String
(Int -> Generator -> ShowS)
-> (Generator -> String)
-> ([Generator] -> ShowS)
-> Show Generator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Generator] -> ShowS
$cshowList :: [Generator] -> ShowS
show :: Generator -> String
$cshow :: Generator -> String
showsPrec :: Int -> Generator -> ShowS
$cshowsPrec :: Int -> Generator -> ShowS
Show)
data Link =
Link
{ Link -> URI
linkHref :: URI
, Link -> Maybe (Either URI URI)
linkRel :: Maybe (Either NCName URI)
, Link -> Maybe URI
linkType :: Maybe MediaType
, Link -> Maybe URI
linkHrefLang :: Maybe Text
, Link -> Maybe URI
linkTitle :: Maybe Text
, Link -> Maybe URI
linkLength :: Maybe Text
, Link -> [Attr]
linkAttrs :: [Attr]
, Link -> [Element]
linkOther :: [XML.Element]
}
deriving (Int -> Link -> ShowS
[Link] -> ShowS
Link -> String
(Int -> Link -> ShowS)
-> (Link -> String) -> ([Link] -> ShowS) -> Show Link
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Link] -> ShowS
$cshowList :: [Link] -> ShowS
show :: Link -> String
$cshow :: Link -> String
showsPrec :: Int -> Link -> ShowS
$cshowsPrec :: Int -> Link -> ShowS
Show)
data TextContent
= TextString Text
| HTMLString Text
| XHTMLString XML.Element
deriving (Int -> TextContent -> ShowS
[TextContent] -> ShowS
TextContent -> String
(Int -> TextContent -> ShowS)
-> (TextContent -> String)
-> ([TextContent] -> ShowS)
-> Show TextContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextContent] -> ShowS
$cshowList :: [TextContent] -> ShowS
show :: TextContent -> String
$cshow :: TextContent -> String
showsPrec :: Int -> TextContent -> ShowS
$cshowsPrec :: Int -> TextContent -> ShowS
Show)
txtToString :: TextContent -> String
txtToString :: TextContent -> String
txtToString (TextString URI
s) = URI -> String
unpack URI
s
txtToString (HTMLString URI
s) = URI -> String
unpack URI
s
txtToString (XHTMLString Element
x) = Element -> String
forall a. Show a => a -> String
show Element
x
data Source =
Source
{ Source -> [Person]
sourceAuthors :: [Person]
, Source -> [Category]
sourceCategories :: [Category]
, Source -> Maybe Generator
sourceGenerator :: Maybe Generator
, Source -> Maybe URI
sourceIcon :: Maybe URI
, Source -> Maybe URI
sourceId :: Maybe URI
, Source -> [Link]
sourceLinks :: [Link]
, Source -> Maybe URI
sourceLogo :: Maybe URI
, Source -> Maybe TextContent
sourceRights :: Maybe TextContent
, Source -> Maybe TextContent
sourceSubtitle :: Maybe TextContent
, Source -> Maybe TextContent
sourceTitle :: Maybe TextContent
, Source -> Maybe URI
sourceUpdated :: Maybe Date
, Source -> [Element]
sourceOther :: [XML.Element]
}
deriving (Int -> Source -> ShowS
[Source] -> ShowS
Source -> String
(Int -> Source -> ShowS)
-> (Source -> String) -> ([Source] -> ShowS) -> Show Source
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Source] -> ShowS
$cshowList :: [Source] -> ShowS
show :: Source -> String
$cshow :: Source -> String
showsPrec :: Int -> Source -> ShowS
$cshowsPrec :: Int -> Source -> ShowS
Show)
data Person =
Person
{ Person -> URI
personName :: Text
, Person -> Maybe URI
personURI :: Maybe URI
, Person -> Maybe URI
personEmail :: Maybe Text
, Person -> [Element]
personOther :: [XML.Element]
}
deriving (Int -> Person -> ShowS
[Person] -> ShowS
Person -> String
(Int -> Person -> ShowS)
-> (Person -> String) -> ([Person] -> ShowS) -> Show Person
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Person] -> ShowS
$cshowList :: [Person] -> ShowS
show :: Person -> String
$cshow :: Person -> String
showsPrec :: Int -> Person -> ShowS
$cshowsPrec :: Int -> Person -> ShowS
Show)
data InReplyTo =
InReplyTo
{ InReplyTo -> URI
replyToRef :: URI
, InReplyTo -> Maybe URI
replyToHRef :: Maybe URI
, InReplyTo -> Maybe URI
replyToType :: Maybe MediaType
, InReplyTo -> Maybe URI
replyToSource :: Maybe URI
, InReplyTo -> [Attr]
replyToOther :: [Attr]
, InReplyTo -> [Node]
replyToContent :: [Node]
}
deriving (Int -> InReplyTo -> ShowS
[InReplyTo] -> ShowS
InReplyTo -> String
(Int -> InReplyTo -> ShowS)
-> (InReplyTo -> String)
-> ([InReplyTo] -> ShowS)
-> Show InReplyTo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InReplyTo] -> ShowS
$cshowList :: [InReplyTo] -> ShowS
show :: InReplyTo -> String
$cshow :: InReplyTo -> String
showsPrec :: Int -> InReplyTo -> ShowS
$cshowsPrec :: Int -> InReplyTo -> ShowS
Show)
data InReplyTotal =
InReplyTotal
{ InReplyTotal -> Integer
replyToTotal :: Integer
, InReplyTotal -> [Attr]
replyToTotalOther :: [Attr]
}
deriving (Int -> InReplyTotal -> ShowS
[InReplyTotal] -> ShowS
InReplyTotal -> String
(Int -> InReplyTotal -> ShowS)
-> (InReplyTotal -> String)
-> ([InReplyTotal] -> ShowS)
-> Show InReplyTotal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InReplyTotal] -> ShowS
$cshowList :: [InReplyTotal] -> ShowS
show :: InReplyTotal -> String
$cshow :: InReplyTotal -> String
showsPrec :: Int -> InReplyTotal -> ShowS
$cshowsPrec :: Int -> InReplyTotal -> ShowS
Show)
newCategory ::
Text
-> Category
newCategory :: URI -> Category
newCategory URI
t = Category :: URI -> Maybe URI -> Maybe URI -> [Element] -> Category
Category {catTerm :: URI
catTerm = URI
t, catScheme :: Maybe URI
catScheme = Maybe URI
forall a. Maybe a
Nothing, catLabel :: Maybe URI
catLabel = URI -> Maybe URI
forall a. a -> Maybe a
Just URI
t, catOther :: [Element]
catOther = []}
nullFeed ::
URI
-> TextContent
-> Date
-> Feed
nullFeed :: URI -> TextContent -> URI -> Feed
nullFeed URI
i TextContent
t URI
u =
Feed :: URI
-> TextContent
-> URI
-> [Person]
-> [Category]
-> [Person]
-> Maybe Generator
-> Maybe URI
-> [Link]
-> Maybe URI
-> Maybe TextContent
-> Maybe TextContent
-> [Entry]
-> [Attr]
-> [Element]
-> Feed
Feed
{ feedId :: URI
feedId = URI
i
, feedTitle :: TextContent
feedTitle = TextContent
t
, feedUpdated :: URI
feedUpdated = URI
u
, feedAuthors :: [Person]
feedAuthors = []
, feedCategories :: [Category]
feedCategories = []
, feedContributors :: [Person]
feedContributors = []
, feedGenerator :: Maybe Generator
feedGenerator = Maybe Generator
forall a. Maybe a
Nothing
, feedIcon :: Maybe URI
feedIcon = Maybe URI
forall a. Maybe a
Nothing
, feedLinks :: [Link]
feedLinks = []
, feedLogo :: Maybe URI
feedLogo = Maybe URI
forall a. Maybe a
Nothing
, feedRights :: Maybe TextContent
feedRights = Maybe TextContent
forall a. Maybe a
Nothing
, feedSubtitle :: Maybe TextContent
feedSubtitle = Maybe TextContent
forall a. Maybe a
Nothing
, feedEntries :: [Entry]
feedEntries = []
, feedAttrs :: [Attr]
feedAttrs = []
, feedOther :: [Element]
feedOther = []
}
nullEntry ::
URI
-> TextContent
-> Date
-> Entry
nullEntry :: URI -> TextContent -> URI -> Entry
nullEntry URI
i TextContent
t URI
u =
Entry :: URI
-> TextContent
-> URI
-> [Person]
-> [Category]
-> Maybe EntryContent
-> [Person]
-> [Link]
-> Maybe URI
-> Maybe TextContent
-> Maybe Source
-> Maybe TextContent
-> Maybe InReplyTo
-> Maybe InReplyTotal
-> [Attr]
-> [Element]
-> Entry
Entry
{ entryId :: URI
entryId = URI
i
, entryTitle :: TextContent
entryTitle = TextContent
t
, entryUpdated :: URI
entryUpdated = URI
u
, entryAuthors :: [Person]
entryAuthors = []
, entryCategories :: [Category]
entryCategories = []
, entryContent :: Maybe EntryContent
entryContent = Maybe EntryContent
forall a. Maybe a
Nothing
, entryContributor :: [Person]
entryContributor = []
, entryLinks :: [Link]
entryLinks = []
, entryPublished :: Maybe URI
entryPublished = Maybe URI
forall a. Maybe a
Nothing
, entryRights :: Maybe TextContent
entryRights = Maybe TextContent
forall a. Maybe a
Nothing
, entrySource :: Maybe Source
entrySource = Maybe Source
forall a. Maybe a
Nothing
, entrySummary :: Maybe TextContent
entrySummary = Maybe TextContent
forall a. Maybe a
Nothing
, entryInReplyTo :: Maybe InReplyTo
entryInReplyTo = Maybe InReplyTo
forall a. Maybe a
Nothing
, entryInReplyTotal :: Maybe InReplyTotal
entryInReplyTotal = Maybe InReplyTotal
forall a. Maybe a
Nothing
, entryAttrs :: [Attr]
entryAttrs = []
, entryOther :: [Element]
entryOther = []
}
nullGenerator ::
Text
-> Generator
nullGenerator :: URI -> Generator
nullGenerator URI
t = Generator :: Maybe URI -> Maybe URI -> URI -> Generator
Generator {genURI :: Maybe URI
genURI = Maybe URI
forall a. Maybe a
Nothing, genVersion :: Maybe URI
genVersion = Maybe URI
forall a. Maybe a
Nothing, genText :: URI
genText = URI
t}
nullLink ::
URI
-> Link
nullLink :: URI -> Link
nullLink URI
uri =
Link :: URI
-> Maybe (Either URI URI)
-> Maybe URI
-> Maybe URI
-> Maybe URI
-> Maybe URI
-> [Attr]
-> [Element]
-> Link
Link
{ linkHref :: URI
linkHref = URI
uri
, linkRel :: Maybe (Either URI URI)
linkRel = Maybe (Either URI URI)
forall a. Maybe a
Nothing
, linkType :: Maybe URI
linkType = Maybe URI
forall a. Maybe a
Nothing
, linkHrefLang :: Maybe URI
linkHrefLang = Maybe URI
forall a. Maybe a
Nothing
, linkTitle :: Maybe URI
linkTitle = Maybe URI
forall a. Maybe a
Nothing
, linkLength :: Maybe URI
linkLength = Maybe URI
forall a. Maybe a
Nothing
, linkAttrs :: [Attr]
linkAttrs = []
, linkOther :: [Element]
linkOther = []
}
nullSource :: Source
nullSource :: Source
nullSource =
Source :: [Person]
-> [Category]
-> Maybe Generator
-> Maybe URI
-> Maybe URI
-> [Link]
-> Maybe URI
-> Maybe TextContent
-> Maybe TextContent
-> Maybe TextContent
-> Maybe URI
-> [Element]
-> Source
Source
{ sourceAuthors :: [Person]
sourceAuthors = []
, sourceCategories :: [Category]
sourceCategories = []
, sourceGenerator :: Maybe Generator
sourceGenerator = Maybe Generator
forall a. Maybe a
Nothing
, sourceIcon :: Maybe URI
sourceIcon = Maybe URI
forall a. Maybe a
Nothing
, sourceId :: Maybe URI
sourceId = Maybe URI
forall a. Maybe a
Nothing
, sourceLinks :: [Link]
sourceLinks = []
, sourceLogo :: Maybe URI
sourceLogo = Maybe URI
forall a. Maybe a
Nothing
, sourceRights :: Maybe TextContent
sourceRights = Maybe TextContent
forall a. Maybe a
Nothing
, sourceSubtitle :: Maybe TextContent
sourceSubtitle = Maybe TextContent
forall a. Maybe a
Nothing
, sourceTitle :: Maybe TextContent
sourceTitle = Maybe TextContent
forall a. Maybe a
Nothing
, sourceUpdated :: Maybe URI
sourceUpdated = Maybe URI
forall a. Maybe a
Nothing
, sourceOther :: [Element]
sourceOther = []
}
nullPerson :: Person
nullPerson :: Person
nullPerson = Person :: URI -> Maybe URI -> Maybe URI -> [Element] -> Person
Person {personName :: URI
personName = URI
"", personURI :: Maybe URI
personURI = Maybe URI
forall a. Maybe a
Nothing, personEmail :: Maybe URI
personEmail = Maybe URI
forall a. Maybe a
Nothing, personOther :: [Element]
personOther = []}