Safe Haskell | None |
---|---|
Language | Haskell2010 |
RSS is an XML dialect for Web content syndication.
Example:
<?xml version="1.0"?> <rss version="2.0"> <channel> <title>Liftoff News</title> <link>http://liftoff.msfc.nasa.gov/</link> <description>Liftoff to Space Exploration.</description> <language>en-us</language> <pubDate>Tue, 10 Jun 2003 04:00:00 GMT</pubDate> <lastBuildDate>Tue, 10 Jun 2003 09:41:01 GMT</lastBuildDate> <docs>http://blogs.law.harvard.edu/tech/rss</docs> <generator>Weblog Editor 2.0</generator> <managingEditor>editor@example.com</managingEditor> <webMaster>webmaster@example.com</webMaster> <item> <title>Star City</title> <link>http://liftoff.msfc.nasa.gov/news/2003/news-starcity.asp</link> <description>How do Americans get ready to work with Russians aboard the International Space Station? They take a crash course in culture, language and protocol at Russia's <a href="http://howe.iki.rssi.ru/GCTC/gctc_e.htm">Star City</a>.</description> <pubDate>Tue, 03 Jun 2003 09:39:21 GMT</pubDate> <guid>http://liftoff.msfc.nasa.gov/2003/06/03.html#item573</guid> </item> </channel> </rss>
Synopsis
- data RssException
- data RssURI = forall a. RssURI (URIRef a)
- withRssURI :: (forall a. URIRef a -> b) -> RssURI -> b
- data RssCategory = RssCategory {}
- data RssEnclosure = RssEnclosure {}
- data RssSource = RssSource {
- sourceUrl :: RssURI
- sourceName :: Text
- data RssGuid
- data RssItem extensions = RssItem {
- itemTitle :: Text
- itemLink :: Maybe RssURI
- itemDescription :: Text
- itemAuthor :: Text
- itemCategories :: [RssCategory]
- itemComments :: Maybe RssURI
- itemEnclosure :: [RssEnclosure]
- itemGuid :: Maybe RssGuid
- itemPubDate :: Maybe UTCTime
- itemSource :: Maybe RssSource
- itemExtensions :: RssItemExtension extensions
- type RssItem' = RssItem NoExtensions
- data RssTextInput = RssTextInput {}
- data CloudProtocol
- data RssCloud = RssCloud {}
- data RssImage = RssImage {
- imageUri :: RssURI
- imageTitle :: Text
- imageLink :: RssURI
- imageWidth :: Maybe Int
- imageHeight :: Maybe Int
- imageDescription :: Text
- newtype Hour = Hour Int
- asHour :: MonadThrow m => Int -> m Hour
- data Day
- asDay :: MonadThrow m => Text -> m Day
- data RssDocument extensions = RssDocument {
- documentVersion :: Version
- channelTitle :: Text
- channelLink :: RssURI
- channelDescription :: Text
- channelItems :: [RssItem extensions]
- channelLanguage :: Text
- channelCopyright :: Text
- channelManagingEditor :: Text
- channelWebmaster :: Text
- channelPubDate :: Maybe UTCTime
- channelLastBuildDate :: Maybe UTCTime
- channelCategories :: [RssCategory]
- channelGenerator :: Text
- channelDocs :: Maybe RssURI
- channelCloud :: Maybe RssCloud
- channelTtl :: Maybe Int
- channelImage :: Maybe RssImage
- channelRating :: Text
- channelTextInput :: Maybe RssTextInput
- channelSkipHours :: Set Hour
- channelSkipDays :: Set Day
- channelExtensions :: RssChannelExtension extensions
- type RssDocument' = RssDocument NoExtensions
- data family RssChannelExtension extensionTag :: *
- data family RssItemExtension extensionTag :: *
- data NoExtensions = NoExtensions
RSS core
data RssException Source #
InvalidBool Text | |
InvalidDay Text | |
InvalidHour Int | |
InvalidInt Text | |
InvalidURI URIParseError | |
InvalidVersion Text | |
InvalidProtocol Text | |
InvalidTime Text | |
MissingElement Text |
Instances
withRssURI :: (forall a. URIRef a -> b) -> RssURI -> b Source #
data RssCategory Source #
The <category>
element.
Instances
data RssEnclosure Source #
The <enclosure>
element.
Instances
The <source>
element.
RssSource | |
|
Instances
Eq RssSource Source # | |
Ord RssSource Source # | |
Defined in Text.RSS.Types | |
Show RssSource Source # | |
Generic RssSource Source # | |
type Rep RssSource Source # | |
Defined in Text.RSS.Types type Rep RssSource = D1 ('MetaData "RssSource" "Text.RSS.Types" "rss-conduit-0.6.0.1-DHcXfD2J21T3sxz3iuRHLV" 'False) (C1 ('MetaCons "RssSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RssURI) :*: S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
The <guid>
element.
Instances
Eq RssGuid Source # | |
Ord RssGuid Source # | |
Show RssGuid Source # | |
Generic RssGuid Source # | |
type Rep RssGuid Source # | |
Defined in Text.RSS.Types type Rep RssGuid = D1 ('MetaData "RssGuid" "Text.RSS.Types" "rss-conduit-0.6.0.1-DHcXfD2J21T3sxz3iuRHLV" 'False) (C1 ('MetaCons "GuidText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "GuidUri" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RssURI))) |
data RssItem extensions Source #
The <item>
element.
This type is open to extensions.
RssItem | |
|
Instances
data RssTextInput Source #
The <textInput>
element.
Instances
data CloudProtocol Source #
Instances
The <cloud>
element.
Instances
Eq RssCloud Source # | |
Ord RssCloud Source # | |
Defined in Text.RSS.Types | |
Show RssCloud Source # | |
Generic RssCloud Source # | |
type Rep RssCloud Source # | |
Defined in Text.RSS.Types type Rep RssCloud = D1 ('MetaData "RssCloud" "Text.RSS.Types" "rss-conduit-0.6.0.1-DHcXfD2J21T3sxz3iuRHLV" 'False) (C1 ('MetaCons "RssCloud" 'PrefixI 'True) (S1 ('MetaSel ('Just "cloudUri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RssURI) :*: (S1 ('MetaSel ('Just "cloudRegisterProcedure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cloudProtocol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CloudProtocol)))) |
The <image>
element.
RssImage | |
|
Instances
Eq RssImage Source # | |
Ord RssImage Source # | |
Defined in Text.RSS.Types | |
Show RssImage Source # | |
Generic RssImage Source # | |
type Rep RssImage Source # | |
Defined in Text.RSS.Types type Rep RssImage = D1 ('MetaData "RssImage" "Text.RSS.Types" "rss-conduit-0.6.0.1-DHcXfD2J21T3sxz3iuRHLV" 'False) (C1 ('MetaCons "RssImage" 'PrefixI 'True) ((S1 ('MetaSel ('Just "imageUri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RssURI) :*: (S1 ('MetaSel ('Just "imageTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "imageLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RssURI))) :*: (S1 ('MetaSel ('Just "imageWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "imageHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "imageDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) |
Instances
Bounded Day Source # | |
Enum Day Source # | |
Eq Day Source # | |
Ord Day Source # | |
Read Day Source # | |
Show Day Source # | |
Generic Day Source # | |
type Rep Day Source # | |
Defined in Text.RSS.Types type Rep Day = D1 ('MetaData "Day" "Text.RSS.Types" "rss-conduit-0.6.0.1-DHcXfD2J21T3sxz3iuRHLV" 'False) ((C1 ('MetaCons "Monday" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Tuesday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Wednesday" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Thursday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Friday" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Saturday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sunday" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data RssDocument extensions Source #
The <rss>
element.
This type is open to extensions.
RssDocument | |
|
Instances
type RssDocument' = RssDocument NoExtensions Source #
Alias for RssDocument
with no RSS extensions.
RSS extensions
data family RssChannelExtension extensionTag :: * Source #
<channel>
extension type.
Instances
data family RssItemExtension extensionTag :: * Source #
<item>
extension type.
Instances
data NoExtensions Source #
Trivial extension type that parses/renders nothing.