{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
-- | RSS is an XML dialect for Web content syndication.
--
-- Example:
--
-- >
-- >
-- >
-- > Liftoff News
-- > http://liftoff.msfc.nasa.gov/
-- > Liftoff to Space Exploration.
-- > en-us
-- > Tue, 10 Jun 2003 04:00:00 GMT
-- > Tue, 10 Jun 2003 09:41:01 GMT
-- > http://blogs.law.harvard.edu/tech/rss
-- > Weblog Editor 2.0
-- > editor@example.com
-- > webmaster@example.com
-- >
-- > Star City
-- > http://liftoff.msfc.nasa.gov/news/2003/news-starcity.asp
-- > 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>.
-- > Tue, 03 Jun 2003 09:39:21 GMT
-- > http://liftoff.msfc.nasa.gov/2003/06/03.html#item573
-- >
-- >
-- >
module Text.RSS.Types where
-- {{{ Imports
import Control.Exception.Safe
import Data.Semigroup
import Data.Set
import Data.Singletons.Prelude.List
import Data.Text hiding (map)
import Data.Time.Clock
import Data.Time.LocalTime ()
import Data.Version
import Data.Vinyl.Core
import GHC.Generics hiding ((:+:))
import Text.Read
import URI.ByteString
-- }}}
-- * RSS core
data RssException = InvalidBool Text
| InvalidDay Text
| InvalidHour Int
| InvalidInt Text
| InvalidURI URIParseError
| InvalidVersion Text
| InvalidProtocol Text
| InvalidTime Text
| MissingElement Text
deriving instance Eq RssException
deriving instance Generic RssException
deriving instance Show RssException
instance Exception RssException where
displayException (InvalidBool t) = "Invalid bool: " ++ unpack t
displayException (InvalidDay t) = "Invalid day: " ++ unpack t
displayException (InvalidHour i) = "Invalid hour: " ++ show i
displayException (InvalidInt t) = "Invalid int: " ++ unpack t
displayException (InvalidURI t) = "Invalid URI reference: " ++ show t
displayException (InvalidVersion t) = "Invalid version: " ++ unpack t
displayException (InvalidProtocol t) = "Invalid Protocol: expected \"xml-rpc\", \"soap\" or \"http-post\", got \"" ++ unpack t ++ "\""
displayException (InvalidTime t) = "Invalid time: " ++ unpack t
displayException (MissingElement t) = "Missing element: " ++ unpack t
data RssURI = forall a . RssURI (URIRef a)
instance Eq RssURI where
RssURI a@URI{} == RssURI b@URI{} = a == b
RssURI a@RelativeRef{} == RssURI b@RelativeRef{} = a == b
_ == _ = False
instance Ord RssURI where
RssURI a@URI{} `compare` RssURI b@URI{} = a `compare` b
RssURI a@RelativeRef{} `compare` RssURI b@RelativeRef{} = a `compare` b
RssURI a@RelativeRef{} `compare` RssURI b@URI{} = LT
_ `compare` _ = GT
instance Show RssURI where
show (RssURI a@URI{}) = show a
show (RssURI a@RelativeRef{}) = show a
withRssURI :: (forall a . URIRef a -> b) -> RssURI -> b
withRssURI f (RssURI a) = f a
-- | The @\@ element.
data RssCategory = RssCategory
{ categoryDomain :: Text
, categoryName :: Text
}
deriving instance Eq RssCategory
deriving instance Generic RssCategory
deriving instance Ord RssCategory
deriving instance Show RssCategory
-- | The @\@ element.
data RssEnclosure = RssEnclosure
{ enclosureUrl :: RssURI
, enclosureLength :: Int
, enclosureType :: Text
}
deriving instance Eq RssEnclosure
deriving instance Generic RssEnclosure
deriving instance Ord RssEnclosure
deriving instance Show RssEnclosure
-- | The @\