{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} -- | Atom is an XML-based Web content and metadata syndication format. -- -- Example: -- -- > -- > -- > -- > Example Feed -- > -- > 2003-12-13T18:30:02Z -- > -- > John Doe -- > -- > urn:uuid:60a76c80-d399-11d9-b93C-0003939e0af6 -- > -- > -- > Atom-Powered Robots Run Amok -- > -- > urn:uuid:1225c695-cfb8-4ebb-aaaa-80da344efa6a -- > 2003-12-13T18:30:02Z -- > Some text. -- > -- > -- > module Text.Atom.Types (module Text.Atom.Types) where -- {{{ Imports import Data.NonNull import Data.Text import Data.Time.Clock import Data.Time.LocalTime () import GHC.Generics import URI.ByteString -- }}} data AtomURI = forall a . AtomURI (URIRef a) withAtomURI :: (forall a . URIRef a -> b) -> AtomURI -> b withAtomURI f (AtomURI a) = f a instance Eq AtomURI where AtomURI a@URI{} == AtomURI b@URI{} = a == b AtomURI a@RelativeRef{} == AtomURI b@RelativeRef{} = a == b _ == _ = False instance Ord AtomURI where AtomURI a@URI{} `compare` AtomURI b@URI{} = a `compare` b AtomURI a@RelativeRef{} `compare` AtomURI b@RelativeRef{} = a `compare` b AtomURI a@URI{} `compare` _ = LT AtomURI a@RelativeRef{} `compare` b = b `compare` AtomURI a instance Show AtomURI where show (AtomURI a@URI{}) = show a show (AtomURI a@RelativeRef{}) = show a data TextType = TypeText | TypeHTML deriving(Eq, Ord, Generic, Read, Show) -- | An atom text construct. data AtomText = AtomPlainText TextType Text | AtomXHTMLText Text -- ^ XHTML special characters will be in encoded form deriving instance Eq AtomText deriving instance Ord AtomText deriving instance Generic AtomText deriving instance Read AtomText deriving instance Show AtomText -- | An atom person construct. data AtomPerson = AtomPerson { personName :: NonNull Text , personEmail :: Text , personUri :: Maybe AtomURI } deriving instance Eq AtomPerson deriving instance Ord AtomPerson deriving instance Generic AtomPerson -- deriving instance Read AtomPerson deriving instance Show AtomPerson -- | The @atom:category@ element. data AtomCategory = AtomCategory { categoryTerm :: NonNull Text , categoryScheme :: Text , categoryLabel :: Text } deriving instance Eq AtomCategory deriving instance Ord AtomCategory deriving instance Generic AtomCategory deriving instance Read AtomCategory deriving instance Show AtomCategory -- | The @atom:link@ element. data AtomLink = AtomLink { linkHref :: AtomURI , linkRel :: Text , linkType :: Text , linkLang :: Text , linkTitle :: Text , linkLength :: Text } deriving instance Eq AtomLink deriving instance Ord AtomLink deriving instance Generic AtomLink -- deriving instance Read AtomLink deriving instance Show AtomLink -- | The @atom:generator@ element. data AtomGenerator = AtomGenerator { generatorUri :: Maybe AtomURI , generatorVersion :: Text , generatorContent :: NonNull Text } deriving instance Eq AtomGenerator deriving instance Ord AtomGenerator deriving instance Generic AtomGenerator -- deriving instance Read AtomGenerator deriving instance Show AtomGenerator -- | The @atom:source@ element. data AtomSource = AtomSource { sourceAuthors :: [AtomPerson] , sourceCategories :: [AtomCategory] , sourceContributors :: [AtomPerson] , sourceGenerator :: Maybe AtomGenerator , sourceIcon :: Maybe AtomURI , sourceId :: Text , sourceLinks :: [AtomLink] , sourceLogo :: Maybe AtomURI , sourceRights :: Maybe AtomText , sourceSubtitle :: Maybe AtomText , sourceTitle :: Maybe AtomText , sourceUpdated :: Maybe UTCTime } deriving instance Eq AtomSource deriving instance Ord AtomSource deriving instance Generic AtomSource -- deriving instance Read AtomSource deriving instance Show AtomSource type Type = Text -- | The @atom:content@ element. data AtomContent = AtomContentInlineText TextType Text | AtomContentInlineXHTML Text | AtomContentInlineOther Type Text | AtomContentOutOfLine Type AtomURI deriving instance Eq AtomContent deriving instance Ord AtomContent deriving instance Generic AtomContent -- deriving instance Read AtomContent deriving instance Show AtomContent -- | The @atom:entry@ element. data AtomEntry = AtomEntry { entryAuthors :: [AtomPerson] , entryCategories :: [AtomCategory] , entryContent :: Maybe AtomContent , entryContributors :: [AtomPerson] , entryId :: Text , entryLinks :: [AtomLink] , entryPublished :: Maybe UTCTime , entryRights :: Maybe AtomText , entrySource :: Maybe AtomSource , entrySummary :: Maybe AtomText , entryTitle :: AtomText , entryUpdated :: UTCTime } deriving instance Eq AtomEntry deriving instance Ord AtomEntry deriving instance Generic AtomEntry -- deriving instance Read AtomEntry deriving instance Show AtomEntry -- | The @atom:feed@ element. data AtomFeed = AtomFeed { feedAuthors :: [AtomPerson] , feedCategories :: [AtomCategory] , feedContributors :: [AtomPerson] , feedEntries :: [AtomEntry] , feedGenerator :: Maybe AtomGenerator , feedIcon :: Maybe AtomURI , feedId :: Text , feedLinks :: [AtomLink] , feedLogo :: Maybe AtomURI , feedRights :: Maybe AtomText , feedSubtitle :: Maybe AtomText , feedTitle :: AtomText , feedUpdated :: UTCTime } deriving instance Eq AtomFeed deriving instance Ord AtomFeed deriving instance Generic AtomFeed -- deriving instance Read AtomFeed deriving instance Show AtomFeed