rss-conduit-0.3.2.0: Streaming parser/renderer for the RSS standard.

Safe HaskellNone
LanguageHaskell2010

Text.RSS.Types

Description

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 &lt;a href="http://howe.iki.rssi.ru/GCTC/gctc_e.htm"&gt;Star City&lt;/a&gt;.</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

Documentation

data RssURI Source #

Constructors

RssURI (URIRef a) 

withRssURI :: (forall a. URIRef a -> b) -> RssURI -> b Source #

data RssEnclosure Source #

The <enclosure> element.

data RssSource Source #

The <source> element.

Constructors

RssSource 

data RssGuid Source #

The <guid> element.

Constructors

GuidText Text 
GuidUri RssURI 

data RssItem Source #

The <item> element.

Instances

Eq RssItem Source # 

Methods

(==) :: RssItem -> RssItem -> Bool #

(/=) :: RssItem -> RssItem -> Bool #

Ord RssItem Source # 
Show RssItem Source # 
Generic RssItem Source # 

Associated Types

type Rep RssItem :: * -> * #

Methods

from :: RssItem -> Rep RssItem x #

to :: Rep RssItem x -> RssItem #

type Rep RssItem Source # 

data RssTextInput Source #

The <textInput> element.

data RssImage Source #

The <image> element.

Instances

Eq RssImage Source # 
Ord RssImage Source # 
Show RssImage Source # 
Generic RssImage Source # 

Associated Types

type Rep RssImage :: * -> * #

Methods

from :: RssImage -> Rep RssImage x #

to :: Rep RssImage x -> RssImage #

type Rep RssImage Source # 

newtype Hour Source #

Constructors

Hour Int 

Instances

Bounded Hour Source # 
Enum Hour Source # 

Methods

succ :: Hour -> Hour #

pred :: Hour -> Hour #

toEnum :: Int -> Hour #

fromEnum :: Hour -> Int #

enumFrom :: Hour -> [Hour] #

enumFromThen :: Hour -> Hour -> [Hour] #

enumFromTo :: Hour -> Hour -> [Hour] #

enumFromThenTo :: Hour -> Hour -> Hour -> [Hour] #

Eq Hour Source # 

Methods

(==) :: Hour -> Hour -> Bool #

(/=) :: Hour -> Hour -> Bool #

Ord Hour Source # 

Methods

compare :: Hour -> Hour -> Ordering #

(<) :: Hour -> Hour -> Bool #

(<=) :: Hour -> Hour -> Bool #

(>) :: Hour -> Hour -> Bool #

(>=) :: Hour -> Hour -> Bool #

max :: Hour -> Hour -> Hour #

min :: Hour -> Hour -> Hour #

Read Hour Source # 
Show Hour Source # 

Methods

showsPrec :: Int -> Hour -> ShowS #

show :: Hour -> String #

showList :: [Hour] -> ShowS #

Generic Hour Source # 

Associated Types

type Rep Hour :: * -> * #

Methods

from :: Hour -> Rep Hour x #

to :: Rep Hour x -> Hour #

type Rep Hour Source # 
type Rep Hour = D1 (MetaData "Hour" "Text.RSS.Types" "rss-conduit-0.3.2.0-40ynSxsLOXDvHREn9zh6P" True) (C1 (MetaCons "Hour" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

asHour :: MonadThrow m => Int -> m Hour Source #

Smart constructor for Hour

data Day Source #

Instances

Bounded Day Source # 

Methods

minBound :: Day #

maxBound :: Day #

Enum Day Source # 

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day Source # 

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Ord Day Source # 

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Read Day Source # 
Show Day Source # 

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Generic Day Source # 

Associated Types

type Rep Day :: * -> * #

Methods

from :: Day -> Rep Day x #

to :: Rep Day x -> Day #

type Rep Day Source # 
type Rep Day = D1 (MetaData "Day" "Text.RSS.Types" "rss-conduit-0.3.2.0-40ynSxsLOXDvHREn9zh6P" False) ((:+:) ((:+:) (C1 (MetaCons "Monday" PrefixI False) U1) ((:+:) (C1 (MetaCons "Tuesday" PrefixI False) U1) (C1 (MetaCons "Wednesday" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Thursday" PrefixI False) U1) (C1 (MetaCons "Friday" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Saturday" PrefixI False) U1) (C1 (MetaCons "Sunday" PrefixI False) U1))))

asDay :: MonadThrow m => Text -> m Day Source #

Basic parser for Day.

data RssDocument Source #

The <rss> element.

Instances

Eq RssDocument Source # 
Ord RssDocument Source # 
Show RssDocument Source # 
Generic RssDocument Source # 

Associated Types

type Rep RssDocument :: * -> * #

type Rep RssDocument Source # 
type Rep RssDocument = D1 (MetaData "RssDocument" "Text.RSS.Types" "rss-conduit-0.3.2.0-40ynSxsLOXDvHREn9zh6P" False) (C1 (MetaCons "RssDocument" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "documentVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) (S1 (MetaSel (Just Symbol "channelTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "channelLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RssURI)) ((:*:) (S1 (MetaSel (Just Symbol "channelDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "channelItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RssItem]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "channelLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "channelCopyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "channelManagingEditor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "channelWebmaster") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "channelPubDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "channelLastBuildDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime))) (S1 (MetaSel (Just Symbol "channelCategories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RssCategory]))) ((:*:) (S1 (MetaSel (Just Symbol "channelGenerator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "channelDocs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RssURI))) (S1 (MetaSel (Just Symbol "channelCloud") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RssCloud)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "channelTtl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "channelImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RssImage))) (S1 (MetaSel (Just Symbol "channelRating") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "channelTextInput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RssTextInput))) ((:*:) (S1 (MetaSel (Just Symbol "channelSkipHours") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Hour))) (S1 (MetaSel (Just Symbol "channelSkipDays") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Day)))))))))