module Text.Feed.Types
( Feed(..)
, Item(..)
, FeedKind(..)
) where
import Prelude.Compat
import Data.Text
import qualified Data.XML.Types as XML
import qualified Text.Atom.Feed as Atom
import qualified Text.RSS.Syntax as RSS
import qualified Text.RSS1.Syntax as RSS1
data Feed
= AtomFeed Atom.Feed
| RSS.RSS
| RSS1.Feed
| XMLFeed 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 Item
= AtomItem Atom.Entry
| RSS.RSSItem
| RSS1.Item
| XMLItem XML.Element
deriving (Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
(Int -> Item -> ShowS)
-> (Item -> String) -> ([Item] -> ShowS) -> Show Item
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Item] -> ShowS
$cshowList :: [Item] -> ShowS
show :: Item -> String
$cshow :: Item -> String
showsPrec :: Int -> Item -> ShowS
$cshowsPrec :: Int -> Item -> ShowS
Show)
data FeedKind
= AtomKind
| (Maybe Text)
| RDFKind (Maybe Text)
deriving (FeedKind -> FeedKind -> Bool
(FeedKind -> FeedKind -> Bool)
-> (FeedKind -> FeedKind -> Bool) -> Eq FeedKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeedKind -> FeedKind -> Bool
$c/= :: FeedKind -> FeedKind -> Bool
== :: FeedKind -> FeedKind -> Bool
$c== :: FeedKind -> FeedKind -> Bool
Eq, Int -> FeedKind -> ShowS
[FeedKind] -> ShowS
FeedKind -> String
(Int -> FeedKind -> ShowS)
-> (FeedKind -> String) -> ([FeedKind] -> ShowS) -> Show FeedKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FeedKind] -> ShowS
$cshowList :: [FeedKind] -> ShowS
show :: FeedKind -> String
$cshow :: FeedKind -> String
showsPrec :: Int -> FeedKind -> ShowS
$cshowsPrec :: Int -> FeedKind -> ShowS
Show)