{-# LANGUAGE DeriveGeneric          #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE GADTs                  #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE OverloadedStrings      #-}
{-# LANGUAGE RankNTypes             #-}
{-# LANGUAGE StandaloneDeriving     #-}
-- | Atom is an XML-based Web content and metadata syndication format.
--
-- Example:
--
-- > <?xml version="1.0" encoding="utf-8"?>
-- > <feed xmlns="http://www.w3.org/2005/Atom">
-- >
-- >   <title>Example Feed</title>
-- >   <link href="http://example.org/"/>
-- >   <updated>2003-12-13T18:30:02Z</updated>
-- >   <author>
-- >     <name>John Doe</name>
-- >   </author>
-- >   <id>urn:uuid:60a76c80-d399-11d9-b93C-0003939e0af6</id>
-- >
-- >   <entry>
-- >     <title>Atom-Powered Robots Run Amok</title>
-- >     <link href="http://example.org/2003/12/13/atom03"/>
-- >     <id>urn:uuid:1225c695-cfb8-4ebb-aaaa-80da344efa6a</id>
-- >     <updated>2003-12-13T18:30:02Z</updated>
-- >     <summary>Some text.</summary>
-- >   </entry>
-- >
-- > </feed>
module Text.Atom.Types (module Text.Atom.Types) where

-- {{{ Imports
import           Control.Monad
import           Data.Text as Text
import           Data.Text.Prettyprint.Doc
import           Data.Time.Clock
import           Data.Time.LocalTime ()
import           Data.Typeable
import           Data.XML.Types as XML
import           GHC.Generics
import           Refined
import           URI.ByteString
import qualified Text.Show as Text
-- }}}

-- | 'Predicate' on 'Text', true iff text is null.
data Null deriving(Typeable)

instance Predicate Null Text where
  validate :: Proxy Null -> Text -> Maybe RefineException
validate Proxy Null
p Text
value = if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
Text.null Text
value
    then RefineException -> Maybe RefineException
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Null -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf Proxy Null
p) (Text -> RefineException) -> Text -> RefineException
forall a b. (a -> b) -> a -> b
$ Text
"Text is not null: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
value
    else Maybe RefineException
forall a. Maybe a
Nothing

data AtomURI = forall a . AtomURI (URIRef a)

withAtomURI :: (forall a . URIRef a -> b) -> AtomURI -> b
withAtomURI :: (forall a. URIRef a -> b) -> AtomURI -> b
withAtomURI forall a. URIRef a -> b
f (AtomURI URIRef a
a) = URIRef a -> b
forall a. URIRef a -> b
f URIRef a
a


instance Eq AtomURI where
  AtomURI a :: URIRef a
a@URI{} == :: AtomURI -> AtomURI -> Bool
== AtomURI b :: URIRef a
b@URI{} = URIRef a
a URIRef a -> URIRef a -> Bool
forall a. Eq a => a -> a -> Bool
== URIRef a
URIRef a
b
  AtomURI a :: URIRef a
a@RelativeRef{} == AtomURI b :: URIRef a
b@RelativeRef{} = URIRef a
a URIRef a -> URIRef a -> Bool
forall a. Eq a => a -> a -> Bool
== URIRef a
URIRef a
b
  AtomURI
_ == AtomURI
_ = Bool
False
instance Ord AtomURI where
  AtomURI a :: URIRef a
a@URI{} compare :: AtomURI -> AtomURI -> Ordering
`compare` AtomURI b :: URIRef a
b@URI{} = URIRef a
a URIRef a -> URIRef a -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` URIRef a
URIRef a
b
  AtomURI a :: URIRef a
a@RelativeRef{} `compare` AtomURI b :: URIRef a
b@RelativeRef{} = URIRef a
a URIRef a -> URIRef a -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` URIRef a
URIRef a
b
  AtomURI a :: URIRef a
a@URI{} `compare` AtomURI
_ = Ordering
LT
  AtomURI a :: URIRef a
a@RelativeRef{} `compare` AtomURI
b = AtomURI
b AtomURI -> AtomURI -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` URIRef a -> AtomURI
forall a. URIRef a -> AtomURI
AtomURI URIRef a
a
instance Text.Show AtomURI where
  show :: AtomURI -> String
show (AtomURI a :: URIRef a
a@URI{}) = URIRef a -> String
forall b a. (Show a, IsString b) => a -> b
show URIRef a
a
  show (AtomURI a :: URIRef a
a@RelativeRef{}) = URIRef a -> String
forall b a. (Show a, IsString b) => a -> b
show URIRef a
a


data TextType = TypeText | TypeHTML
  deriving(TextType -> TextType -> Bool
(TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool) -> Eq TextType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextType -> TextType -> Bool
$c/= :: TextType -> TextType -> Bool
== :: TextType -> TextType -> Bool
$c== :: TextType -> TextType -> Bool
Eq, Eq TextType
Eq TextType
-> (TextType -> TextType -> Ordering)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool)
-> (TextType -> TextType -> TextType)
-> (TextType -> TextType -> TextType)
-> Ord TextType
TextType -> TextType -> Bool
TextType -> TextType -> Ordering
TextType -> TextType -> TextType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TextType -> TextType -> TextType
$cmin :: TextType -> TextType -> TextType
max :: TextType -> TextType -> TextType
$cmax :: TextType -> TextType -> TextType
>= :: TextType -> TextType -> Bool
$c>= :: TextType -> TextType -> Bool
> :: TextType -> TextType -> Bool
$c> :: TextType -> TextType -> Bool
<= :: TextType -> TextType -> Bool
$c<= :: TextType -> TextType -> Bool
< :: TextType -> TextType -> Bool
$c< :: TextType -> TextType -> Bool
compare :: TextType -> TextType -> Ordering
$ccompare :: TextType -> TextType -> Ordering
$cp1Ord :: Eq TextType
Ord, (forall x. TextType -> Rep TextType x)
-> (forall x. Rep TextType x -> TextType) -> Generic TextType
forall x. Rep TextType x -> TextType
forall x. TextType -> Rep TextType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextType x -> TextType
$cfrom :: forall x. TextType -> Rep TextType x
Generic, Int -> TextType -> ShowS
[TextType] -> ShowS
TextType -> String
(Int -> TextType -> ShowS)
-> (TextType -> String) -> ([TextType] -> ShowS) -> Show TextType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextType] -> ShowS
$cshowList :: [TextType] -> ShowS
show :: TextType -> String
$cshow :: TextType -> String
showsPrec :: Int -> TextType -> ShowS
$cshowsPrec :: Int -> TextType -> ShowS
Show)

-- | An atom text construct.
data AtomText = AtomPlainText TextType Text
              | AtomXHTMLText XML.Element

deriving instance Eq AtomText
deriving instance Ord AtomText
deriving instance Generic AtomText
deriving instance Show AtomText

-- | An atom person construct.
data AtomPerson = AtomPerson
  { AtomPerson -> Refined (Not Null) Text
personName  :: Refined (Not Null) Text
  , AtomPerson -> Text
personEmail :: Text
  , AtomPerson -> Maybe AtomURI
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
  { AtomCategory -> Refined (Not Null) Text
categoryTerm   :: Refined (Not Null) Text
  , AtomCategory -> Text
categoryScheme :: Text
  , AtomCategory -> Text
categoryLabel  :: Text
  }

deriving instance Eq AtomCategory
deriving instance Ord AtomCategory
deriving instance Generic AtomCategory
deriving instance Show AtomCategory

-- | The @atom:link@ element.
data AtomLink = AtomLink
  { AtomLink -> AtomURI
linkHref   :: AtomURI
  , AtomLink -> Text
linkRel    :: Text
  , AtomLink -> Text
linkType   :: Text
  , AtomLink -> Text
linkLang   :: Text
  , AtomLink -> Text
linkTitle  :: Text
  , AtomLink -> Text
linkLength :: Text
  }

deriving instance Eq AtomLink
deriving instance Ord AtomLink
deriving instance Generic AtomLink
deriving instance Show AtomLink

-- | The @atom:generator@ element.
data AtomGenerator = AtomGenerator
  { AtomGenerator -> Maybe AtomURI
generatorUri     :: Maybe AtomURI
  , AtomGenerator -> Text
generatorVersion :: Text
  , AtomGenerator -> Refined (Not Null) Text
generatorContent :: Refined (Not Null) Text
  }

deriving instance Eq AtomGenerator
deriving instance Ord AtomGenerator
deriving instance Generic AtomGenerator
deriving instance Show AtomGenerator

-- | The @atom:source@ element.
data AtomSource = AtomSource
  { AtomSource -> [AtomPerson]
sourceAuthors      :: [AtomPerson]
  , AtomSource -> [AtomCategory]
sourceCategories   :: [AtomCategory]
  , AtomSource -> [AtomPerson]
sourceContributors :: [AtomPerson]
  , AtomSource -> Maybe AtomGenerator
sourceGenerator    :: Maybe AtomGenerator
  , AtomSource -> Maybe AtomURI
sourceIcon         :: Maybe AtomURI
  , AtomSource -> Text
sourceId           :: Text
  , AtomSource -> [AtomLink]
sourceLinks        :: [AtomLink]
  ,          :: Maybe AtomURI
  , AtomSource -> Maybe AtomText
sourceRights       :: Maybe AtomText
  , AtomSource -> Maybe AtomText
sourceSubtitle     :: Maybe AtomText
  , AtomSource -> Maybe AtomText
sourceTitle        :: Maybe AtomText
  , AtomSource -> Maybe UTCTime
sourceUpdated      :: Maybe UTCTime
  }

deriving instance Eq AtomSource
deriving instance Ord AtomSource
deriving instance Generic AtomSource
deriving instance Show AtomSource

type ContentType = Text

-- | The @atom:content@ element.
data AtomContent = AtomContentInlineText TextType Text
                 | AtomContentInlineXHTML XML.Element
                 | AtomContentInlineOther ContentType Text
                 | AtomContentOutOfLine ContentType AtomURI

deriving instance Eq AtomContent
deriving instance Ord AtomContent
deriving instance Generic AtomContent
deriving instance Show AtomContent

-- | The @atom:entry@ element.
data AtomEntry = AtomEntry
  { AtomEntry -> [AtomPerson]
entryAuthors      :: [AtomPerson]
  , AtomEntry -> [AtomCategory]
entryCategories   :: [AtomCategory]
  , AtomEntry -> Maybe AtomContent
entryContent      :: Maybe AtomContent
  , AtomEntry -> [AtomPerson]
entryContributors :: [AtomPerson]
  , AtomEntry -> Text
entryId           :: Text
  , AtomEntry -> [AtomLink]
entryLinks        :: [AtomLink]
  , AtomEntry -> Maybe UTCTime
entryPublished    :: Maybe UTCTime
  , AtomEntry -> Maybe AtomText
entryRights       :: Maybe AtomText
  , AtomEntry -> Maybe AtomSource
entrySource       :: Maybe AtomSource
  , AtomEntry -> Maybe AtomText
entrySummary      :: Maybe AtomText
  , AtomEntry -> AtomText
entryTitle        :: AtomText
  , AtomEntry -> UTCTime
entryUpdated      :: UTCTime
  }

deriving instance Eq AtomEntry
deriving instance Ord AtomEntry
deriving instance Generic AtomEntry
deriving instance Show AtomEntry

-- | The @atom:feed@ element.
data AtomFeed = AtomFeed
  { AtomFeed -> [AtomPerson]
feedAuthors      :: [AtomPerson]
  , AtomFeed -> [AtomCategory]
feedCategories   :: [AtomCategory]
  , AtomFeed -> [AtomPerson]
feedContributors :: [AtomPerson]
  , AtomFeed -> [AtomEntry]
feedEntries      :: [AtomEntry]
  , AtomFeed -> Maybe AtomGenerator
feedGenerator    :: Maybe AtomGenerator
  , AtomFeed -> Maybe AtomURI
feedIcon         :: Maybe AtomURI
  , AtomFeed -> Text
feedId           :: Text
  , AtomFeed -> [AtomLink]
feedLinks        :: [AtomLink]
  ,          :: Maybe AtomURI
  , AtomFeed -> Maybe AtomText
feedRights       :: Maybe AtomText
  , AtomFeed -> Maybe AtomText
feedSubtitle     :: Maybe AtomText
  , AtomFeed -> AtomText
feedTitle        :: AtomText
  , AtomFeed -> UTCTime
feedUpdated      :: UTCTime
  }

deriving instance Eq AtomFeed
deriving instance Ord AtomFeed
deriving instance Generic AtomFeed
deriving instance Show AtomFeed